From git at git.haskell.org Fri Jan 2 12:34:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jan 2015 12:34:25 +0000 (UTC) Subject: [commit: ghc] master: Comments only, mainly on superclasses (a9dc427) Message-ID: <20150102123425.9A8B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a9dc427770a02f8df03b7b80d3f76b4d191f49d8/ghc >--------------------------------------------------------------- commit a9dc427770a02f8df03b7b80d3f76b4d191f49d8 Author: Simon Peyton Jones Date: Tue Dec 30 16:36:36 2014 +0000 Comments only, mainly on superclasses This tidies up all the comments about recursive superclasses and when to add superclasses. Lots of duplicate and contradictory comments removed! >--------------------------------------------------------------- a9dc427770a02f8df03b7b80d3f76b4d191f49d8 compiler/typecheck/TcCanonical.hs | 128 ++++++---- compiler/typecheck/TcInstDcls.hs | 5 +- compiler/typecheck/TcInteract.hs | 485 ++------------------------------------ compiler/typecheck/TcSMonad.hs | 167 ++++++++++++- 4 files changed, 264 insertions(+), 521 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a9dc427770a02f8df03b7b80d3f76b4d191f49d8 From git at git.haskell.org Fri Jan 2 12:34:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jan 2015 12:34:28 +0000 (UTC) Subject: [commit: ghc] master: Eliminate the final two calls to xCtEvidence (fd97d2a) Message-ID: <20150102123428.2ED893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fd97d2a77599e7f4a6e5c01bc7da9b12bd676e21/ghc >--------------------------------------------------------------- commit fd97d2a77599e7f4a6e5c01bc7da9b12bd676e21 Author: Simon Peyton Jones Date: Wed Dec 31 10:02:24 2014 +0000 Eliminate the final two calls to xCtEvidence I always found calls to TcCanonical.xCtEvidence hard to grok; and I found that we only had two left. This patch eliminates them, along with xCtEvidence, its accompanying comments, and the auxiliary XEvTerm type. The two remaining calls were these: * One was in newSCWorkFromFlavored, where we'd already done case-splitting for given/wanted/derived. So inlining the xCtEvidence made the code simpler, clearer, and faster. * The other was in canTuple; here all of xCtEvidence's functionality was needed, but inlining again made a net gain in code size and clarity. >--------------------------------------------------------------- fd97d2a77599e7f4a6e5c01bc7da9b12bd676e21 compiler/typecheck/TcCanonical.hs | 82 ++++++++++++--------------------------- compiler/typecheck/TcSMonad.hs | 9 ----- 2 files changed, 24 insertions(+), 67 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index ee8b201..a5b0d99 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -186,13 +186,27 @@ canEvNC ev -} canTuple :: CtEvidence -> [PredType] -> TcS (StopOrContinue Ct) -canTuple ev tys - = do { traceTcS "can_pred" (text "TuplePred!") - ; let xcomp = EvTupleMk - xdecomp x = zipWith (\_ i -> EvTupleSel x i) tys [0..] - ; xCtEvidence ev (XEvTerm tys xcomp xdecomp) +canTuple ev preds + | CtWanted { ctev_evar = evar, ctev_loc = loc } <- ev + = do { new_evars <- mapM (newWantedEvVar loc) preds + ; setEvBind evar (EvTupleMk (map (ctEvTerm . fst) new_evars)) + ; emitWorkNC (freshGoals new_evars) + -- Note the "NC": these are fresh goals, not necessarily canonical + ; stopWith ev "Decomposed tuple constraint" } + + | CtGiven { ctev_evtm = tm, ctev_loc = loc } <- ev + = do { let mk_pr pred i = (pred, EvTupleSel tm i) + ; given_evs <- newGivenEvVars loc (zipWith mk_pr preds [0..]) + ; emitWorkNC given_evs + ; stopWith ev "Decomposed tuple constraint" } + + | CtDerived { ctev_loc = loc } <- ev + = do { mapM_ (emitNewDerived loc) preds ; stopWith ev "Decomposed tuple constraint" } + | otherwise = panic "canTuple" + + {- ************************************************************************ * * @@ -339,13 +353,11 @@ newSCWorkFromFlavored flavor cls xis = return () -- Deriveds don't yield more superclasses because we will -- add them transitively in the case of wanteds. - | isGiven flavor + | CtGiven { ctev_evtm = ev_tm, ctev_loc = loc } <- flavor = do { let sc_theta = immSuperClasses cls xis - xev_decomp x = zipWith (\_ i -> EvSuperClass x i) sc_theta [0..] - xev = XEvTerm { ev_preds = sc_theta - , ev_comp = panic "Can't compose for given!" - , ev_decomp = xev_decomp } - ; xCtEvidence flavor xev } + mk_pr sc_pred i = (sc_pred, EvSuperClass ev_tm i) + ; given_evs <- newGivenEvVars loc (zipWith mk_pr sc_theta [0..]) + ; emitWorkNC given_evs } | isEmptyVarSet (tyVarsOfTypes xis) = return () -- Wanteds with no variables yield no deriveds. @@ -683,8 +695,7 @@ try_decompose_nom_app ev ty1 ty2 | otherwise -- Neither is an AppTy = canEqNC ev NomEq ty1 ty2 where - -- do_decompose is like xCtEvidence, but recurses - -- to try_decompose_nom_app to decompose a chain of AppTys + -- Recurses to try_decompose_nom_app to decompose a chain of AppTys do_decompose s1 t1 s2 t2 | CtDerived { ctev_loc = loc } <- ev = do { emitNewDerived loc (mkTcEqPred t1 t2) @@ -1359,31 +1370,6 @@ itself, and so on. See Note [Occurs check expansion] in TcType -} {- -Note [xCtEvidence] -~~~~~~~~~~~~~~~~~~ -A call might look like this: - - xCtEvidence ev evidence-transformer - - ev is Given => use ev_decomp to create new Givens for ev_preds, - and return them - - ev is Wanted => create new wanteds for ev_preds, - use ev_comp to bind ev, - return fresh wanteds (ie ones not cached in inert_cans or solved) - - ev is Derived => create new deriveds for ev_preds - (unless cached in inert_cans or solved) - -Note: The [CtEvidence] returned is a subset of the subgoal-preds passed in - Ones that are already cached are not returned - -Example - ev : Tree a b ~ Tree c d - xCtEvidence ev [a~c, b~d] (XEvTerm { ev_comp = \[c1 c2]. c1 c2 - , ev_decomp = \c. [nth 1 c, nth 2 c] }) - (\fresh-goals. stuff) - Note [Bind new Givens immediately] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ For Givens we make new EvVars and bind them immediately. We don't worry @@ -1398,26 +1384,6 @@ But that superclass selector can't (yet) appear in a coercion See Note [Coercion evidence terms] in TcEvidence. -} -xCtEvidence :: CtEvidence -- Original evidence - -> XEvTerm -- Instructions about how to manipulate evidence - -> TcS () - -xCtEvidence (CtWanted { ctev_evar = evar, ctev_loc = loc }) - (XEvTerm { ev_preds = ptys, ev_comp = comp_fn }) - = do { new_evars <- mapM (newWantedEvVar loc) ptys - ; setEvBind evar (comp_fn (map (ctEvTerm . fst) new_evars)) - ; emitWorkNC (freshGoals new_evars) } - -- Note the "NC": these are fresh goals, not necessarily canonical - -xCtEvidence (CtGiven { ctev_evtm = tm, ctev_loc = loc }) - (XEvTerm { ev_preds = ptys, ev_decomp = decomp_fn }) - = ASSERT( equalLength ptys (decomp_fn tm) ) - do { given_evs <- newGivenEvVars loc (ptys `zip` decomp_fn tm) - ; emitWorkNC given_evs } - -xCtEvidence (CtDerived { ctev_loc = loc }) - (XEvTerm { ev_preds = ptys }) - = mapM_ (emitNewDerived loc) ptys ----------------------------- data StopOrContinue a diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 56c8a9a..d62f098 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -23,7 +23,6 @@ module TcSMonad ( wrapErrTcS, wrapWarnTcS, -- Evidence creation and transformation - XEvTerm(..), Freshness(..), freshGoals, isFresh, newTcEvBinds, newWantedEvVar, newWantedEvVarNC, @@ -1752,14 +1751,6 @@ instFlexiTcSHelperTcS n k = wrapTcS (instFlexiTcSHelper n k) -- Creating and setting evidence variables and CtFlavors -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -data XEvTerm - = XEvTerm { ev_preds :: [PredType] -- New predicate types - , ev_comp :: [EvTerm] -> EvTerm -- How to compose evidence - , ev_decomp :: EvTerm -> [EvTerm] -- How to decompose evidence - -- In both ev_comp and ev_decomp, the [EvTerm] is 1-1 with ev_preds - -- and each EvTerm has type of the corresponding EvPred - } - data Freshness = Fresh | Cached isFresh :: Freshness -> Bool From git at git.haskell.org Fri Jan 2 12:34:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Jan 2015 12:34:30 +0000 (UTC) Subject: [commit: ghc] master: When solving one Given from another, use the depth to control which way round (d8d0031) Message-ID: <20150102123430.B99A33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d8d003185a4bca1a1ebbadb5111118ef37bbc83a/ghc >--------------------------------------------------------------- commit d8d003185a4bca1a1ebbadb5111118ef37bbc83a Author: Simon Peyton Jones Date: Wed Dec 31 10:21:43 2014 +0000 When solving one Given from another, use the depth to control which way round See Note [Replacement vs keeping]. There's a bit further to go with this change (to report unused givens). But it's already an improvement; see the latent bug described in the Note. >--------------------------------------------------------------- d8d003185a4bca1a1ebbadb5111118ef37bbc83a compiler/typecheck/TcInteract.hs | 59 ++++++++++++++++++++++++++++++++++++---- compiler/typecheck/TcRnTypes.hs | 5 +++- compiler/typecheck/TcSMonad.hs | 2 +- compiler/typecheck/TcType.hs | 2 +- 4 files changed, 60 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 8b85a71..79a61a3 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -450,7 +450,11 @@ interactWithInertsStage wi -- CHoleCan are put straight into inert_frozen, so never get here -- CNonCanonical have been canonicalised -data InteractResult = IRKeep | IRReplace | IRDelete +data InteractResult + = IRKeep -- Keep the existing inert constraint in the inert set + | IRReplace -- Replace the existing inert constraint with the work item + | IRDelete -- Delete the existing inert constraint from the inert set + instance Outputable InteractResult where ppr IRKeep = ptext (sLit "keep") ppr IRReplace = ptext (sLit "replace") @@ -479,12 +483,57 @@ solveOneFromTheOther ev_i ev_w = do { setEvBind ev_id (ctEvTerm ev_w) ; return (IRReplace, True) } - | otherwise -- If both are Given, we already have evidence; no need to duplicate - -- But the work item *overrides* the inert item (hence IRReplace) - -- See Note [Shadowing of Implicit Parameters] - = return (IRReplace, True) + | otherwise -- Both are Given + = return (if use_replacement then IRReplace else IRKeep, True) + + where + pred = ctEvPred ev_i + loc_i = ctEvLoc ev_i + loc_w = ctEvLoc ev_w + lvl_i = ctLocLevel loc_i + lvl_w = ctLocLevel loc_w + + use_replacement -- See Note [Replacement vs keeping] + | isIPPred pred = lvl_w > lvl_i + | otherwise = lvl_w < lvl_i {- +Note [Replacement vs keeping] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When we have two Given constraints both of type (C tys), say, which should +we keep? + + * For implicit parameters we want to keep the innermost (deepest) + one, so that it overrides the outer one. + See Note [Shadowing of Implicit Parameters] + + * For everything else, we want to keep the outermost one. Reason: that + makes it more likely that the inner one will turn out to be unused, + and can be reported as redundant. + +When there is a choice, use IRKeep rather than IRReplace, to avoid unnecesary +munging of the inert set. + +Doing the depth-check for implicit parameters, rather than making the work item +always overrride, is important. Consider + + data T a where { T1 :: (?x::Int) => T Int; T2 :: T a } + + f :: (?x::a) => T a -> Int + f T1 = ?x + f T2 = 3 + +We have a [G] (?x::a) in the inert set, and at the pattern match on T1 we add +two new givens in the work-list: [G] (?x::Int) + [G] (a ~ Int) +Now consider these steps + - process a~Int, kicking out (?x::a) + - process (?x::Int), the inner given, adding to inert set + - process (?x::a), the outer given, overriding the inner given +Wrong! The depth-check ensures that the inner implicit parameter wins. +(Actually I think that the order in which the work-list is processed means +that this chain of events won't happen, but that's very fragile.) + ********************************************************************************* * * interactIrred diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 31624a8..c2cc36d 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -67,7 +67,7 @@ module TcRnTypes( SubGoalCounter(..), SubGoalDepth, initialSubGoalDepth, maxSubGoalDepth, bumpSubGoalDepth, subGoalCounterValue, subGoalDepthExceeded, - CtLoc(..), ctLocSpan, ctLocEnv, ctLocOrigin, + CtLoc(..), ctLocSpan, ctLocEnv, ctLocLevel, ctLocOrigin, ctLocDepth, bumpCtLocDepth, setCtLocOrigin, setCtLocEnv, setCtLocSpan, CtOrigin(..), pprCtOrigin, @@ -1835,6 +1835,9 @@ mkGivenLoc tclvl skol_info env ctLocEnv :: CtLoc -> TcLclEnv ctLocEnv = ctl_env +ctLocLevel :: CtLoc -> TcLevel +ctLocLevel loc = tcl_tclvl (ctLocEnv loc) + ctLocDepth :: CtLoc -> SubGoalDepth ctLocDepth = ctl_depth diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index d62f098..d7c58d5 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -828,7 +828,7 @@ getNoGivenEqs tclvl skol_tvs -- i.e. the current level ev_given_here ev = isGiven ev - && tclvl == tcl_tclvl (ctl_env (ctEvLoc ev)) + && tclvl == ctLocLevel (ctEvLoc ev) add_fsk :: Ct -> VarSet -> VarSet add_fsk ct fsks | CFunEqCan { cc_fsk = tv, cc_ev = ev } <- ct diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index e760cc4..e0ce00f 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -414,7 +414,7 @@ data UserTypeCtxt ************************************************************************ -} -newtype TcLevel = TcLevel Int deriving( Eq ) +newtype TcLevel = TcLevel Int deriving( Eq, Ord ) -- See Note [TcLevel and untouchable type variables] for what this Int is {- From git at git.haskell.org Sat Jan 3 05:24:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 05:24:14 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9953' created Message-ID: <20150103052414.7B55C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T9953 Referencing: 969d73ccce9e1c1ba5827b76d9c7ebe946fd9e54 From git at git.haskell.org Sat Jan 3 05:24:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 05:24:17 +0000 (UTC) Subject: [commit: ghc] wip/T9953: Add psEqSpec field to PatSyn (969d73c) Message-ID: <20150103052417.2DDAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9953 Link : http://ghc.haskell.org/trac/ghc/changeset/969d73ccce9e1c1ba5827b76d9c7ebe946fd9e54/ghc >--------------------------------------------------------------- commit 969d73ccce9e1c1ba5827b76d9c7ebe946fd9e54 Author: Dr. ERDI Gergo Date: Sat Jan 3 13:01:24 2015 +0800 Add psEqSpec field to PatSyn >--------------------------------------------------------------- 969d73ccce9e1c1ba5827b76d9c7ebe946fd9e54 compiler/basicTypes/PatSyn.hs | 28 +++++++++++++++++++--------- compiler/iface/BuildTyCl.hs | 6 ++++-- compiler/iface/IfaceSyn.hs | 9 +++++++-- compiler/iface/MkIface.hs | 10 ++++++++-- compiler/iface/TcIface.hs | 6 ++++-- compiler/typecheck/TcPatSyn.hs | 1 + 6 files changed, 43 insertions(+), 17 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 969d73ccce9e1c1ba5827b76d9c7ebe946fd9e54 From git at git.haskell.org Sat Jan 3 07:55:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 07:55:55 +0000 (UTC) Subject: [commit: ghc] wip/T9953: Add psEqSpec field to PatSyn (2e25633) Message-ID: <20150103075555.C2FDD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9953 Link : http://ghc.haskell.org/trac/ghc/changeset/2e2563376b6fa2b382e046e87a3cb132594a6dfb/ghc >--------------------------------------------------------------- commit 2e2563376b6fa2b382e046e87a3cb132594a6dfb Author: Dr. ERDI Gergo Date: Sat Jan 3 14:46:00 2015 +0800 Add psEqSpec field to PatSyn >--------------------------------------------------------------- 2e2563376b6fa2b382e046e87a3cb132594a6dfb compiler/basicTypes/PatSyn.hs | 28 +++++++++++++++++++--------- compiler/iface/BuildTyCl.hs | 6 ++++-- compiler/iface/IfaceSyn.hs | 9 +++++++-- compiler/iface/MkIface.hs | 10 ++++++++-- compiler/iface/TcIface.hs | 6 ++++-- compiler/typecheck/TcPatSyn.hs | 11 +++++++++-- 6 files changed, 51 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2e2563376b6fa2b382e046e87a3cb132594a6dfb From git at git.haskell.org Sat Jan 3 07:55:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 07:55:58 +0000 (UTC) Subject: [commit: ghc] wip/T9953: Extract implicit equalities from result type of pattern synonym type signature (33b349c) Message-ID: <20150103075558.5FC2B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9953 Link : http://ghc.haskell.org/trac/ghc/changeset/33b349c483886d9d762bbd65751c38070c435f12/ghc >--------------------------------------------------------------- commit 33b349c483886d9d762bbd65751c38070c435f12 Author: Dr. ERDI Gergo Date: Sat Jan 3 15:37:36 2015 +0800 Extract implicit equalities from result type of pattern synonym type signature >--------------------------------------------------------------- 33b349c483886d9d762bbd65751c38070c435f12 compiler/typecheck/TcPatSyn.hs | 28 ++++++++++++++++++++++++++++ 1 file changed, 28 insertions(+) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index e444ee4..224abe2 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -130,6 +130,34 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; checkTc (length arg_names == ty_arity) (wrongNumberOfParmsErr ty_arity) + -- Recover implicit type equalities + ; (pat_ty, spec_tvs, spec_eqs) <- case tcSplitTyConApp_maybe pat_ty of + Nothing -> return (pat_ty, [], []) + Just (tyCon, conArgs) -> do + { spec_eqs <- forM conArgs $ \conArg -> do + { tv <- zonkQuantifiedTyVar =<< newMetaTyVar SigTv (typeKind conArg) + ; return (tv, conArg) } + ; let spec_tvs = map fst spec_eqs + pat_ty' = mkTyConApp tyCon (map mkTyVarTy spec_tvs) + ; return (pat_ty', spec_tvs, spec_eqs) } + ; traceTc "tcCheckPatSynDecl spec {" $ + ppr pat_ty $$ + ppr spec_tvs $$ + ppr spec_eqs + + ; let con_arg_tvs = tcTyVarsOfTypes (map snd spec_eqs) + ; univ_tvs <- return $ filter (not . (`elemVarSet` con_arg_tvs)) univ_tvs ++ spec_tvs + ; ex_tvs <- return $ ex_tvs ++ varSetElems con_arg_tvs + -- ex_tys' = ex_tys ++ map mkTyVarTy (varSetElems con_arg_tvs) + ; prov_theta <- return $ prov_theta ++ [ mkEqPred (mkTyVarTy tv) conArg + | (tv, conArg) <- spec_eqs + ] + + ; traceTc "tcCheckPatSynDecl spec }" $ + ppr univ_tvs $$ + ppr ex_tvs $$ + ppr prov_theta + -- Typecheck the pattern against pat_ty, then unify the type of args -- against arg_tys, with ex_tvs changed to SigTyVars. -- We get out of this: From git at git.haskell.org Sat Jan 3 07:56:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 07:56:00 +0000 (UTC) Subject: [commit: ghc] wip/T9953: Pass spec_eqs to tc_patsyn_finish (67049f1) Message-ID: <20150103075600.F019F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9953 Link : http://ghc.haskell.org/trac/ghc/changeset/67049f11ec5f5498729a44a039bea414ea0b0491/ghc >--------------------------------------------------------------- commit 67049f11ec5f5498729a44a039bea414ea0b0491 Author: Dr. ERDI Gergo Date: Sat Jan 3 15:50:48 2015 +0800 Pass spec_eqs to tc_patsyn_finish >--------------------------------------------------------------- 67049f11ec5f5498729a44a039bea414ea0b0491 compiler/typecheck/TcPatSyn.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 224abe2..9a10ad1 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -98,6 +98,7 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; tc_patsyn_finish lname dir is_infix lpat' (univ_tvs, req_theta, ev_binds, req_dicts) (ex_tvs, map mkTyVarTy ex_tvs, prov_theta, emptyTcEvBinds, prov_dicts) + [] (zip args $ repeat idHsWrapper) pat_ty } @@ -194,6 +195,7 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; tc_patsyn_finish lname dir is_infix lpat' (univ_tvs, req_theta, req_ev_binds, req_dicts) (ex_tvs, ex_tys, prov_theta, prov_ev_binds, prov_dicts) + spec_eqs wrapped_args pat_ty } where @@ -212,17 +214,20 @@ tc_patsyn_finish :: Located Name -> LPat Id -> ([TcTyVar], [PredType], TcEvBinds, [EvVar]) -> ([TcTyVar], [TcType], [PredType], TcEvBinds, [EvVar]) + -> [(TcTyVar, TcType)] -> [(Var, HsWrapper)] -> TcType -> TcM (PatSyn, LHsBinds Id) tc_patsyn_finish lname dir is_infix lpat' (univ_tvs, req_theta, req_ev_binds, req_dicts) (ex_tvs, subst, prov_theta, prov_ev_binds, prov_dicts) + spec_eqs wrapped_args pat_ty = do { traceTc "tc_patsyn_finish" $ ppr (univ_tvs, req_theta, req_ev_binds, req_dicts) $$ ppr (ex_tvs, subst, prov_theta, prov_ev_binds, prov_dicts) $$ + ppr spec_eqs $$ ppr wrapped_args $$ ppr pat_ty @@ -237,7 +242,7 @@ tc_patsyn_finish lname dir is_infix lpat' ; let patSyn = mkPatSyn (unLoc lname) is_infix (univ_tvs, req_theta) (ex_tvs, prov_theta) - [] + spec_eqs arg_tys pat_ty matcher_id builder_id From git at git.haskell.org Sat Jan 3 13:01:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 13:01:40 +0000 (UTC) Subject: [commit: ghc] wip/T9953: Pass spec_eqs to tc_patsyn_finish (fe7651c) Message-ID: <20150103130140.948D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9953 Link : http://ghc.haskell.org/trac/ghc/changeset/fe7651ca5cbf7eff75b6197de4acf4473aa604fd/ghc >--------------------------------------------------------------- commit fe7651ca5cbf7eff75b6197de4acf4473aa604fd Author: Dr. ERDI Gergo Date: Sat Jan 3 15:50:48 2015 +0800 Pass spec_eqs to tc_patsyn_finish >--------------------------------------------------------------- fe7651ca5cbf7eff75b6197de4acf4473aa604fd compiler/typecheck/TcPatSyn.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index d0b316e..2f60f3c 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -98,6 +98,7 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; tc_patsyn_finish lname dir is_infix lpat' (univ_tvs, req_theta, ev_binds, req_dicts) (ex_tvs, map mkTyVarTy ex_tvs, prov_theta, emptyTcEvBinds, prov_dicts) + [] (zip args $ repeat idHsWrapper) pat_ty } @@ -194,6 +195,7 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; tc_patsyn_finish lname dir is_infix lpat' (univ_tvs, req_theta, req_ev_binds, req_dicts) (ex_tvs, ex_tys, prov_theta, prov_ev_binds, prov_dicts) + spec_eqs wrapped_args pat_ty } where @@ -212,17 +214,20 @@ tc_patsyn_finish :: Located Name -> LPat Id -> ([TcTyVar], [PredType], TcEvBinds, [EvVar]) -> ([TcTyVar], [TcType], [PredType], TcEvBinds, [EvVar]) + -> [(TcTyVar, TcType)] -> [(Var, HsWrapper)] -> TcType -> TcM (PatSyn, LHsBinds Id) tc_patsyn_finish lname dir is_infix lpat' (univ_tvs, req_theta, req_ev_binds, req_dicts) (ex_tvs, subst, prov_theta, prov_ev_binds, prov_dicts) + spec_eqs wrapped_args pat_ty = do { traceTc "tc_patsyn_finish" $ ppr (univ_tvs, req_theta, req_ev_binds, req_dicts) $$ ppr (ex_tvs, subst, prov_theta, prov_ev_binds, prov_dicts) $$ + ppr spec_eqs $$ ppr wrapped_args $$ ppr pat_ty @@ -237,7 +242,7 @@ tc_patsyn_finish lname dir is_infix lpat' ; let patSyn = mkPatSyn (unLoc lname) is_infix (univ_tvs, req_theta) (ex_tvs, prov_theta) - [] + spec_eqs arg_tys pat_ty matcher_id builder_id From git at git.haskell.org Sat Jan 3 13:01:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 13:01:43 +0000 (UTC) Subject: [commit: ghc] wip/T9953: Extract implicit equalities from result type of pattern synonym type signature (355a5fa) Message-ID: <20150103130143.38D8B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9953 Link : http://ghc.haskell.org/trac/ghc/changeset/355a5fa25dafdfcbfca655db980bc2fc5b9211b6/ghc >--------------------------------------------------------------- commit 355a5fa25dafdfcbfca655db980bc2fc5b9211b6 Author: Dr. ERDI Gergo Date: Sat Jan 3 15:37:36 2015 +0800 Extract implicit equalities from result type of pattern synonym type signature >--------------------------------------------------------------- 355a5fa25dafdfcbfca655db980bc2fc5b9211b6 compiler/typecheck/TcPatSyn.hs | 28 ++++++++++++++++++++++++++++ 1 file changed, 28 insertions(+) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index e444ee4..d0b316e 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -130,6 +130,34 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; checkTc (length arg_names == ty_arity) (wrongNumberOfParmsErr ty_arity) + -- Recover implicit type equalities + ; (pat_ty, spec_tvs, spec_eqs) <- case tcSplitTyConApp_maybe pat_ty of + Nothing -> return (pat_ty, [], []) + Just (tyCon, conArgs) -> do + { spec_eqs <- forM conArgs $ \conArg -> do + { tv <- zonkQuantifiedTyVar =<< newMetaTyVar SigTv (typeKind conArg) + ; return (tv, conArg) } + ; let spec_tvs = map fst spec_eqs + pat_ty' = mkTyConApp tyCon (map mkTyVarTy spec_tvs) + ; return (pat_ty', spec_tvs, spec_eqs) } + ; traceTc "tcCheckPatSynDecl spec {" $ + ppr pat_ty $$ + ppr spec_tvs $$ + ppr spec_eqs + + ; let con_arg_tvs = tcTyVarsOfTypes (map snd spec_eqs) + spec_theta = [ mkEqPred (mkTyVarTy tv) conArg + | (tv, conArg) <- spec_eqs ] + ; univ_tvs <- return $ filter (not . (`elemVarSet` con_arg_tvs)) univ_tvs ++ spec_tvs + ; ex_tvs <- return $ ex_tvs ++ varSetElems con_arg_tvs + -- ex_tys' = ex_tys ++ map mkTyVarTy (varSetElems con_arg_tvs) + ; prov_theta <- return $ prov_theta ++ spec_theta + + ; traceTc "tcCheckPatSynDecl spec }" $ + ppr univ_tvs $$ + ppr ex_tvs $$ + ppr prov_theta + -- Typecheck the pattern against pat_ty, then unify the type of args -- against arg_tys, with ex_tvs changed to SigTyVars. -- We get out of this: From git at git.haskell.org Sat Jan 3 13:39:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 13:39:41 +0000 (UTC) Subject: [commit: ghc] master: Mark T9938 as not broken (633814f) Message-ID: <20150103133941.D9C403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/633814f5664f135b3648e2a0a6f37e41e2b54ea0/ghc >--------------------------------------------------------------- commit 633814f5664f135b3648e2a0a6f37e41e2b54ea0 Author: Joachim Breitner Date: Sat Jan 3 14:39:52 2015 +0100 Mark T9938 as not broken either one of the two recent commits (d8d0031, fd97d2a) fixed it, or there is some nondeterminism here. See #9938. >--------------------------------------------------------------- 633814f5664f135b3648e2a0a6f37e41e2b54ea0 testsuite/tests/driver/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index fbacf2e..0bd8d5b 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -411,7 +411,7 @@ test('write_interface_make', normal, run_command, ['$MAKE -s --no-print-director test('T9776', normal, compile_fail, ['-frule-check']) test('T9938', - [ extra_clean(['T9938.hi', 'T9938.o', 'T9938']), expect_broken(9938)], + [ extra_clean(['T9938.hi', 'T9938.o', 'T9938']) ], run_command, ['$MAKE -s --no-print-directory T9938']) From git at git.haskell.org Sat Jan 3 20:31:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 20:31:35 +0000 (UTC) Subject: [commit: ghc] master: Don't do a half-hearted recompilation check in compileOne (af4d998) Message-ID: <20150103203135.CA8E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/af4d99803ea7676f88f250ad56a8c31c1c8cd5bc/ghc >--------------------------------------------------------------- commit af4d99803ea7676f88f250ad56a8c31c1c8cd5bc Author: Edward Z. Yang Date: Fri Dec 26 21:56:54 2014 -0800 Don't do a half-hearted recompilation check in compileOne Summary: The isNothing maybe_old_linkable check predates 48bc81ad466edfc80237015dbe5d78ba70eb5095, which fixed #481 by requiring recompilation information to be passed in as an argument to compileOne. As a result, the check here is redundant: the client has already taken a look at the object file to see if it is available or not. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonmar, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D594 >--------------------------------------------------------------- af4d99803ea7676f88f250ad56a8c31c1c8cd5bc compiler/main/DriverPipeline.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index fdec73e..e8be297 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -171,7 +171,7 @@ compileOne' m_tc_result mHscMessage -- -fforce-recomp should also work with --make let force_recomp = gopt Opt_ForceRecomp dflags source_modified - | force_recomp || isNothing maybe_old_linkable = SourceModified + | force_recomp = SourceModified | otherwise = source_modified0 object_filename = ml_obj_file location From git at git.haskell.org Sat Jan 3 20:31:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 20:31:39 +0000 (UTC) Subject: [commit: ghc] master: Fix #9243 so recompilation avoidance works with -fno-code (2223e19) Message-ID: <20150103203139.C52C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2223e196b2dc5340d70e58be011c279d381b4319/ghc >--------------------------------------------------------------- commit 2223e196b2dc5340d70e58be011c279d381b4319 Author: Edward Z. Yang Date: Sat Dec 27 10:50:01 2014 -0800 Fix #9243 so recompilation avoidance works with -fno-code Summary: Where we track timestamps of object files, also track timestamps for interface files. When -fno-code -fwrite-interface is enabled, use the interface file timestamp as an extra check to see if the files are up-to-date. We had to apply this logic to one-shot and make modes. This fix would be good to merge into 7.10; it makes using -fno-code -fwrite-interface for flywheel type checking usable. Signed-off-by: Edward Z. Yang Test Plan: validate and new test cases Reviewers: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D596 GHC Trac Issues: #9243 >--------------------------------------------------------------- 2223e196b2dc5340d70e58be011c279d381b4319 compiler/main/DriverPipeline.hs | 19 +++++++--- compiler/main/GhcMake.hs | 40 ++++++++++++++++++++-- compiler/main/HscTypes.hs | 4 +++ testsuite/.gitignore | 4 +++ testsuite/tests/driver/recomp001/Makefile | 1 - testsuite/tests/driver/{recomp001 => retc001}/A.hs | 0 .../tests/driver/{recomp001 => retc001}/B1.hs | 0 .../tests/driver/{recomp001 => retc001}/B2.hs | 0 testsuite/tests/driver/{recomp001 => retc001}/C.hs | 0 testsuite/tests/driver/retc001/Makefile | 24 +++++++++++++ testsuite/tests/driver/retc001/all.T | 5 +++ .../recomp001.stderr => retc001/retc001.stderr} | 0 testsuite/tests/driver/retc001/retc001.stdout | 7 ++++ .../tests/driver/{recomp002 => retc002}/Makefile | 6 ++-- testsuite/tests/driver/{recomp002 => retc002}/Q.hs | 2 -- testsuite/tests/driver/{recomp002 => retc002}/W.hs | 2 -- .../tests/driver/{recomp002 => retc002}/W.hs-boot | 2 -- .../tests/driver/{recomp001 => retc002}/all.T | 4 +-- .../recomp002.stderr => retc002/retc002.stderr} | 0 testsuite/tests/driver/retc002/retc002.stdout | 3 ++ testsuite/tests/driver/{recomp003 => retc003}/A.hs | 1 - .../tests/driver/{recomp003 => retc003}/Makefile | 12 ++++--- .../tests/driver/{recomp003 => retc003}/all.T | 4 +-- testsuite/tests/driver/retc003/retc003.stdout | 3 ++ 24 files changed, 117 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2223e196b2dc5340d70e58be011c279d381b4319 From git at git.haskell.org Sat Jan 3 22:16:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 22:16:29 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to latest 1.22 snapshot (d84742b) Message-ID: <20150103221629.316C53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d84742b0df27daa2b48464ca9e71f0101e9266cc/ghc >--------------------------------------------------------------- commit d84742b0df27daa2b48464ca9e71f0101e9266cc Author: Herbert Valerio Riedel Date: Sat Jan 3 23:17:14 2015 +0100 Update Cabal submodule to latest 1.22 snapshot >--------------------------------------------------------------- d84742b0df27daa2b48464ca9e71f0101e9266cc libraries/Cabal | 2 +- testsuite/tests/driver/T4437.hs | 4 ---- 2 files changed, 1 insertion(+), 5 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index d920a43..3a7f901 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit d920a43faba148ef63dff4d4a748ac5343380465 +Subproject commit 3a7f9015828745932a65d95fa985c98073fc7d95 diff --git a/testsuite/tests/driver/T4437.hs b/testsuite/tests/driver/T4437.hs index 4120ae9..dde6da7 100644 --- a/testsuite/tests/driver/T4437.hs +++ b/testsuite/tests/driver/T4437.hs @@ -33,10 +33,6 @@ expectedGhcOnlyExtensions :: [String] expectedGhcOnlyExtensions = ["RelaxedLayout", "AlternativeLayoutRule", "AlternativeLayoutRuleTransitional", - "DeriveAnyClass", - "PatternSynonyms", - "PartialTypeSignatures", - "NamedWildCards", "StaticPointers"] expectedCabalOnlyExtensions :: [String] From git at git.haskell.org Sat Jan 3 22:18:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Jan 2015 22:18:27 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Cabal submodule to latest 1.22 snapshot (a1e2a2c) Message-ID: <20150103221827.157B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a1e2a2c875640873cb19b732317543fb8c32a731/ghc >--------------------------------------------------------------- commit a1e2a2c875640873cb19b732317543fb8c32a731 Author: Herbert Valerio Riedel Date: Sat Jan 3 23:17:14 2015 +0100 Update Cabal submodule to latest 1.22 snapshot (cherry picked from commit d84742b0df27daa2b48464ca9e71f0101e9266cc) >--------------------------------------------------------------- a1e2a2c875640873cb19b732317543fb8c32a731 libraries/Cabal | 2 +- testsuite/tests/driver/T4437.hs | 4 ---- 2 files changed, 1 insertion(+), 5 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index d920a43..3a7f901 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit d920a43faba148ef63dff4d4a748ac5343380465 +Subproject commit 3a7f9015828745932a65d95fa985c98073fc7d95 diff --git a/testsuite/tests/driver/T4437.hs b/testsuite/tests/driver/T4437.hs index 4120ae9..dde6da7 100644 --- a/testsuite/tests/driver/T4437.hs +++ b/testsuite/tests/driver/T4437.hs @@ -33,10 +33,6 @@ expectedGhcOnlyExtensions :: [String] expectedGhcOnlyExtensions = ["RelaxedLayout", "AlternativeLayoutRule", "AlternativeLayoutRuleTransitional", - "DeriveAnyClass", - "PatternSynonyms", - "PartialTypeSignatures", - "NamedWildCards", "StaticPointers"] expectedCabalOnlyExtensions :: [String] From git at git.haskell.org Mon Jan 5 08:42:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 08:42:25 +0000 (UTC) Subject: [commit: ghc] branch 'wip/redundant-constraints' created Message-ID: <20150105084225.5614D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/redundant-constraints Referencing: 3a2ffab45e552375ca46ed819f157423c73fac4b From git at git.haskell.org Mon Jan 5 08:42:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 08:42:27 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Modify a couple of error messages slightly (3c1eb86) Message-ID: <20150105084227.F2C4A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/3c1eb8616f15f2c025db7e8f5df28966bad0abb8/ghc >--------------------------------------------------------------- commit 3c1eb8616f15f2c025db7e8f5df28966bad0abb8 Author: Simon Peyton Jones Date: Sat Jan 3 23:27:21 2015 +0000 Modify a couple of error messages slightly In particular In the type signature for: f :: Int -> Int I added the colon Also reword the "maybe you haven't applied a function to enough arguments?" suggestion to make grammatical sense. These tiny changes affect a lot of error messages. >--------------------------------------------------------------- 3c1eb8616f15f2c025db7e8f5df28966bad0abb8 compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 68 +++++++++++++--------- .../tests/annotations/should_fail/annfail08.stderr | 4 +- testsuite/tests/arrows/should_fail/T5380.stderr | 8 +-- .../tests/deriving/should_fail/drvfail007.stderr | 2 +- testsuite/tests/driver/T2182.stderr | 8 +-- testsuite/tests/gadt/T3169.stderr | 4 +- testsuite/tests/gadt/T3651.stderr | 6 +- testsuite/tests/gadt/T7293.stderr | 3 +- testsuite/tests/gadt/T7294.stderr | 3 +- testsuite/tests/gadt/T7558.stderr | 4 +- testsuite/tests/gadt/gadt-escape1.stderr | 3 +- testsuite/tests/gadt/gadt13.stderr | 3 +- testsuite/tests/gadt/gadt21.stderr | 2 +- testsuite/tests/gadt/gadt7.stderr | 3 +- testsuite/tests/gadt/rw.stderr | 4 +- .../tests/ghci.debugger/scripts/break003.stderr | 2 +- testsuite/tests/ghci/scripts/Defer02.stderr | 15 +++-- testsuite/tests/ghci/scripts/T2182ghci.stderr | 10 ++-- .../should_compile/PushedInAsGivens.stderr | 2 +- .../indexed-types/should_compile/Simple14.stderr | 4 +- .../indexed-types/should_compile/T3208b.stderr | 8 +-- .../indexed-types/should_fail/GADTwrong1.stderr | 5 +- .../indexed-types/should_fail/Overlap6.stderr | 2 +- .../indexed-types/should_fail/SimpleFail5a.stderr | 2 +- .../tests/indexed-types/should_fail/T2664.stderr | 6 +- .../tests/indexed-types/should_fail/T3330a.stderr | 6 +- .../tests/indexed-types/should_fail/T3440.stderr | 6 +- .../tests/indexed-types/should_fail/T4093a.stderr | 2 +- .../tests/indexed-types/should_fail/T4093b.stderr | 16 ++--- .../tests/indexed-types/should_fail/T4174.stderr | 8 +-- .../tests/indexed-types/should_fail/T4272.stderr | 2 +- .../tests/indexed-types/should_fail/T7194.stderr | 2 +- .../tests/indexed-types/should_fail/T7786.stderr | 3 +- .../tests/indexed-types/should_fail/T9662.stderr | 36 ++++++------ testsuite/tests/parser/should_fail/T7848.stderr | 2 +- .../should_fail/AnnotatedConstraint.stderr | 2 +- .../should_fail/NamedWildcardsNotEnabled.stderr | 4 +- testsuite/tests/polykinds/T7230.stderr | 10 ++-- testsuite/tests/polykinds/T7438.stderr | 2 +- testsuite/tests/polykinds/T8566.stderr | 2 +- testsuite/tests/rebindable/rebindable6.stderr | 6 +- .../tests/typecheck/should_compile/FD1.stderr | 2 +- .../tests/typecheck/should_compile/FD2.stderr | 8 +-- .../tests/typecheck/should_compile/FD3.stderr | 2 +- .../tests/typecheck/should_compile/T7220a.stderr | 4 +- .../tests/typecheck/should_compile/T9834.stderr | 20 +++---- .../tests/typecheck/should_compile/tc141.stderr | 2 +- .../typecheck/should_fail/FDsFromGivens.stderr | 2 +- .../should_fail/FailDueToGivenOverlapping.stderr | 2 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 3 +- .../tests/typecheck/should_fail/IPFail.stderr | 2 +- testsuite/tests/typecheck/should_fail/T1899.stderr | 2 +- testsuite/tests/typecheck/should_fail/T2714.stderr | 4 +- .../tests/typecheck/should_fail/T2846b.stderr | 2 +- testsuite/tests/typecheck/should_fail/T3592.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5236.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 10 ++-- testsuite/tests/typecheck/should_fail/T7453.stderr | 6 +- .../tests/typecheck/should_fail/T7748a.stderr | 2 +- .../tests/typecheck/should_fail/T8392a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8450.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9109.stderr | 3 +- .../should_fail/TcStaticPointersFail02.stderr | 4 +- testsuite/tests/typecheck/should_fail/mc22.stderr | 0 .../tests/typecheck/should_fail/tcfail034.stderr | 4 +- .../tests/typecheck/should_fail/tcfail065.stderr | 2 +- .../tests/typecheck/should_fail/tcfail067.stderr | 22 +++---- .../tests/typecheck/should_fail/tcfail068.stderr | 34 +++++------ .../tests/typecheck/should_fail/tcfail072.stderr | 4 +- .../tests/typecheck/should_fail/tcfail097.stderr | 2 +- .../tests/typecheck/should_fail/tcfail099.stderr | 3 +- .../tests/typecheck/should_fail/tcfail102.stderr | 4 +- .../tests/typecheck/should_fail/tcfail103.stderr | 4 +- .../tests/typecheck/should_fail/tcfail125.stderr | 2 +- .../tests/typecheck/should_fail/tcfail131.stderr | 2 +- .../tests/typecheck/should_fail/tcfail142.stderr | 2 +- .../tests/typecheck/should_fail/tcfail153.stderr | 2 +- .../tests/typecheck/should_fail/tcfail167.stderr | 3 +- .../tests/typecheck/should_fail/tcfail171.stderr | 2 +- .../tests/typecheck/should_fail/tcfail174.stderr | 2 +- .../tests/typecheck/should_fail/tcfail175.stderr | 2 +- .../tests/typecheck/should_fail/tcfail179.stderr | 4 +- .../tests/typecheck/should_fail/tcfail201.stderr | 2 +- .../tests/typecheck/should_fail/tcfail206.stderr | 4 +- .../tests/typecheck/should_fail/tcfail208.stderr | 4 +- 86 files changed, 245 insertions(+), 247 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3c1eb8616f15f2c025db7e8f5df28966bad0abb8 From git at git.haskell.org Mon Jan 5 08:42:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 08:42:30 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Replace fixVarSet with transCloVarSet (6912660) Message-ID: <20150105084230.8AF703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/6912660d9122ecee83b118d0aa052ec25b6fb1e9/ghc >--------------------------------------------------------------- commit 6912660d9122ecee83b118d0aa052ec25b6fb1e9 Author: Simon Peyton Jones Date: Sat Jan 3 23:36:09 2015 +0000 Replace fixVarSet with transCloVarSet I think the new implementation is a bit more efficient, because it uses a work-list, rather than iterating over the entire set every time >--------------------------------------------------------------- 6912660d9122ecee83b118d0aa052ec25b6fb1e9 compiler/basicTypes/VarSet.hs | 29 ++++++++++++++++++++++------- compiler/typecheck/TcSimplify.hs | 31 +++++++++++++++++-------------- 2 files changed, 39 insertions(+), 21 deletions(-) diff --git a/compiler/basicTypes/VarSet.hs b/compiler/basicTypes/VarSet.hs index c134124..6c920ba 100644 --- a/compiler/basicTypes/VarSet.hs +++ b/compiler/basicTypes/VarSet.hs @@ -16,7 +16,8 @@ module VarSet ( unionVarSet, unionVarSets, mapUnionVarSet, intersectVarSet, intersectsVarSet, disjointVarSet, isEmptyVarSet, delVarSet, delVarSetList, delVarSetByKey, - minusVarSet, foldVarSet, filterVarSet, fixVarSet, + minusVarSet, foldVarSet, filterVarSet, + transCloVarSet, lookupVarSet, mapVarSet, sizeVarSet, seqVarSet, elemVarSetByKey, partitionVarSet ) where @@ -69,7 +70,6 @@ extendVarSet_C :: (Var->Var->Var) -> VarSet -> Var -> VarSet delVarSetByKey :: VarSet -> Unique -> VarSet elemVarSetByKey :: Unique -> VarSet -> Bool -fixVarSet :: (VarSet -> VarSet) -> VarSet -> VarSet partitionVarSet :: (Var -> Bool) -> VarSet -> (VarSet, VarSet) emptyVarSet = emptyUniqSet @@ -110,11 +110,26 @@ intersectsVarSet s1 s2 = not (s1 `disjointVarSet` s2) disjointVarSet s1 s2 = isEmptyVarSet (s1 `intersectVarSet` s2) subVarSet s1 s2 = isEmptyVarSet (s1 `minusVarSet` s2) --- Iterate f to a fixpoint -fixVarSet f s | new_s `subVarSet` s = s - | otherwise = fixVarSet f new_s - where - new_s = f s +transCloVarSet :: (VarSet -> VarSet) + -- Map some variables in the set to + -- *extra* variables that should be in it + -> VarSet -> VarSet +-- (transCloVarSet f s) repeatedly applies f to the set s, adding any +-- new variables to s that it finds thereby, until it reaches a fixed +-- point. The actual algorithm is a bit more efficient. +transCloVarSet fn seeds + = go seeds seeds + where + go :: VarSet -- Accumulating result + -> VarSet -- Work-list; un-processed subset of accumulating result + -> VarSet + -- Specification: go acc vs = acc `union` transClo fn vs + + go acc candidates + | isEmptyVarSet new_vs = acc + | otherwise = go (acc `unionVarSet` new_vs) new_vs + where + new_vs = fn candidates `minusVarSet` acc seqVarSet :: VarSet -> () seqVarSet s = sizeVarSet s `seq` () diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 01da61f..0c9b093 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -468,17 +468,18 @@ quantifyPred qtvs pred growThetaTyVars :: ThetaType -> TyVarSet -> TyVarSet -- See Note [Growing the tau-tvs using constraints] growThetaTyVars theta tvs - | null theta = tvs - | isEmptyVarSet seed_tvs = tvs - | otherwise = fixVarSet mk_next seed_tvs + | null theta = tvs + | otherwise = transCloVarSet mk_next seed_tvs where seed_tvs = tvs `unionVarSet` tyVarsOfTypes ips (ips, non_ips) = partition isIPPred theta -- See note [Inheriting implicit parameters] - mk_next tvs = foldr grow_one tvs non_ips - grow_one pred tvs - | pred_tvs `intersectsVarSet` tvs = tvs `unionVarSet` pred_tvs - | otherwise = tvs + + mk_next :: VarSet -> VarSet -- Maps current set to newly-grown ones + mk_next so_far = foldr (grow_one so_far) emptyVarSet non_ips + grow_one so_far pred tvs + | pred_tvs `intersectsVarSet` so_far = tvs `unionVarSet` pred_tvs + | otherwise = tvs where pred_tvs = tyVarsOfType pred @@ -990,14 +991,16 @@ approximateWC wc = filterBag is_floatable simples `unionBags` do_bag (float_implic new_trapping_tvs) implics where - new_trapping_tvs = fixVarSet grow trapping_tvs is_floatable ct = tyVarsOfCt ct `disjointVarSet` new_trapping_tvs - - grow tvs = foldrBag grow_one tvs simples - grow_one ct tvs | ct_tvs `intersectsVarSet` tvs = tvs `unionVarSet` ct_tvs - | otherwise = tvs - where - ct_tvs = tyVarsOfCt ct + new_trapping_tvs = transCloVarSet grow trapping_tvs + + grow :: VarSet -> VarSet -- Maps current trapped tyvars to newly-trapped ones + grow so_far = foldrBag (grow_one so_far) emptyVarSet simples + grow_one so_far ct tvs + | ct_tvs `intersectsVarSet` so_far = tvs `unionVarSet` ct_tvs + | otherwise = tvs + where + ct_tvs = tyVarsOfCt ct float_implic :: TcTyVarSet -> Implication -> Cts float_implic trapping_tvs imp From git at git.haskell.org Mon Jan 5 08:42:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 08:42:33 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Work in progress on redundant constraints (3a2ffab) Message-ID: <20150105084233.549B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/3a2ffab45e552375ca46ed819f157423c73fac4b/ghc >--------------------------------------------------------------- commit 3a2ffab45e552375ca46ed819f157423c73fac4b Author: Simon Peyton Jones Date: Mon Jan 5 08:43:14 2015 +0000 Work in progress on redundant constraints >--------------------------------------------------------------- 3a2ffab45e552375ca46ed819f157423c73fac4b compiler/cmm/CmmExpr.hs | 8 +- compiler/coreSyn/TrieMap.hs | 4 +- compiler/deSugar/DsArrows.hs | 4 +- compiler/deSugar/DsBinds.hs | 27 +- compiler/deSugar/DsExpr.hs | 2 +- compiler/hsSyn/HsBinds.hs | 2 +- compiler/hsSyn/HsDecls.hs | 8 +- compiler/hsSyn/HsExpr.hs | 8 +- compiler/main/DynFlags.hs | 7 +- compiler/typecheck/Inst.hs | 18 +- compiler/typecheck/TcBinds.hs | 99 ++- compiler/typecheck/TcCanonical.hs | 30 +- compiler/typecheck/TcClassDcl.hs | 133 ++-- compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcErrors.hs | 236 +++++--- compiler/typecheck/TcEvidence.hs | 40 +- compiler/typecheck/TcFlatten.hs | 6 +- compiler/typecheck/TcHsSyn.hs | 31 +- compiler/typecheck/TcInstDcls.hs | 672 ++++++++++++--------- compiler/typecheck/TcInteract.hs | 60 +- compiler/typecheck/TcMType.hs | 35 +- compiler/typecheck/TcMatches.hs | 2 +- compiler/typecheck/TcPat.hs | 18 +- compiler/typecheck/TcPatSyn.hs | 9 +- compiler/typecheck/TcRnDriver.hs | 5 +- compiler/typecheck/TcRnMonad.hs | 33 +- compiler/typecheck/TcRnTypes.hs | 79 ++- compiler/typecheck/TcRules.hs | 36 +- compiler/typecheck/TcSMonad.hs | 44 +- compiler/typecheck/TcSimplify.hs | 292 +++++++-- compiler/typecheck/TcTyClsDecls.hs | 6 +- compiler/typecheck/TcType.hs | 18 +- compiler/typecheck/TcUnify.hs | 50 +- compiler/typecheck/TcValidity.hs | 2 +- compiler/types/TypeRep.hs | 2 +- testsuite/tests/arrows/should_compile/arrowpat.hs | 3 +- testsuite/tests/codeGen/should_compile/T3286.hs | 1 + testsuite/tests/deriving/should_compile/T2856.hs | 1 + testsuite/tests/deriving/should_compile/T4966.hs | 2 + .../tests/deriving/should_compile/T4966.stderr | 4 +- .../tests/deriving/should_compile/deriving-1935.hs | 2 + .../deriving/should_compile/deriving-1935.stderr | 6 +- testsuite/tests/deriving/should_compile/drv001.hs | 2 + testsuite/tests/deriving/should_compile/drv002.hs | 2 + testsuite/tests/deriving/should_compile/drv003.hs | 2 + .../tests/deriving/should_compile/drv003.stderr | 4 +- testsuite/tests/deriving/should_run/T9576.stderr | 2 +- testsuite/tests/gadt/Gadt17_help.hs | 2 +- testsuite/tests/ghci/scripts/T5045.hs | 1 + testsuite/tests/ghci/scripts/T8357.hs | 1 + testsuite/tests/ghci/scripts/ghci044.script | 1 + testsuite/tests/ghci/scripts/ghci044.stderr | 6 +- testsuite/tests/ghci/scripts/ghci047.script | 1 + testsuite/tests/ghci/scripts/ghci047.stderr | 4 +- testsuite/tests/ghci/scripts/ghci050.stderr | 0 testsuite/tests/haddock/haddock_examples/Test.hs | 1 + .../haddock/haddock_examples/haddock.Test.stderr | 8 +- .../should_compile_flag_haddock/haddockA023.hs | 2 + .../should_compile_flag_haddock/haddockA026.hs | 2 + .../should_compile_flag_haddock/haddockA027.hs | 2 + .../should_compile_noflag_haddock/haddockC026.hs | 2 + .../should_compile_noflag_haddock/haddockC027.hs | 2 + .../tests/indexed-types/should_compile/Class2.hs | 1 + .../tests/indexed-types/should_compile/Gentle.hs | 1 + .../should_compile/InstContextNorm.hs | 1 + .../indexed-types/should_compile/InstEqContext.hs | 1 + .../indexed-types/should_compile/InstEqContext2.hs | 1 + .../indexed-types/should_compile/InstEqContext3.hs | 1 + .../indexed-types/should_compile/NonLinearLHS.hs | 1 + .../tests/indexed-types/should_compile/Rules1.hs | 1 + .../tests/indexed-types/should_compile/Simple24.hs | 1 + .../tests/indexed-types/should_compile/T2448.hs | 1 + .../tests/indexed-types/should_compile/T3023.hs | 3 +- .../indexed-types/should_compile/T3023.stderr | 5 +- .../tests/indexed-types/should_compile/T3484.hs | 3 +- .../tests/indexed-types/should_compile/T4200.hs | 1 + .../tests/indexed-types/should_compile/T4497.hs | 1 + .../tests/indexed-types/should_compile/T4981-V1.hs | 2 + .../tests/indexed-types/should_compile/T4981-V2.hs | 2 + .../tests/indexed-types/should_compile/T4981-V3.hs | 2 + .../tests/indexed-types/should_compile/T5002.hs | 1 + .../tests/indexed-types/should_compile/T9090.hs | 2 + .../tests/indexed-types/should_compile/T9316.hs | 1 + .../tests/indexed-types/should_compile/T9747.hs | 2 + testsuite/tests/indexed-types/should_fail/T2239.hs | 1 + .../tests/indexed-types/should_fail/T3330c.stderr | 4 + testsuite/tests/indexed-types/should_fail/T7862.hs | 1 + .../tests/indexed-types/should_fail/T7862.stderr | 2 +- .../tests/indexed-types/should_fail/T8155.stderr | 0 testsuite/tests/module/mod129.hs | 2 + testsuite/tests/module/mod71.stderr | 9 + testsuite/tests/parser/should_compile/mc15.hs | 2 +- testsuite/tests/parser/should_compile/read002.hs | 2 + testsuite/tests/partial-sigs/should_compile/all.T | 2 +- testsuite/tests/patsyn/should_compile/T8584-2.hs | 2 + testsuite/tests/patsyn/should_compile/T8968-1.hs | 1 + testsuite/tests/patsyn/should_compile/all.T | 4 +- testsuite/tests/patsyn/should_compile/ex-view.hs | 4 +- testsuite/tests/perf/compiler/T3064.hs | 2 + testsuite/tests/perf/compiler/T5030.hs | 6 +- testsuite/tests/polykinds/PolyKinds08.hs | 1 + testsuite/tests/polykinds/T6015a.hs | 1 + testsuite/tests/polykinds/T6020a.hs | 1 + testsuite/tests/polykinds/T6068.hs | 1 + testsuite/tests/polykinds/T7090.hs | 1 + testsuite/tests/polykinds/T7332.hs | 20 +- testsuite/tests/polykinds/T8359.hs | 2 + testsuite/tests/polykinds/T9569.hs | 1 + testsuite/tests/polykinds/T9750.hs | 1 + testsuite/tests/rebindable/T5821.hs | 3 +- testsuite/tests/rebindable/rebindable9.hs | 4 +- testsuite/tests/rename/should_fail/rnfail020.hs | 1 + testsuite/tests/simplCore/should_compile/T3831.hs | 1 + testsuite/tests/simplCore/should_compile/T4398.hs | 1 + .../tests/simplCore/should_compile/T4398.stderr | 2 +- testsuite/tests/simplCore/should_compile/T5329.hs | 1 + testsuite/tests/simplCore/should_compile/T5342.hs | 1 + testsuite/tests/simplCore/should_compile/T5359b.hs | 1 + .../tests/simplCore/should_compile/T5359b.stderr | 2 +- testsuite/tests/simplCore/should_compile/T8848.hs | 3 +- testsuite/tests/simplCore/should_compile/T8848a.hs | 1 + .../tests/simplCore/should_compile/simpl002.hs | 2 + .../tests/simplCore/should_compile/simpl007.hs | 1 + .../tests/simplCore/should_compile/simpl014.hs | 1 + .../tests/simplCore/should_compile/simpl016.hs | 2 + .../tests/simplCore/should_compile/simpl016.stderr | 2 +- .../tests/simplCore/should_compile/spec003.hs | 2 + testsuite/tests/th/T3100.hs | 1 + testsuite/tests/th/T7021a.hs | 1 + testsuite/tests/th/T8807.hs | 1 + testsuite/tests/th/TH_tf3.hs | 1 + .../typecheck/should_compile/GivenOverlapping.hs | 1 + .../typecheck/should_compile/LoopOfTheDay1.hs | 1 + .../typecheck/should_compile/LoopOfTheDay2.hs | 1 + .../typecheck/should_compile/LoopOfTheDay3.hs | 1 + testsuite/tests/typecheck/should_compile/T1470.hs | 1 + testsuite/tests/typecheck/should_compile/T2683.hs | 1 + testsuite/tests/typecheck/should_compile/T3018.hs | 1 + testsuite/tests/typecheck/should_compile/T3108.hs | 1 + testsuite/tests/typecheck/should_compile/T3692.hs | 1 + testsuite/tests/typecheck/should_compile/T3743.hs | 1 + testsuite/tests/typecheck/should_compile/T4361.hs | 1 + testsuite/tests/typecheck/should_compile/T4401.hs | 1 + testsuite/tests/typecheck/should_compile/T4524.hs | 1 + testsuite/tests/typecheck/should_compile/T4952.hs | 1 + testsuite/tests/typecheck/should_compile/T4969.hs | 2 +- testsuite/tests/typecheck/should_compile/T5514.hs | 1 + testsuite/tests/typecheck/should_compile/T5581.hs | 2 + testsuite/tests/typecheck/should_compile/T5676.hs | 1 + testsuite/tests/typecheck/should_compile/T6055.hs | 1 + testsuite/tests/typecheck/should_compile/T6134.hs | 1 + testsuite/tests/typecheck/should_compile/T7171a.hs | 1 + testsuite/tests/typecheck/should_compile/T7196.hs | 1 + testsuite/tests/typecheck/should_compile/T7220.hs | 1 + testsuite/tests/typecheck/should_compile/T7541.hs | 2 +- testsuite/tests/typecheck/should_compile/T7875.hs | 1 + testsuite/tests/typecheck/should_compile/T7903.hs | 1 + .../typecheck/should_compile/T7903.stderr-ghc | 4 +- .../tests/typecheck/should_compile/Tc170_Aux.hs | 1 + testsuite/tests/typecheck/should_compile/Tc173a.hs | 2 + testsuite/tests/typecheck/should_compile/tc045.hs | 1 + testsuite/tests/typecheck/should_compile/tc051.hs | 2 + .../tests/typecheck/should_compile/tc056.stderr | 10 +- testsuite/tests/typecheck/should_compile/tc058.hs | 2 + testsuite/tests/typecheck/should_compile/tc065.hs | 4 +- testsuite/tests/typecheck/should_compile/tc078.hs | 2 + .../typecheck/should_compile/tc078.stderr-ghc | 4 +- testsuite/tests/typecheck/should_compile/tc079.hs | 2 + testsuite/tests/typecheck/should_compile/tc088.hs | 2 + testsuite/tests/typecheck/should_compile/tc091.hs | 2 + testsuite/tests/typecheck/should_compile/tc092.hs | 1 + testsuite/tests/typecheck/should_compile/tc109.hs | 1 + testsuite/tests/typecheck/should_compile/tc113.hs | 2 + testsuite/tests/typecheck/should_compile/tc115.hs | 1 + .../typecheck/should_compile/tc115.stderr-ghc | 2 +- testsuite/tests/typecheck/should_compile/tc116.hs | 1 + .../typecheck/should_compile/tc116.stderr-ghc | 2 +- testsuite/tests/typecheck/should_compile/tc125.hs | 1 + .../typecheck/should_compile/tc125.stderr-ghc | 10 +- testsuite/tests/typecheck/should_compile/tc126.hs | 1 + .../typecheck/should_compile/tc126.stderr-ghc | 4 +- testsuite/tests/typecheck/should_compile/tc145.hs | 1 + testsuite/tests/typecheck/should_compile/tc152.hs | 1 + testsuite/tests/typecheck/should_compile/tc176.hs | 1 + testsuite/tests/typecheck/should_compile/tc178.hs | 1 + testsuite/tests/typecheck/should_compile/tc180.hs | 1 + testsuite/tests/typecheck/should_compile/tc181.hs | 1 + testsuite/tests/typecheck/should_compile/tc183.hs | 1 + testsuite/tests/typecheck/should_compile/tc187.hs | 1 + testsuite/tests/typecheck/should_compile/tc192.hs | 1 + testsuite/tests/typecheck/should_compile/tc203.hs | 1 + testsuite/tests/typecheck/should_compile/tc204.hs | 3 +- testsuite/tests/typecheck/should_compile/tc206.hs | 1 + testsuite/tests/typecheck/should_compile/tc208.hs | 1 + testsuite/tests/typecheck/should_compile/tc229.hs | 1 + testsuite/tests/typecheck/should_compile/tc230.hs | 1 + testsuite/tests/typecheck/should_compile/tc235.hs | 1 + testsuite/tests/typecheck/should_compile/tc237.hs | 1 + testsuite/tests/typecheck/should_compile/tc239.hs | 1 + testsuite/tests/typecheck/should_compile/twins.hs | 1 + testsuite/tests/typecheck/should_fail/T6161.stderr | 4 +- testsuite/tests/typecheck/should_fail/mc25.stderr | 0 .../tests/typecheck/should_fail/tcfail017.stderr | 4 +- .../tests/typecheck/should_fail/tcfail020.stderr | 4 +- testsuite/tests/typecheck/should_fail/tcfail071.hs | 2 + testsuite/tests/typecheck/should_fail/tcfail138.hs | 1 + .../tests/typecheck/should_fail/tcfail143.stderr | 4 +- 207 files changed, 1477 insertions(+), 893 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3a2ffab45e552375ca46ed819f157423c73fac4b From git at git.haskell.org Mon Jan 5 15:01:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:13 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Modify a couple of error messages slightly (63cf7a4) Message-ID: <20150105150113.C1B8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/63cf7a4b9b237597dbd3740eecd40c1547abbf43/ghc >--------------------------------------------------------------- commit 63cf7a4b9b237597dbd3740eecd40c1547abbf43 Author: Simon Peyton Jones Date: Sat Jan 3 23:27:21 2015 +0000 Modify a couple of error messages slightly In particular In the type signature for: f :: Int -> Int I added the colon Also reword the "maybe you haven't applied a function to enough arguments?" suggestion to make grammatical sense. These tiny changes affect a lot of error messages. >--------------------------------------------------------------- 63cf7a4b9b237597dbd3740eecd40c1547abbf43 compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 68 +++++++++++++--------- .../tests/annotations/should_fail/annfail08.stderr | 4 +- testsuite/tests/arrows/should_fail/T5380.stderr | 8 +-- .../tests/deriving/should_fail/drvfail007.stderr | 2 +- testsuite/tests/driver/T2182.stderr | 8 +-- testsuite/tests/gadt/T3169.stderr | 4 +- testsuite/tests/gadt/T3651.stderr | 6 +- testsuite/tests/gadt/T7293.stderr | 3 +- testsuite/tests/gadt/T7294.stderr | 3 +- testsuite/tests/gadt/T7558.stderr | 4 +- testsuite/tests/gadt/gadt-escape1.stderr | 3 +- testsuite/tests/gadt/gadt13.stderr | 3 +- testsuite/tests/gadt/gadt21.stderr | 2 +- testsuite/tests/gadt/gadt7.stderr | 3 +- testsuite/tests/gadt/rw.stderr | 4 +- .../tests/ghci.debugger/scripts/break003.stderr | 2 +- testsuite/tests/ghci/scripts/Defer02.stderr | 15 +++-- testsuite/tests/ghci/scripts/T2182ghci.stderr | 10 ++-- .../should_compile/PushedInAsGivens.stderr | 2 +- .../indexed-types/should_compile/Simple14.stderr | 4 +- .../indexed-types/should_compile/T3208b.stderr | 8 +-- .../indexed-types/should_fail/GADTwrong1.stderr | 5 +- .../indexed-types/should_fail/Overlap6.stderr | 2 +- .../indexed-types/should_fail/SimpleFail5a.stderr | 2 +- .../tests/indexed-types/should_fail/T2664.stderr | 6 +- .../tests/indexed-types/should_fail/T3330a.stderr | 6 +- .../tests/indexed-types/should_fail/T3440.stderr | 6 +- .../tests/indexed-types/should_fail/T4093a.stderr | 2 +- .../tests/indexed-types/should_fail/T4093b.stderr | 16 ++--- .../tests/indexed-types/should_fail/T4174.stderr | 8 +-- .../tests/indexed-types/should_fail/T4272.stderr | 2 +- .../tests/indexed-types/should_fail/T7194.stderr | 2 +- .../tests/indexed-types/should_fail/T7786.stderr | 3 +- .../tests/indexed-types/should_fail/T9662.stderr | 36 ++++++------ testsuite/tests/parser/should_fail/T7848.stderr | 2 +- .../should_fail/AnnotatedConstraint.stderr | 2 +- .../should_fail/NamedWildcardsNotEnabled.stderr | 4 +- testsuite/tests/polykinds/T7230.stderr | 10 ++-- testsuite/tests/polykinds/T7438.stderr | 2 +- testsuite/tests/polykinds/T8566.stderr | 2 +- testsuite/tests/rebindable/rebindable6.stderr | 6 +- .../tests/typecheck/should_compile/FD1.stderr | 2 +- .../tests/typecheck/should_compile/FD2.stderr | 8 +-- .../tests/typecheck/should_compile/FD3.stderr | 2 +- .../tests/typecheck/should_compile/T7220a.stderr | 4 +- .../tests/typecheck/should_compile/T9834.stderr | 20 +++---- .../tests/typecheck/should_compile/tc141.stderr | 2 +- .../typecheck/should_fail/FDsFromGivens.stderr | 2 +- .../should_fail/FailDueToGivenOverlapping.stderr | 2 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 3 +- .../tests/typecheck/should_fail/IPFail.stderr | 2 +- testsuite/tests/typecheck/should_fail/T1899.stderr | 2 +- testsuite/tests/typecheck/should_fail/T2714.stderr | 4 +- .../tests/typecheck/should_fail/T2846b.stderr | 2 +- testsuite/tests/typecheck/should_fail/T3592.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5236.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 10 ++-- testsuite/tests/typecheck/should_fail/T7453.stderr | 6 +- .../tests/typecheck/should_fail/T7748a.stderr | 2 +- .../tests/typecheck/should_fail/T8392a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8450.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9109.stderr | 3 +- .../should_fail/TcStaticPointersFail02.stderr | 4 +- testsuite/tests/typecheck/should_fail/mc22.stderr | 0 .../tests/typecheck/should_fail/tcfail034.stderr | 4 +- .../tests/typecheck/should_fail/tcfail065.stderr | 2 +- .../tests/typecheck/should_fail/tcfail067.stderr | 22 +++---- .../tests/typecheck/should_fail/tcfail068.stderr | 34 +++++------ .../tests/typecheck/should_fail/tcfail072.stderr | 4 +- .../tests/typecheck/should_fail/tcfail097.stderr | 2 +- .../tests/typecheck/should_fail/tcfail099.stderr | 3 +- .../tests/typecheck/should_fail/tcfail102.stderr | 4 +- .../tests/typecheck/should_fail/tcfail103.stderr | 4 +- .../tests/typecheck/should_fail/tcfail125.stderr | 2 +- .../tests/typecheck/should_fail/tcfail131.stderr | 2 +- .../tests/typecheck/should_fail/tcfail142.stderr | 2 +- .../tests/typecheck/should_fail/tcfail153.stderr | 2 +- .../tests/typecheck/should_fail/tcfail167.stderr | 3 +- .../tests/typecheck/should_fail/tcfail171.stderr | 2 +- .../tests/typecheck/should_fail/tcfail174.stderr | 2 +- .../tests/typecheck/should_fail/tcfail175.stderr | 2 +- .../tests/typecheck/should_fail/tcfail179.stderr | 4 +- .../tests/typecheck/should_fail/tcfail201.stderr | 2 +- .../tests/typecheck/should_fail/tcfail206.stderr | 4 +- .../tests/typecheck/should_fail/tcfail208.stderr | 4 +- 86 files changed, 245 insertions(+), 247 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 63cf7a4b9b237597dbd3740eecd40c1547abbf43 From git at git.haskell.org Mon Jan 5 15:01:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:16 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Replace fixVarSet with transCloVarSet (eaf2638) Message-ID: <20150105150116.616893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/eaf2638b24c1fc1d40a8d7bb782349e5ed989852/ghc >--------------------------------------------------------------- commit eaf2638b24c1fc1d40a8d7bb782349e5ed989852 Author: Simon Peyton Jones Date: Sat Jan 3 23:36:09 2015 +0000 Replace fixVarSet with transCloVarSet I think the new implementation is a bit more efficient, because it uses a work-list, rather than iterating over the entire set every time >--------------------------------------------------------------- eaf2638b24c1fc1d40a8d7bb782349e5ed989852 compiler/basicTypes/VarSet.hs | 29 ++++++++++++++++++++++------- compiler/typecheck/TcSimplify.hs | 31 +++++++++++++++++-------------- 2 files changed, 39 insertions(+), 21 deletions(-) diff --git a/compiler/basicTypes/VarSet.hs b/compiler/basicTypes/VarSet.hs index c134124..6c920ba 100644 --- a/compiler/basicTypes/VarSet.hs +++ b/compiler/basicTypes/VarSet.hs @@ -16,7 +16,8 @@ module VarSet ( unionVarSet, unionVarSets, mapUnionVarSet, intersectVarSet, intersectsVarSet, disjointVarSet, isEmptyVarSet, delVarSet, delVarSetList, delVarSetByKey, - minusVarSet, foldVarSet, filterVarSet, fixVarSet, + minusVarSet, foldVarSet, filterVarSet, + transCloVarSet, lookupVarSet, mapVarSet, sizeVarSet, seqVarSet, elemVarSetByKey, partitionVarSet ) where @@ -69,7 +70,6 @@ extendVarSet_C :: (Var->Var->Var) -> VarSet -> Var -> VarSet delVarSetByKey :: VarSet -> Unique -> VarSet elemVarSetByKey :: Unique -> VarSet -> Bool -fixVarSet :: (VarSet -> VarSet) -> VarSet -> VarSet partitionVarSet :: (Var -> Bool) -> VarSet -> (VarSet, VarSet) emptyVarSet = emptyUniqSet @@ -110,11 +110,26 @@ intersectsVarSet s1 s2 = not (s1 `disjointVarSet` s2) disjointVarSet s1 s2 = isEmptyVarSet (s1 `intersectVarSet` s2) subVarSet s1 s2 = isEmptyVarSet (s1 `minusVarSet` s2) --- Iterate f to a fixpoint -fixVarSet f s | new_s `subVarSet` s = s - | otherwise = fixVarSet f new_s - where - new_s = f s +transCloVarSet :: (VarSet -> VarSet) + -- Map some variables in the set to + -- *extra* variables that should be in it + -> VarSet -> VarSet +-- (transCloVarSet f s) repeatedly applies f to the set s, adding any +-- new variables to s that it finds thereby, until it reaches a fixed +-- point. The actual algorithm is a bit more efficient. +transCloVarSet fn seeds + = go seeds seeds + where + go :: VarSet -- Accumulating result + -> VarSet -- Work-list; un-processed subset of accumulating result + -> VarSet + -- Specification: go acc vs = acc `union` transClo fn vs + + go acc candidates + | isEmptyVarSet new_vs = acc + | otherwise = go (acc `unionVarSet` new_vs) new_vs + where + new_vs = fn candidates `minusVarSet` acc seqVarSet :: VarSet -> () seqVarSet s = sizeVarSet s `seq` () diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 01da61f..0c9b093 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -468,17 +468,18 @@ quantifyPred qtvs pred growThetaTyVars :: ThetaType -> TyVarSet -> TyVarSet -- See Note [Growing the tau-tvs using constraints] growThetaTyVars theta tvs - | null theta = tvs - | isEmptyVarSet seed_tvs = tvs - | otherwise = fixVarSet mk_next seed_tvs + | null theta = tvs + | otherwise = transCloVarSet mk_next seed_tvs where seed_tvs = tvs `unionVarSet` tyVarsOfTypes ips (ips, non_ips) = partition isIPPred theta -- See note [Inheriting implicit parameters] - mk_next tvs = foldr grow_one tvs non_ips - grow_one pred tvs - | pred_tvs `intersectsVarSet` tvs = tvs `unionVarSet` pred_tvs - | otherwise = tvs + + mk_next :: VarSet -> VarSet -- Maps current set to newly-grown ones + mk_next so_far = foldr (grow_one so_far) emptyVarSet non_ips + grow_one so_far pred tvs + | pred_tvs `intersectsVarSet` so_far = tvs `unionVarSet` pred_tvs + | otherwise = tvs where pred_tvs = tyVarsOfType pred @@ -990,14 +991,16 @@ approximateWC wc = filterBag is_floatable simples `unionBags` do_bag (float_implic new_trapping_tvs) implics where - new_trapping_tvs = fixVarSet grow trapping_tvs is_floatable ct = tyVarsOfCt ct `disjointVarSet` new_trapping_tvs - - grow tvs = foldrBag grow_one tvs simples - grow_one ct tvs | ct_tvs `intersectsVarSet` tvs = tvs `unionVarSet` ct_tvs - | otherwise = tvs - where - ct_tvs = tyVarsOfCt ct + new_trapping_tvs = transCloVarSet grow trapping_tvs + + grow :: VarSet -> VarSet -- Maps current trapped tyvars to newly-trapped ones + grow so_far = foldrBag (grow_one so_far) emptyVarSet simples + grow_one so_far ct tvs + | ct_tvs `intersectsVarSet` so_far = tvs `unionVarSet` ct_tvs + | otherwise = tvs + where + ct_tvs = tyVarsOfCt ct float_implic :: TcTyVarSet -> Implication -> Cts float_implic trapping_tvs imp From git at git.haskell.org Mon Jan 5 15:01:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:18 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Remove redundant constraints in GHC source code discovered by -fwarn-redundant-constraints (8088ab6) Message-ID: <20150105150118.F30D53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/8088ab68dc514c7b7aad1e173b1e43d84a7818a1/ghc >--------------------------------------------------------------- commit 8088ab68dc514c7b7aad1e173b1e43d84a7818a1 Author: Simon Peyton Jones Date: Mon Jan 5 09:07:47 2015 +0000 Remove redundant constraints in GHC source code discovered by -fwarn-redundant-constraints >--------------------------------------------------------------- 8088ab68dc514c7b7aad1e173b1e43d84a7818a1 compiler/cmm/CmmExpr.hs | 8 ++++---- compiler/coreSyn/TrieMap.hs | 4 ++-- compiler/hsSyn/HsDecls.hs | 8 +++----- compiler/hsSyn/HsExpr.hs | 8 ++++---- 4 files changed, 13 insertions(+), 15 deletions(-) diff --git a/compiler/cmm/CmmExpr.hs b/compiler/cmm/CmmExpr.hs index 4d9bbf8..aa5cef1 100644 --- a/compiler/cmm/CmmExpr.hs +++ b/compiler/cmm/CmmExpr.hs @@ -280,15 +280,15 @@ type RegSet r = Set r type LocalRegSet = RegSet LocalReg type GlobalRegSet = RegSet GlobalReg -emptyRegSet :: Ord r => RegSet r -nullRegSet :: Ord r => RegSet r -> Bool +emptyRegSet :: RegSet r +nullRegSet :: RegSet r -> Bool elemRegSet :: Ord r => r -> RegSet r -> Bool extendRegSet :: Ord r => RegSet r -> r -> RegSet r deleteFromRegSet :: Ord r => RegSet r -> r -> RegSet r mkRegSet :: Ord r => [r] -> RegSet r minusRegSet, plusRegSet, timesRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r -sizeRegSet :: Ord r => RegSet r -> Int -regSetToList :: Ord r => RegSet r -> [r] +sizeRegSet :: RegSet r -> Int +regSetToList :: RegSet r -> [r] emptyRegSet = Set.empty nullRegSet = Set.null diff --git a/compiler/coreSyn/TrieMap.hs b/compiler/coreSyn/TrieMap.hs index efae286..9197386 100644 --- a/compiler/coreSyn/TrieMap.hs +++ b/compiler/coreSyn/TrieMap.hs @@ -154,12 +154,12 @@ mapMb :: TrieMap m => (a->b) -> MaybeMap m a -> MaybeMap m b mapMb f (MM { mm_nothing = mn, mm_just = mj }) = MM { mm_nothing = fmap f mn, mm_just = mapTM f mj } -lkMaybe :: TrieMap m => (forall b. k -> m b -> Maybe b) +lkMaybe :: (forall b. k -> m b -> Maybe b) -> Maybe k -> MaybeMap m a -> Maybe a lkMaybe _ Nothing = mm_nothing lkMaybe lk (Just x) = mm_just >.> lk x -xtMaybe :: TrieMap m => (forall b. k -> XT b -> m b -> m b) +xtMaybe :: (forall b. k -> XT b -> m b -> m b) -> Maybe k -> XT a -> MaybeMap m a -> MaybeMap m a xtMaybe _ Nothing f m = m { mm_nothing = f (mm_nothing m) } xtMaybe tr (Just x) f m = m { mm_just = mm_just m |> tr x f } diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/hsSyn/HsDecls.hs index f81d0a1..4b54a8d 100644 --- a/compiler/hsSyn/HsDecls.hs +++ b/compiler/hsSyn/HsDecls.hs @@ -601,12 +601,10 @@ isDataFamilyDecl _other = False -- Dealing with names -tyFamInstDeclName :: OutputableBndr name - => TyFamInstDecl name -> name +tyFamInstDeclName :: TyFamInstDecl name -> name tyFamInstDeclName = unLoc . tyFamInstDeclLName -tyFamInstDeclLName :: OutputableBndr name - => TyFamInstDecl name -> Located name +tyFamInstDeclLName :: TyFamInstDecl name -> Located name tyFamInstDeclLName (TyFamInstDecl { tfid_eqn = (L _ (TyFamEqn { tfe_tycon = ln })) }) = ln @@ -618,7 +616,7 @@ tyClDeclLName decl = tcdLName decl tcdName :: TyClDecl name -> name tcdName = unLoc . tyClDeclLName -tyClDeclTyVars :: OutputableBndr name => TyClDecl name -> LHsTyVarBndrs name +tyClDeclTyVars :: TyClDecl name -> LHsTyVarBndrs name tyClDeclTyVars (FamDecl { tcdFam = FamilyDecl { fdTyVars = tvs } }) = tvs tyClDeclTyVars d = tcdTyVars d diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs index 384222b..a5a1aaf 100644 --- a/compiler/hsSyn/HsExpr.hs +++ b/compiler/hsSyn/HsExpr.hs @@ -1064,14 +1064,14 @@ pprMatch ctxt (Match pats maybe_ty grhss) Nothing -> empty -pprGRHSs :: (OutputableBndr idL, OutputableBndr idR, Outputable body) +pprGRHSs :: (OutputableBndr idR, Outputable body) => HsMatchContext idL -> GRHSs idR body -> SDoc pprGRHSs ctxt (GRHSs grhss binds) = vcat (map (pprGRHS ctxt . unLoc) grhss) $$ ppUnless (isEmptyLocalBinds binds) (text "where" $$ nest 4 (pprBinds binds)) -pprGRHS :: (OutputableBndr idL, OutputableBndr idR, Outputable body) +pprGRHS :: (OutputableBndr idR, Outputable body) => HsMatchContext idL -> GRHS idR body -> SDoc pprGRHS ctxt (GRHS [] body) = pp_rhs ctxt body @@ -1355,8 +1355,8 @@ In any other context than 'MonadComp', the fields for most of these 'SyntaxExpr's stay bottom. -} -instance (OutputableBndr idL, OutputableBndr idR) - => Outputable (ParStmtBlock idL idR) where +instance (OutputableBndr idL) + => Outputable (ParStmtBlock idL idR) where ppr (ParStmtBlock stmts _ _) = interpp'SP stmts instance (OutputableBndr idL, OutputableBndr idR, Outputable body) From git at git.haskell.org Mon Jan 5 15:01:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:21 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Always generalise a partial type signature (b129f95) Message-ID: <20150105150121.B343D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/b129f951f18e4b9774c9e3446ee3926542e1f482/ghc >--------------------------------------------------------------- commit b129f951f18e4b9774c9e3446ee3926542e1f482 Author: Simon Peyton Jones Date: Mon Jan 5 10:39:46 2015 +0000 Always generalise a partial type signature This fixes an ASSERT failure in TcBinds. The problem was that we were generating NoGen plan for a function with a partial type signature, and that led to confusion and lost invariants. See Note [Partial type signatures and generalisation] in TcBinds >--------------------------------------------------------------- b129f951f18e4b9774c9e3446ee3926542e1f482 compiler/typecheck/TcBinds.hs | 56 ++++++++++++++++++++++++++++++++----------- 1 file changed, 42 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index 842ccfa..b4bb65d 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -769,6 +769,29 @@ completeTheta inferred_theta , typeSigCtxt (idName poly_id) sig ] {- +Note [Partial type signatures and generalisation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When we have a partial type signature, like + f :: _ -> Int +then we *always* use the InferGen plan, and hence tcPolyInfer. +We do this even for a local binding with -XMonoLocalBinds. +Reasons: + * The TcSigInfo for 'f' has a unification variable for the '_', + whose TcLevel is one level deeper than the current level. + (See pushTcLevelM in tcTySig.) But NoGen doesn't increase + the TcLevel like InferGen, so we lose the level invariant. + + * The signature might be f :: forall a. _ -> a + so it really is polymorphic. It's not clear what it would + mean to use NoGen on this, and indeed the ASSERT in tcLhs, + in the (Just sig) case, checks that if there is a signature + then we are using LetLclBndr, and hence a nested AbsBinds with + increased TcLevel + +It might be possible to fix these difficulties somehow, but there +doesn't seem much point. Indeed, adding a partial type signature is a +way to get per-binding inferred generalisation. + Note [Validity of inferred types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We need to check inferred type for validity, in case it uses language @@ -1196,14 +1219,17 @@ tcLhs :: TcSigFun -> LetBndrSpec -> HsBind Name -> TcM TcMonoBind tcLhs sig_fn no_gen (FunBind { fun_id = L nm_loc name, fun_infix = inf, fun_matches = matches }) | Just sig <- sig_fn name = ASSERT2( case no_gen of { LetLclBndr -> True; LetGblBndr {} -> False } - , ppr name ) -- { f :: ty; f x = e } is always done via CheckGen - -- which gives rise to LetLclBndr. It wouldn't make - -- sense to have a *polymorphic* function Id at this point + , ppr name ) + -- { f :: ty; f x = e } is always done via CheckGen (full signature) + -- or InferGen (partial signature) + -- see Note [Partial type signatures and generalisation] + -- Both InferGen and CheckGen gives rise to LetLclBndr do { mono_name <- newLocalName name ; let mono_id = mkLocalId mono_name (sig_tau sig) ; addErrCtxt (typeSigCtxt name sig) $ emitWildcardHoleConstraints (sig_nwcs sig) ; return (TcFunBind (name, Just sig, mono_id) nm_loc inf matches) } + | otherwise = do { mono_ty <- newFlexiTyVarTy openTypeKind ; mono_id <- newNoSigLetBndr no_gen name mono_ty @@ -1455,12 +1481,15 @@ decideGeneralisationPlan :: DynFlags -> TcTypeEnv -> [Name] -> [LHsBind Name] -> TcSigFun -> GeneralisationPlan decideGeneralisationPlan dflags type_env bndr_names lbinds sig_fn - | strict_pat_binds = NoGen - | Just (lbind, sig) <- one_funbind_with_sig lbinds = CheckGen lbind sig - | mono_local_binds = NoGen - | otherwise = InferGen mono_restriction closed_flag - + | strict_pat_binds = NoGen + | Just (lbind, sig) <- one_funbind_with_sig = if isPartialSig sig + -- See Note [Partial type signatures and generalisation] + then infer_plan + else CheckGen lbind sig + | mono_local_binds = NoGen + | otherwise = infer_plan where + infer_plan = InferGen mono_restriction closed_flag bndr_set = mkNameSet bndr_names binds = map unLoc lbinds @@ -1503,12 +1532,11 @@ decideGeneralisationPlan dflags type_env bndr_names lbinds sig_fn -- With OutsideIn, all nested bindings are monomorphic -- except a single function binding with a signature - one_funbind_with_sig [lbind@(L _ (FunBind { fun_id = v }))] - = case sig_fn (unLoc v) of - Nothing -> Nothing - Just sig | isPartialSig sig -> Nothing - Just sig | otherwise -> Just (lbind, sig) - one_funbind_with_sig _ + one_funbind_with_sig + | [lbind@(L _ (FunBind { fun_id = v }))] <- lbinds + , Just sig <- sig_fn (unLoc v) + = Just (lbind, sig) + | otherwise = Nothing -- The Haskell 98 monomorphism resetriction From git at git.haskell.org Mon Jan 5 15:01:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:24 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Use a less fragile method for defaulting (e4c7531) Message-ID: <20150105150124.4DEE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/e4c7531db4d0999fe815fdb85e1a9069017a5492/ghc >--------------------------------------------------------------- commit e4c7531db4d0999fe815fdb85e1a9069017a5492 Author: Simon Peyton Jones Date: Mon Jan 5 10:53:37 2015 +0000 Use a less fragile method for defaulting When doing top-level defaulting, in TcSimplify.applyDefaultingRules, we were temporarily making a unification variable equal to the default type (Integer, say, or Float), as a 'given', and trying to solve. But this relied on the unification variable being untouchable, which seems complicated. It's much simpler just to generate a new set of constraints to solve, using newWantedEvVarNC in disambigGroup. (I tripped over an ASSERT failure, and this solved it in a robust way.) >--------------------------------------------------------------- e4c7531db4d0999fe815fdb85e1a9069017a5492 compiler/typecheck/TcSimplify.hs | 60 +++++++++++++++++++++++----------------- 1 file changed, 34 insertions(+), 26 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 0c9b093..61fd591 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -101,7 +101,7 @@ simpl_top wanteds | isEmptyWC wc = return wc | otherwise -- See Note [When to do type-class defaulting] - = do { something_happened <- applyDefaultingRules (approximateWC wc) + = do { something_happened <- applyDefaultingRules wc -- See Note [Top-level Defaulting Plan] ; if something_happened then do { wc_residual <- nestTcS (solveWantedsAndDrop wc) @@ -1337,13 +1337,13 @@ to beta[1], and that means the (a ~ beta[1]) will be stuck, as it should be. ********************************************************************************* -} -applyDefaultingRules :: Cts -> TcS Bool +applyDefaultingRules :: WantedConstraints -> TcS Bool -- True <=> I did some defaulting, reflected in ty_binds -- Return some extra derived equalities, which express the -- type-class default choice. applyDefaultingRules wanteds - | isEmptyBag wanteds + | isEmptyWC wanteds = return False | otherwise = do { traceTcS "applyDefaultingRules { " $ @@ -1351,8 +1351,10 @@ applyDefaultingRules wanteds ; info@(default_tys, _) <- getDefaultInfo ; let groups = findDefaultableGroups info wanteds + ; traceTcS "findDefaultableGroups" $ vcat [ text "groups=" <+> ppr groups , text "info=" <+> ppr info ] + ; something_happeneds <- mapM (disambigGroup default_tys) groups ; traceTcS "applyDefaultingRules }" (ppr something_happeneds) @@ -1361,19 +1363,27 @@ applyDefaultingRules wanteds findDefaultableGroups :: ( [Type] - , (Bool,Bool) ) -- (Overloaded strings, extended default rules) - -> Cts -- Unsolved (wanted or derived) - -> [[(Ct,Class,TcTyVar)]] + , (Bool,Bool) ) -- (Overloaded strings, extended default rules) + -> WantedConstraints -- Unsolved (wanted or derived) + -> [(TyVar, [Class], Cts)] findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds - | null default_tys = [] - | otherwise = defaultable_groups + | null default_tys + = [] + | otherwise + = [ (tv, clss, listToBag (map fstOf3 group)) + | group@((_,_,tv):_) <- groups + , let clss = map sndOf3 group + , defaultable_tyvar tv + , defaultable_classes clss ] where - defaultable_groups = filter is_defaultable_group groups - groups = equivClasses cmp_tv unaries - unaries :: [(Ct, Class, TcTyVar)] -- (C tv) constraints - non_unaries :: [Ct] -- and *other* constraints + simples = approximateWC wanteds + (unaries, non_unaries) = partitionWith find_unary (bagToList simples) + groups = equivClasses cmp_tv unaries + + groups :: [[(Ct, Class, TcTyVar)]] -- (C tv) constraints + unaries :: [(Ct, Class, TcTyVar)] -- (C tv) constraints + non_unaries :: [Ct] -- and *other* constraints - (unaries, non_unaries) = partitionWith find_unary (bagToList wanteds) -- Finds unary type-class constraints -- But take account of polykinded classes like Typeable, -- which may look like (Typeable * (a:*)) (Trac #8931) @@ -1392,12 +1402,10 @@ findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds cmp_tv (_,_,tv1) (_,_,tv2) = tv1 `compare` tv2 - is_defaultable_group ds@((_,_,tv):_) + defaultable_tyvar tv = let b1 = isTyConableTyVar tv -- Note [Avoiding spurious errors] b2 = not (tv `elemVarSet` bad_tvs) - b4 = defaultable_classes [cls | (_,cls,_) <- ds] - in (b1 && b2 && b4) - is_defaultable_group [] = panic "defaultable_group" + in b1 && b2 defaultable_classes clss | extended_defaults = any isInteractiveClass clss @@ -1417,20 +1425,22 @@ findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds ------------------------------ disambigGroup :: [Type] -- The default types - -> [(Ct, Class, TcTyVar)] -- All classes of the form (C a) + -> (TcTyVar, [Class], Cts) -- All classes of the form (C a) -- sharing same type variable -> TcS Bool -- True <=> something happened, reflected in ty_binds -disambigGroup [] _grp +disambigGroup [] _ = return False -disambigGroup (default_ty:default_tys) group - = do { traceTcS "disambigGroup {" (ppr group $$ ppr default_ty) +disambigGroup (default_ty:default_tys) group@(the_tv, clss, wanteds) + = do { traceTcS "disambigGroup {" (vcat [ ppr default_ty, ppr the_tv, ppr wanteds ]) ; fake_ev_binds_var <- TcS.newTcEvBinds - ; given_ev_var <- TcS.newEvVar (mkTcEqPred (mkTyVarTy the_tv) default_ty) ; tclvl <- TcS.getTcLevel ; success <- nestImplicTcS fake_ev_binds_var (pushTcLevel tclvl) $ - do { solveSimpleGivens loc [given_ev_var] - ; residual_wanted <- solveSimpleWanteds wanteds + do { wanted_evs <- mapM (newWantedEvVarNC loc) + [ mkClassPred cls [default_ty] + | cls <- clss ] + ; residual_wanted <- solveSimpleWanteds $ listToBag $ + map mkNonCanonical wanted_evs ; return (isEmptyWC residual_wanted) } ; if success then @@ -1445,8 +1455,6 @@ disambigGroup (default_ty:default_tys) group (ppr default_ty) ; disambigGroup default_tys group } } where - wanteds = listToBag (map fstOf3 group) - ((_,_,the_tv):_) = group loc = CtLoc { ctl_origin = GivenOrigin UnkSkol , ctl_env = panic "disambigGroup:env" , ctl_depth = initialSubGoalDepth } From git at git.haskell.org Mon Jan 5 15:01:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:26 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: wibble to robustify-defaulting (191b889) Message-ID: <20150105150126.E4E913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/191b889ae569aebbcadd50a662e9bb8bfcd56c24/ghc >--------------------------------------------------------------- commit 191b889ae569aebbcadd50a662e9bb8bfcd56c24 Author: Simon Peyton Jones Date: Mon Jan 5 11:46:49 2015 +0000 wibble to robustify-defaulting >--------------------------------------------------------------- 191b889ae569aebbcadd50a662e9bb8bfcd56c24 compiler/typecheck/TcSimplify.hs | 54 ++++++++++++++++++++++++---------------- 1 file changed, 32 insertions(+), 22 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 61fd591..68978df 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -20,6 +20,7 @@ import TcSMonad as TcS import TcInteract import Kind ( isKind, isSubKind, defaultKind_maybe ) import Inst +import Unify ( tcMatchTy ) import Type ( classifyPredType, isIPClass, PredTree(..) , getClassPredTys_maybe, EqRel(..) ) import TyCon ( isTypeFamilyTyCon ) @@ -1365,32 +1366,31 @@ findDefaultableGroups :: ( [Type] , (Bool,Bool) ) -- (Overloaded strings, extended default rules) -> WantedConstraints -- Unsolved (wanted or derived) - -> [(TyVar, [Class], Cts)] + -> [(TyVar, [Ct])] findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds | null default_tys = [] | otherwise - = [ (tv, clss, listToBag (map fstOf3 group)) - | group@((_,_,tv):_) <- groups - , let clss = map sndOf3 group + = [ (tv, map fstOf3 group) + | group@((_,_,tv):_) <- unary_groups , defaultable_tyvar tv - , defaultable_classes clss ] + , defaultable_classes (map sndOf3 group) ] where simples = approximateWC wanteds (unaries, non_unaries) = partitionWith find_unary (bagToList simples) - groups = equivClasses cmp_tv unaries + unary_groups = equivClasses cmp_tv unaries - groups :: [[(Ct, Class, TcTyVar)]] -- (C tv) constraints - unaries :: [(Ct, Class, TcTyVar)] -- (C tv) constraints - non_unaries :: [Ct] -- and *other* constraints + unary_groups :: [[(Ct, Class, TcTyVar)]] -- (C tv) constraints + unaries :: [(Ct, Class, TcTyVar)] -- (C tv) constraints + non_unaries :: [Ct] -- and *other* constraints -- Finds unary type-class constraints -- But take account of polykinded classes like Typeable, -- which may look like (Typeable * (a:*)) (Trac #8931) find_unary cc | Just (cls,tys) <- getClassPredTys_maybe (ctPred cc) - , Just (kinds, ty) <- snocView tys - , all isKind kinds + , Just (kinds, ty) <- snocView tys -- Ignore kind arguments + , all isKind kinds -- for this purpose , Just tv <- tcGetTyVar_maybe ty , isMetaTyVar tv -- We might have runtime-skolems in GHCi, and -- we definitely don't want to try to assign to those! @@ -1424,24 +1424,19 @@ findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds -- Similarly is_std_class ------------------------------ -disambigGroup :: [Type] -- The default types - -> (TcTyVar, [Class], Cts) -- All classes of the form (C a) - -- sharing same type variable +disambigGroup :: [Type] -- The default types + -> (TcTyVar, [Ct]) -- All classes of the form (C a) + -- sharing same type variable -> TcS Bool -- True <=> something happened, reflected in ty_binds disambigGroup [] _ = return False -disambigGroup (default_ty:default_tys) group@(the_tv, clss, wanteds) +disambigGroup (default_ty:default_tys) group@(the_tv, wanteds) = do { traceTcS "disambigGroup {" (vcat [ ppr default_ty, ppr the_tv, ppr wanteds ]) ; fake_ev_binds_var <- TcS.newTcEvBinds ; tclvl <- TcS.getTcLevel - ; success <- nestImplicTcS fake_ev_binds_var (pushTcLevel tclvl) $ - do { wanted_evs <- mapM (newWantedEvVarNC loc) - [ mkClassPred cls [default_ty] - | cls <- clss ] - ; residual_wanted <- solveSimpleWanteds $ listToBag $ - map mkNonCanonical wanted_evs - ; return (isEmptyWC residual_wanted) } + ; success <- nestImplicTcS fake_ev_binds_var (pushTcLevel tclvl) + try_group ; if success then -- Success: record the type variable binding, and return @@ -1455,6 +1450,21 @@ disambigGroup (default_ty:default_tys) group@(the_tv, clss, wanteds) (ppr default_ty) ; disambigGroup default_tys group } } where + try_group + | Just subst <- mb_subst + = do { wanted_evs <- mapM (newWantedEvVarNC loc . substTy subst . ctPred) + wanteds + ; residual_wanted <- solveSimpleWanteds $ listToBag $ + map mkNonCanonical wanted_evs + ; return (isEmptyWC residual_wanted) } + | otherwise + = return False + + tmpl_tvs = extendVarSet (tyVarsOfType (tyVarKind the_tv)) the_tv + mb_subst = tcMatchTy tmpl_tvs (mkTyVarTy the_tv) default_ty + -- Make sure the kinds match too; hence this call to tcMatchTy + -- E.g. suppose the only constraint was (Typeable k (a::k)) + loc = CtLoc { ctl_origin = GivenOrigin UnkSkol , ctl_env = panic "disambigGroup:env" , ctl_depth = initialSubGoalDepth } From git at git.haskell.org Mon Jan 5 15:01:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:29 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Print singleton consraints without parens (6ec089a) Message-ID: <20150105150129.99A423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/6ec089a820114a678dbd6df45ab4ddbd247ab0d5/ghc >--------------------------------------------------------------- commit 6ec089a820114a678dbd6df45ab4ddbd247ab0d5 Author: Simon Peyton Jones Date: Mon Jan 5 12:56:46 2015 +0000 Print singleton consraints without parens The main change is in TypeRep.pprTheta, so we print Eq a for a singleton, but (Eq a, Show a) for multiple constraints. There are lots of trivial knock-on changes to error messages >--------------------------------------------------------------- 6ec089a820114a678dbd6df45ab4ddbd247ab0d5 compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcErrors.hs | 8 ++++---- compiler/types/TypeRep.hs | 2 +- testsuite/tests/deriving/should_fail/T5287.stderr | 2 +- .../tests/deriving/should_fail/drvfail-functor2.stderr | 2 +- testsuite/tests/gadt/gadt-escape1.stderr | 2 +- testsuite/tests/gadt/gadt13.stderr | 2 +- testsuite/tests/gadt/gadt21.stderr | 2 +- testsuite/tests/gadt/gadt7.stderr | 2 +- .../tests/indexed-types/should_compile/Simple14.stderr | 2 +- .../tests/indexed-types/should_compile/T3208b.stderr | 8 ++++---- testsuite/tests/indexed-types/should_fail/T2664.stderr | 4 ++-- testsuite/tests/indexed-types/should_fail/T3440.stderr | 4 ++-- .../tests/indexed-types/should_fail/T4093a.stderr | 4 ++-- .../tests/indexed-types/should_fail/T4093b.stderr | 6 +++--- testsuite/tests/indexed-types/should_fail/T8155.stderr | 2 +- testsuite/tests/module/mod47.stderr | 2 +- .../WarningWildcardInstantiations.stderr | 5 ++--- .../ExtraConstraintsWildcardNotEnabled.stderr | 2 +- .../InstantiatedNamedWildcardsInConstraints.stderr | 2 +- .../should_fail/WildcardInstantiations.stderr | 2 +- testsuite/tests/polykinds/T7230.stderr | 8 ++++---- testsuite/tests/polykinds/T7438.stderr | 2 +- testsuite/tests/polykinds/T7594.stderr | 2 +- testsuite/tests/polykinds/T8566.stderr | 4 ++-- testsuite/tests/polykinds/T9222.stderr | 2 +- testsuite/tests/typecheck/should_compile/T7220a.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc168.stderr | 2 +- .../should_fail/FailDueToGivenOverlapping.stderr | 2 +- testsuite/tests/typecheck/should_fail/IPFail.stderr | 2 +- testsuite/tests/typecheck/should_fail/T1897a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/T5853.stderr | 18 +++++++++--------- testsuite/tests/typecheck/should_fail/T7279.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7525.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/T7857.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8912.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9109.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail034.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail041.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail042.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/tcfail067.stderr | 8 ++++---- testsuite/tests/typecheck/should_fail/tcfail072.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail080.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail097.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail098.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail102.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail108.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail130.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail142.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail181.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail208.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail211.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail213.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail214.stderr | 2 +- 55 files changed, 85 insertions(+), 86 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6ec089a820114a678dbd6df45ab4ddbd247ab0d5 From git at git.haskell.org Mon Jan 5 15:01:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:32 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Major patch to add -fwarn-redundant-constraints (440e39e) Message-ID: <20150105150132.7F3EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/440e39e603d3a2da4b5472e5c2a43dc6f66bfb61/ghc >--------------------------------------------------------------- commit 440e39e603d3a2da4b5472e5c2a43dc6f66bfb61 Author: Simon Peyton Jones Date: Mon Jan 5 13:20:48 2015 +0000 Major patch to add -fwarn-redundant-constraints The idea was promted by Trac #9939, but it was Christmas, so I did some recreational programming that went much further. The idea is to warn when a constraint in a user-supplied context is redundant. Everything is described in detail in Note [Tracking redundant constraints] in TcSimplify. Main changes: * The new ic_status field in an implication, of type ImplicStatus. It replaces ic_insol, and includes information about redundant constraints. * New function TcSimplify.setImplicationStatus sets the ic_status. * TcSigInfo has sig_report_redundant field to say whenther a redundant constraint should be reported; and similarly the FunSigCtxt constructor of UserTypeCtxt * EvBinds has a field eb_is_given, to record whether it is a given or wanted binding. Some consequential chagnes to creating an evidence binding (so that we record whether it is given or wanted). * AbsBinds field abs_ev_binds is now a *list* of TcEvBiinds; see Note [Typechecking plan for instance declarations] in TcInstDcls * Some significant changes to the type checking of instance declarations; Note [Typechecking plan for instance declarations] in TcInstDcls. * I found that TcErrors.relevantBindings was failing to zonk the origin of the constraint it was looking at, and hence failing to find some relevant bindings. Easy to fix, and orthogonal to everything else, but hard to disentangle. Some minor refactorig: * TcMType.newSimpleWanteds moves to Inst, renamed as newWanteds * TcClassDcl and TcInstDcls now have their own code for typechecking a method body, rather than sharing a single function. The shared function (ws TcClassDcl.tcInstanceMethodBody) didn't have much code and the differences were growing confusing. * Add new function TcRnMonad.pushLevelAndCaptureConstraints, and use it * Add new function Bag.catBagMaybes, and use it in TcSimplify >--------------------------------------------------------------- 440e39e603d3a2da4b5472e5c2a43dc6f66bfb61 compiler/basicTypes/BasicTypes.hs | 2 + compiler/deSugar/DsArrows.hs | 4 +- compiler/deSugar/DsBinds.hs | 27 +- compiler/deSugar/DsExpr.hs | 2 +- compiler/hsSyn/HsBinds.hs | 9 +- compiler/iface/BuildTyCl.hs | 2 +- compiler/iface/IfaceSyn.hs | 2 +- compiler/main/DynFlags.hs | 7 +- compiler/typecheck/Inst.hs | 18 +- compiler/typecheck/TcBinds.hs | 52 ++- compiler/typecheck/TcCanonical.hs | 30 +- compiler/typecheck/TcClassDcl.hs | 133 +++---- compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcErrors.hs | 244 +++++++----- compiler/typecheck/TcEvidence.hs | 42 ++- compiler/typecheck/TcFlatten.hs | 6 +- compiler/typecheck/TcHsSyn.hs | 31 +- compiler/typecheck/TcInstDcls.hs | 751 ++++++++++++++++++++++--------------- compiler/typecheck/TcInteract.hs | 63 ++-- compiler/typecheck/TcMType.hs | 35 +- compiler/typecheck/TcMatches.hs | 2 +- compiler/typecheck/TcPat.hs | 29 +- compiler/typecheck/TcPatSyn.hs | 16 +- compiler/typecheck/TcRnDriver.hs | 5 +- compiler/typecheck/TcRnMonad.hs | 33 +- compiler/typecheck/TcRnTypes.hs | 79 +++- compiler/typecheck/TcRules.hs | 36 +- compiler/typecheck/TcSMonad.hs | 42 ++- compiler/typecheck/TcSimplify.hs | 270 +++++++++++-- compiler/typecheck/TcTyClsDecls.hs | 6 +- compiler/typecheck/TcType.hs | 18 +- compiler/typecheck/TcUnify.hs | 37 +- compiler/typecheck/TcValidity.hs | 2 +- compiler/utils/Bag.hs | 15 +- compiler/utils/Util.hs | 2 + 35 files changed, 1271 insertions(+), 783 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 440e39e603d3a2da4b5472e5c2a43dc6f66bfb61 From git at git.haskell.org Mon Jan 5 15:01:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:35 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: User manual wibble (357c3ac) Message-ID: <20150105150135.1FEED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/357c3acef26e44d8e90b6f4f2520da4bcbfa877d/ghc >--------------------------------------------------------------- commit 357c3acef26e44d8e90b6f4f2520da4bcbfa877d Author: Simon Peyton Jones Date: Mon Jan 5 13:21:31 2015 +0000 User manual wibble >--------------------------------------------------------------- 357c3acef26e44d8e90b6f4f2520da4bcbfa877d docs/users_guide/using.xml | 32 ++++++++++++++++++++++++++++++++ 1 file changed, 32 insertions(+) diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 3059cff..88dbdb7 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -1408,6 +1408,38 @@ foreign import "&f" f :: FunPtr t The warning will indicate the duplicated Eq a constraint. + This option is now deprecated in favour of . + + + + + : + + + redundant constraints, warning + + Have the compiler warn about redundant constraints in a type signature. For + example + + + + f :: (Eq a, Ord a) => a -> a + + The warning will indicate the redundant Eq a constraint: + it is subsumed by the Ord a constraint. + + + + f :: Eq a => a -> a -> Bool + f x y = True + + The warning will indicate the redundant Eq a constraint: + : it is not used by the definition of f.) + + + Similar warnings are given for a redundant constraint in an instance declaration. + + This option is on by default. From git at git.haskell.org Mon Jan 5 15:01:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:37 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Error message wibbles following -fwarn-redundant-constraints (02ddcd2) Message-ID: <20150105150137.D9E9E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/02ddcd2ebab4d4f137941413c13f9ddc9cdae534/ghc >--------------------------------------------------------------- commit 02ddcd2ebab4d4f137941413c13f9ddc9cdae534 Author: Simon Peyton Jones Date: Mon Jan 5 13:26:05 2015 +0000 Error message wibbles following -fwarn-redundant-constraints Lots of small changes: * Many tests deliberately have functions like foo :: Eq a => blah foo = error "urk" and that (rightly) gives a redundant-constraint warning. So I add {-# OPTIONS -fno-warn-redundant-constraints #-} to all those tests That in turn changes the line number of error message for the test * A few tests had unnecessary redundant constraints; I removed them * Small change to error message for superclasses * One change (tcfail143) in which error is reported, when there is more than one on the same line >--------------------------------------------------------------- 02ddcd2ebab4d4f137941413c13f9ddc9cdae534 testsuite/tests/arrows/should_compile/arrowpat.hs | 3 ++- testsuite/tests/codeGen/should_compile/T3286.hs | 1 + testsuite/tests/deriving/should_compile/T2856.hs | 1 + testsuite/tests/deriving/should_compile/T4966.hs | 2 ++ testsuite/tests/deriving/should_compile/T4966.stderr | 4 ++-- .../tests/deriving/should_compile/deriving-1935.hs | 2 ++ .../deriving/should_compile/deriving-1935.stderr | 6 +++--- testsuite/tests/deriving/should_compile/drv001.hs | 2 ++ testsuite/tests/deriving/should_compile/drv002.hs | 2 ++ testsuite/tests/deriving/should_compile/drv003.hs | 2 ++ .../tests/deriving/should_compile/drv003.stderr | 4 ++-- testsuite/tests/deriving/should_run/T9576.stderr | 2 +- testsuite/tests/gadt/Gadt17_help.hs | 2 +- testsuite/tests/ghci/scripts/T5045.hs | 1 + testsuite/tests/ghci/scripts/T8357.hs | 1 + testsuite/tests/ghci/scripts/T8931.script | 1 + testsuite/tests/ghci/scripts/ghci044.script | 1 + testsuite/tests/ghci/scripts/ghci044.stderr | 6 +++--- testsuite/tests/ghci/scripts/ghci047.script | 1 + testsuite/tests/ghci/scripts/ghci047.stderr | 4 ++-- testsuite/tests/haddock/haddock_examples/Test.hs | 1 + .../haddock/haddock_examples/haddock.Test.stderr | 8 ++++---- .../should_compile_flag_haddock/haddockA023.hs | 2 ++ .../should_compile_flag_haddock/haddockA026.hs | 2 ++ .../should_compile_flag_haddock/haddockA027.hs | 2 ++ .../should_compile_noflag_haddock/haddockC026.hs | 2 ++ .../should_compile_noflag_haddock/haddockC027.hs | 2 ++ .../tests/indexed-types/should_compile/Class2.hs | 1 + .../tests/indexed-types/should_compile/Gentle.hs | 1 + .../indexed-types/should_compile/InstContextNorm.hs | 1 + .../indexed-types/should_compile/InstEqContext.hs | 1 + .../indexed-types/should_compile/InstEqContext2.hs | 1 + .../indexed-types/should_compile/InstEqContext3.hs | 1 + .../indexed-types/should_compile/NonLinearLHS.hs | 1 + .../tests/indexed-types/should_compile/Rules1.hs | 1 + .../tests/indexed-types/should_compile/Simple24.hs | 1 + .../tests/indexed-types/should_compile/T2448.hs | 1 + .../tests/indexed-types/should_compile/T3023.hs | 3 ++- .../tests/indexed-types/should_compile/T3023.stderr | 5 ++--- .../tests/indexed-types/should_compile/T3484.hs | 3 ++- .../tests/indexed-types/should_compile/T4200.hs | 1 + .../tests/indexed-types/should_compile/T4497.hs | 1 + .../tests/indexed-types/should_compile/T4981-V1.hs | 2 ++ .../tests/indexed-types/should_compile/T4981-V2.hs | 2 ++ .../tests/indexed-types/should_compile/T4981-V3.hs | 2 ++ .../tests/indexed-types/should_compile/T5002.hs | 1 + .../tests/indexed-types/should_compile/T9090.hs | 2 ++ .../tests/indexed-types/should_compile/T9316.hs | 1 + .../tests/indexed-types/should_compile/T9747.hs | 2 ++ testsuite/tests/indexed-types/should_fail/T2239.hs | 1 + .../tests/indexed-types/should_fail/T3330c.stderr | 4 ++++ testsuite/tests/indexed-types/should_fail/T7862.hs | 1 + .../tests/indexed-types/should_fail/T7862.stderr | 2 +- testsuite/tests/module/mod129.hs | 2 ++ testsuite/tests/module/mod71.stderr | 9 +++++++++ testsuite/tests/parser/should_compile/mc15.hs | 2 +- testsuite/tests/parser/should_compile/read002.hs | 2 ++ testsuite/tests/partial-sigs/should_compile/all.T | 2 +- testsuite/tests/patsyn/should_compile/T8584-2.hs | 2 ++ testsuite/tests/patsyn/should_compile/T8968-1.hs | 1 + testsuite/tests/patsyn/should_compile/all.T | 4 ++-- testsuite/tests/patsyn/should_compile/ex-view.hs | 4 +++- testsuite/tests/perf/compiler/T3064.hs | 2 ++ testsuite/tests/perf/compiler/T5030.hs | 6 +++--- testsuite/tests/polykinds/PolyKinds08.hs | 1 + testsuite/tests/polykinds/T6015a.hs | 1 + testsuite/tests/polykinds/T6020a.hs | 1 + testsuite/tests/polykinds/T6068.hs | 1 + testsuite/tests/polykinds/T7090.hs | 1 + testsuite/tests/polykinds/T7332.hs | 20 ++++++++++++++++++-- testsuite/tests/polykinds/T8359.hs | 2 ++ testsuite/tests/polykinds/T9569.hs | 1 + testsuite/tests/polykinds/T9750.hs | 1 + testsuite/tests/rebindable/T5821.hs | 3 ++- testsuite/tests/rebindable/rebindable9.hs | 4 ++-- testsuite/tests/rename/should_fail/rnfail020.hs | 1 + testsuite/tests/simplCore/should_compile/T3831.hs | 1 + testsuite/tests/simplCore/should_compile/T4398.hs | 1 + .../tests/simplCore/should_compile/T4398.stderr | 2 +- testsuite/tests/simplCore/should_compile/T5329.hs | 1 + testsuite/tests/simplCore/should_compile/T5342.hs | 1 + testsuite/tests/simplCore/should_compile/T5359b.hs | 1 + .../tests/simplCore/should_compile/T5359b.stderr | 2 +- testsuite/tests/simplCore/should_compile/T8848.hs | 3 ++- .../tests/simplCore/should_compile/T8848.stderr | 2 +- testsuite/tests/simplCore/should_compile/T8848a.hs | 1 + testsuite/tests/simplCore/should_compile/simpl002.hs | 2 ++ testsuite/tests/simplCore/should_compile/simpl007.hs | 1 + testsuite/tests/simplCore/should_compile/simpl014.hs | 1 + testsuite/tests/simplCore/should_compile/simpl016.hs | 2 ++ .../tests/simplCore/should_compile/simpl016.stderr | 2 +- testsuite/tests/simplCore/should_compile/spec003.hs | 2 ++ testsuite/tests/th/T3100.hs | 1 + testsuite/tests/th/T7021a.hs | 1 + testsuite/tests/th/T8807.hs | 1 + testsuite/tests/th/TH_tf3.hs | 1 + .../typecheck/should_compile/GivenOverlapping.hs | 1 + .../tests/typecheck/should_compile/LoopOfTheDay1.hs | 1 + .../tests/typecheck/should_compile/LoopOfTheDay2.hs | 1 + .../tests/typecheck/should_compile/LoopOfTheDay3.hs | 1 + testsuite/tests/typecheck/should_compile/T1470.hs | 1 + testsuite/tests/typecheck/should_compile/T2683.hs | 1 + testsuite/tests/typecheck/should_compile/T3018.hs | 1 + testsuite/tests/typecheck/should_compile/T3108.hs | 1 + testsuite/tests/typecheck/should_compile/T3692.hs | 1 + testsuite/tests/typecheck/should_compile/T3743.hs | 1 + testsuite/tests/typecheck/should_compile/T4361.hs | 1 + testsuite/tests/typecheck/should_compile/T4401.hs | 1 + testsuite/tests/typecheck/should_compile/T4524.hs | 1 + testsuite/tests/typecheck/should_compile/T4952.hs | 1 + testsuite/tests/typecheck/should_compile/T4969.hs | 2 +- testsuite/tests/typecheck/should_compile/T5514.hs | 1 + testsuite/tests/typecheck/should_compile/T5581.hs | 2 ++ testsuite/tests/typecheck/should_compile/T5676.hs | 1 + testsuite/tests/typecheck/should_compile/T6055.hs | 1 + testsuite/tests/typecheck/should_compile/T6134.hs | 1 + testsuite/tests/typecheck/should_compile/T7171a.hs | 1 + testsuite/tests/typecheck/should_compile/T7196.hs | 1 + testsuite/tests/typecheck/should_compile/T7220.hs | 1 + testsuite/tests/typecheck/should_compile/T7541.hs | 2 +- testsuite/tests/typecheck/should_compile/T7875.hs | 1 + testsuite/tests/typecheck/should_compile/T7903.hs | 1 + .../tests/typecheck/should_compile/T7903.stderr-ghc | 4 ++-- .../tests/typecheck/should_compile/Tc170_Aux.hs | 1 + testsuite/tests/typecheck/should_compile/Tc173a.hs | 2 ++ testsuite/tests/typecheck/should_compile/tc045.hs | 1 + testsuite/tests/typecheck/should_compile/tc051.hs | 2 ++ .../tests/typecheck/should_compile/tc056.stderr | 6 ++---- testsuite/tests/typecheck/should_compile/tc058.hs | 2 ++ testsuite/tests/typecheck/should_compile/tc065.hs | 4 ++-- testsuite/tests/typecheck/should_compile/tc078.hs | 2 ++ .../tests/typecheck/should_compile/tc078.stderr-ghc | 4 ++-- testsuite/tests/typecheck/should_compile/tc079.hs | 2 ++ testsuite/tests/typecheck/should_compile/tc088.hs | 2 ++ testsuite/tests/typecheck/should_compile/tc091.hs | 2 ++ testsuite/tests/typecheck/should_compile/tc092.hs | 1 + testsuite/tests/typecheck/should_compile/tc109.hs | 1 + testsuite/tests/typecheck/should_compile/tc113.hs | 2 ++ testsuite/tests/typecheck/should_compile/tc115.hs | 1 + .../tests/typecheck/should_compile/tc115.stderr-ghc | 2 +- testsuite/tests/typecheck/should_compile/tc116.hs | 1 + .../tests/typecheck/should_compile/tc116.stderr-ghc | 2 +- testsuite/tests/typecheck/should_compile/tc125.hs | 1 + .../tests/typecheck/should_compile/tc125.stderr-ghc | 10 +++++----- testsuite/tests/typecheck/should_compile/tc126.hs | 1 + .../tests/typecheck/should_compile/tc126.stderr-ghc | 4 ++-- testsuite/tests/typecheck/should_compile/tc145.hs | 1 + testsuite/tests/typecheck/should_compile/tc152.hs | 1 + testsuite/tests/typecheck/should_compile/tc176.hs | 1 + testsuite/tests/typecheck/should_compile/tc178.hs | 1 + testsuite/tests/typecheck/should_compile/tc180.hs | 1 + testsuite/tests/typecheck/should_compile/tc181.hs | 1 + testsuite/tests/typecheck/should_compile/tc183.hs | 1 + testsuite/tests/typecheck/should_compile/tc187.hs | 1 + testsuite/tests/typecheck/should_compile/tc192.hs | 1 + testsuite/tests/typecheck/should_compile/tc203.hs | 1 + testsuite/tests/typecheck/should_compile/tc204.hs | 3 ++- testsuite/tests/typecheck/should_compile/tc206.hs | 1 + testsuite/tests/typecheck/should_compile/tc208.hs | 1 + testsuite/tests/typecheck/should_compile/tc229.hs | 1 + testsuite/tests/typecheck/should_compile/tc230.hs | 1 + testsuite/tests/typecheck/should_compile/tc235.hs | 1 + testsuite/tests/typecheck/should_compile/tc237.hs | 1 + testsuite/tests/typecheck/should_compile/tc239.hs | 1 + testsuite/tests/typecheck/should_compile/twins.hs | 1 + testsuite/tests/typecheck/should_fail/T6161.stderr | 4 +++- .../tests/typecheck/should_fail/tcfail017.stderr | 4 +++- .../tests/typecheck/should_fail/tcfail020.stderr | 4 +++- testsuite/tests/typecheck/should_fail/tcfail071.hs | 2 ++ testsuite/tests/typecheck/should_fail/tcfail138.hs | 1 + .../tests/typecheck/should_fail/tcfail143.stderr | 4 ++-- 171 files changed, 271 insertions(+), 70 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 02ddcd2ebab4d4f137941413c13f9ddc9cdae534 From git at git.haskell.org Mon Jan 5 15:01:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 15:01:40 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints's head updated: Error message wibbles following -fwarn-redundant-constraints (02ddcd2) Message-ID: <20150105150140.5DDE23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/redundant-constraints' now includes: 633814f Mark T9938 as not broken af4d998 Don't do a half-hearted recompilation check in compileOne 2223e19 Fix #9243 so recompilation avoidance works with -fno-code d84742b Update Cabal submodule to latest 1.22 snapshot 63cf7a4 Modify a couple of error messages slightly eaf2638 Replace fixVarSet with transCloVarSet 8088ab6 Remove redundant constraints in GHC source code discovered by -fwarn-redundant-constraints b129f95 Always generalise a partial type signature e4c7531 Use a less fragile method for defaulting 191b889 wibble to robustify-defaulting 6ec089a Print singleton consraints without parens 440e39e Major patch to add -fwarn-redundant-constraints 357c3ac User manual wibble 02ddcd2 Error message wibbles following -fwarn-redundant-constraints From git at git.haskell.org Mon Jan 5 16:59:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 16:59:52 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Always generalise a partial type signature (acf9aaa) Message-ID: <20150105165952.133F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/acf9aaa672dbc004c45bfcc09b7f9187412971c4/ghc >--------------------------------------------------------------- commit acf9aaa672dbc004c45bfcc09b7f9187412971c4 Author: Simon Peyton Jones Date: Mon Jan 5 10:39:46 2015 +0000 Always generalise a partial type signature This fixes an ASSERT failure in TcBinds. The problem was that we were generating NoGen plan for a function with a partial type signature, and that led to confusion and lost invariants. See Note [Partial type signatures and generalisation] in TcBinds >--------------------------------------------------------------- acf9aaa672dbc004c45bfcc09b7f9187412971c4 compiler/typecheck/TcBinds.hs | 56 ++++++++++++++++++++++++++++++++----------- 1 file changed, 42 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index 842ccfa..b4bb65d 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -769,6 +769,29 @@ completeTheta inferred_theta , typeSigCtxt (idName poly_id) sig ] {- +Note [Partial type signatures and generalisation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When we have a partial type signature, like + f :: _ -> Int +then we *always* use the InferGen plan, and hence tcPolyInfer. +We do this even for a local binding with -XMonoLocalBinds. +Reasons: + * The TcSigInfo for 'f' has a unification variable for the '_', + whose TcLevel is one level deeper than the current level. + (See pushTcLevelM in tcTySig.) But NoGen doesn't increase + the TcLevel like InferGen, so we lose the level invariant. + + * The signature might be f :: forall a. _ -> a + so it really is polymorphic. It's not clear what it would + mean to use NoGen on this, and indeed the ASSERT in tcLhs, + in the (Just sig) case, checks that if there is a signature + then we are using LetLclBndr, and hence a nested AbsBinds with + increased TcLevel + +It might be possible to fix these difficulties somehow, but there +doesn't seem much point. Indeed, adding a partial type signature is a +way to get per-binding inferred generalisation. + Note [Validity of inferred types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We need to check inferred type for validity, in case it uses language @@ -1196,14 +1219,17 @@ tcLhs :: TcSigFun -> LetBndrSpec -> HsBind Name -> TcM TcMonoBind tcLhs sig_fn no_gen (FunBind { fun_id = L nm_loc name, fun_infix = inf, fun_matches = matches }) | Just sig <- sig_fn name = ASSERT2( case no_gen of { LetLclBndr -> True; LetGblBndr {} -> False } - , ppr name ) -- { f :: ty; f x = e } is always done via CheckGen - -- which gives rise to LetLclBndr. It wouldn't make - -- sense to have a *polymorphic* function Id at this point + , ppr name ) + -- { f :: ty; f x = e } is always done via CheckGen (full signature) + -- or InferGen (partial signature) + -- see Note [Partial type signatures and generalisation] + -- Both InferGen and CheckGen gives rise to LetLclBndr do { mono_name <- newLocalName name ; let mono_id = mkLocalId mono_name (sig_tau sig) ; addErrCtxt (typeSigCtxt name sig) $ emitWildcardHoleConstraints (sig_nwcs sig) ; return (TcFunBind (name, Just sig, mono_id) nm_loc inf matches) } + | otherwise = do { mono_ty <- newFlexiTyVarTy openTypeKind ; mono_id <- newNoSigLetBndr no_gen name mono_ty @@ -1455,12 +1481,15 @@ decideGeneralisationPlan :: DynFlags -> TcTypeEnv -> [Name] -> [LHsBind Name] -> TcSigFun -> GeneralisationPlan decideGeneralisationPlan dflags type_env bndr_names lbinds sig_fn - | strict_pat_binds = NoGen - | Just (lbind, sig) <- one_funbind_with_sig lbinds = CheckGen lbind sig - | mono_local_binds = NoGen - | otherwise = InferGen mono_restriction closed_flag - + | strict_pat_binds = NoGen + | Just (lbind, sig) <- one_funbind_with_sig = if isPartialSig sig + -- See Note [Partial type signatures and generalisation] + then infer_plan + else CheckGen lbind sig + | mono_local_binds = NoGen + | otherwise = infer_plan where + infer_plan = InferGen mono_restriction closed_flag bndr_set = mkNameSet bndr_names binds = map unLoc lbinds @@ -1503,12 +1532,11 @@ decideGeneralisationPlan dflags type_env bndr_names lbinds sig_fn -- With OutsideIn, all nested bindings are monomorphic -- except a single function binding with a signature - one_funbind_with_sig [lbind@(L _ (FunBind { fun_id = v }))] - = case sig_fn (unLoc v) of - Nothing -> Nothing - Just sig | isPartialSig sig -> Nothing - Just sig | otherwise -> Just (lbind, sig) - one_funbind_with_sig _ + one_funbind_with_sig + | [lbind@(L _ (FunBind { fun_id = v }))] <- lbinds + , Just sig <- sig_fn (unLoc v) + = Just (lbind, sig) + | otherwise = Nothing -- The Haskell 98 monomorphism resetriction From git at git.haskell.org Mon Jan 5 16:59:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 16:59:54 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Use a less fragile method for defaulting (824df94) Message-ID: <20150105165954.BE6CB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/824df94984b4fb53bd1a45f47f2ed3f6c14efd65/ghc >--------------------------------------------------------------- commit 824df94984b4fb53bd1a45f47f2ed3f6c14efd65 Author: Simon Peyton Jones Date: Mon Jan 5 10:53:37 2015 +0000 Use a less fragile method for defaulting When doing top-level defaulting, in TcSimplify.applyDefaultingRules, we were temporarily making a unification variable equal to the default type (Integer, say, or Float), as a 'given', and trying to solve. But this relied on the unification variable being untouchable, which seems complicated. It's much simpler just to generate a new set of constraints to solve, using newWantedEvVarNC in disambigGroup. (I tripped over an ASSERT failure, and this solved it in a robust way.) >--------------------------------------------------------------- 824df94984b4fb53bd1a45f47f2ed3f6c14efd65 compiler/typecheck/TcSimplify.hs | 82 ++++++++++++++++++++++++---------------- 1 file changed, 50 insertions(+), 32 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 0c9b093..68978df 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -20,6 +20,7 @@ import TcSMonad as TcS import TcInteract import Kind ( isKind, isSubKind, defaultKind_maybe ) import Inst +import Unify ( tcMatchTy ) import Type ( classifyPredType, isIPClass, PredTree(..) , getClassPredTys_maybe, EqRel(..) ) import TyCon ( isTypeFamilyTyCon ) @@ -101,7 +102,7 @@ simpl_top wanteds | isEmptyWC wc = return wc | otherwise -- See Note [When to do type-class defaulting] - = do { something_happened <- applyDefaultingRules (approximateWC wc) + = do { something_happened <- applyDefaultingRules wc -- See Note [Top-level Defaulting Plan] ; if something_happened then do { wc_residual <- nestTcS (solveWantedsAndDrop wc) @@ -1337,13 +1338,13 @@ to beta[1], and that means the (a ~ beta[1]) will be stuck, as it should be. ********************************************************************************* -} -applyDefaultingRules :: Cts -> TcS Bool +applyDefaultingRules :: WantedConstraints -> TcS Bool -- True <=> I did some defaulting, reflected in ty_binds -- Return some extra derived equalities, which express the -- type-class default choice. applyDefaultingRules wanteds - | isEmptyBag wanteds + | isEmptyWC wanteds = return False | otherwise = do { traceTcS "applyDefaultingRules { " $ @@ -1351,8 +1352,10 @@ applyDefaultingRules wanteds ; info@(default_tys, _) <- getDefaultInfo ; let groups = findDefaultableGroups info wanteds + ; traceTcS "findDefaultableGroups" $ vcat [ text "groups=" <+> ppr groups , text "info=" <+> ppr info ] + ; something_happeneds <- mapM (disambigGroup default_tys) groups ; traceTcS "applyDefaultingRules }" (ppr something_happeneds) @@ -1361,26 +1364,33 @@ applyDefaultingRules wanteds findDefaultableGroups :: ( [Type] - , (Bool,Bool) ) -- (Overloaded strings, extended default rules) - -> Cts -- Unsolved (wanted or derived) - -> [[(Ct,Class,TcTyVar)]] + , (Bool,Bool) ) -- (Overloaded strings, extended default rules) + -> WantedConstraints -- Unsolved (wanted or derived) + -> [(TyVar, [Ct])] findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds - | null default_tys = [] - | otherwise = defaultable_groups + | null default_tys + = [] + | otherwise + = [ (tv, map fstOf3 group) + | group@((_,_,tv):_) <- unary_groups + , defaultable_tyvar tv + , defaultable_classes (map sndOf3 group) ] where - defaultable_groups = filter is_defaultable_group groups - groups = equivClasses cmp_tv unaries - unaries :: [(Ct, Class, TcTyVar)] -- (C tv) constraints - non_unaries :: [Ct] -- and *other* constraints + simples = approximateWC wanteds + (unaries, non_unaries) = partitionWith find_unary (bagToList simples) + unary_groups = equivClasses cmp_tv unaries + + unary_groups :: [[(Ct, Class, TcTyVar)]] -- (C tv) constraints + unaries :: [(Ct, Class, TcTyVar)] -- (C tv) constraints + non_unaries :: [Ct] -- and *other* constraints - (unaries, non_unaries) = partitionWith find_unary (bagToList wanteds) -- Finds unary type-class constraints -- But take account of polykinded classes like Typeable, -- which may look like (Typeable * (a:*)) (Trac #8931) find_unary cc | Just (cls,tys) <- getClassPredTys_maybe (ctPred cc) - , Just (kinds, ty) <- snocView tys - , all isKind kinds + , Just (kinds, ty) <- snocView tys -- Ignore kind arguments + , all isKind kinds -- for this purpose , Just tv <- tcGetTyVar_maybe ty , isMetaTyVar tv -- We might have runtime-skolems in GHCi, and -- we definitely don't want to try to assign to those! @@ -1392,12 +1402,10 @@ findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds cmp_tv (_,_,tv1) (_,_,tv2) = tv1 `compare` tv2 - is_defaultable_group ds@((_,_,tv):_) + defaultable_tyvar tv = let b1 = isTyConableTyVar tv -- Note [Avoiding spurious errors] b2 = not (tv `elemVarSet` bad_tvs) - b4 = defaultable_classes [cls | (_,cls,_) <- ds] - in (b1 && b2 && b4) - is_defaultable_group [] = panic "defaultable_group" + in b1 && b2 defaultable_classes clss | extended_defaults = any isInteractiveClass clss @@ -1416,22 +1424,19 @@ findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds -- Similarly is_std_class ------------------------------ -disambigGroup :: [Type] -- The default types - -> [(Ct, Class, TcTyVar)] -- All classes of the form (C a) - -- sharing same type variable +disambigGroup :: [Type] -- The default types + -> (TcTyVar, [Ct]) -- All classes of the form (C a) + -- sharing same type variable -> TcS Bool -- True <=> something happened, reflected in ty_binds -disambigGroup [] _grp +disambigGroup [] _ = return False -disambigGroup (default_ty:default_tys) group - = do { traceTcS "disambigGroup {" (ppr group $$ ppr default_ty) +disambigGroup (default_ty:default_tys) group@(the_tv, wanteds) + = do { traceTcS "disambigGroup {" (vcat [ ppr default_ty, ppr the_tv, ppr wanteds ]) ; fake_ev_binds_var <- TcS.newTcEvBinds - ; given_ev_var <- TcS.newEvVar (mkTcEqPred (mkTyVarTy the_tv) default_ty) ; tclvl <- TcS.getTcLevel - ; success <- nestImplicTcS fake_ev_binds_var (pushTcLevel tclvl) $ - do { solveSimpleGivens loc [given_ev_var] - ; residual_wanted <- solveSimpleWanteds wanteds - ; return (isEmptyWC residual_wanted) } + ; success <- nestImplicTcS fake_ev_binds_var (pushTcLevel tclvl) + try_group ; if success then -- Success: record the type variable binding, and return @@ -1445,8 +1450,21 @@ disambigGroup (default_ty:default_tys) group (ppr default_ty) ; disambigGroup default_tys group } } where - wanteds = listToBag (map fstOf3 group) - ((_,_,the_tv):_) = group + try_group + | Just subst <- mb_subst + = do { wanted_evs <- mapM (newWantedEvVarNC loc . substTy subst . ctPred) + wanteds + ; residual_wanted <- solveSimpleWanteds $ listToBag $ + map mkNonCanonical wanted_evs + ; return (isEmptyWC residual_wanted) } + | otherwise + = return False + + tmpl_tvs = extendVarSet (tyVarsOfType (tyVarKind the_tv)) the_tv + mb_subst = tcMatchTy tmpl_tvs (mkTyVarTy the_tv) default_ty + -- Make sure the kinds match too; hence this call to tcMatchTy + -- E.g. suppose the only constraint was (Typeable k (a::k)) + loc = CtLoc { ctl_origin = GivenOrigin UnkSkol , ctl_env = panic "disambigGroup:env" , ctl_depth = initialSubGoalDepth } From git at git.haskell.org Mon Jan 5 16:59:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 16:59:57 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Print singleton consraints without parens (38abdab) Message-ID: <20150105165957.7EA873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/38abdab8e907300ab3110d0df117eb54e35913c2/ghc >--------------------------------------------------------------- commit 38abdab8e907300ab3110d0df117eb54e35913c2 Author: Simon Peyton Jones Date: Mon Jan 5 12:56:46 2015 +0000 Print singleton consraints without parens The main change is in TypeRep.pprTheta, so we print Eq a for a singleton, but (Eq a, Show a) for multiple constraints. There are lots of trivial knock-on changes to error messages >--------------------------------------------------------------- 38abdab8e907300ab3110d0df117eb54e35913c2 compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcErrors.hs | 8 ++++---- compiler/types/TypeRep.hs | 2 +- testsuite/tests/deriving/should_fail/T5287.stderr | 2 +- .../tests/deriving/should_fail/drvfail-functor2.stderr | 2 +- testsuite/tests/gadt/gadt-escape1.stderr | 2 +- testsuite/tests/gadt/gadt13.stderr | 2 +- testsuite/tests/gadt/gadt21.stderr | 2 +- testsuite/tests/gadt/gadt7.stderr | 2 +- .../tests/indexed-types/should_compile/Simple14.stderr | 2 +- .../tests/indexed-types/should_compile/T3208b.stderr | 8 ++++---- testsuite/tests/indexed-types/should_fail/T2664.stderr | 4 ++-- testsuite/tests/indexed-types/should_fail/T3440.stderr | 4 ++-- .../tests/indexed-types/should_fail/T4093a.stderr | 4 ++-- .../tests/indexed-types/should_fail/T4093b.stderr | 6 +++--- testsuite/tests/indexed-types/should_fail/T8155.stderr | 2 +- testsuite/tests/module/mod47.stderr | 2 +- .../WarningWildcardInstantiations.stderr | 5 ++--- .../ExtraConstraintsWildcardNotEnabled.stderr | 2 +- .../InstantiatedNamedWildcardsInConstraints.stderr | 2 +- .../should_fail/WildcardInstantiations.stderr | 2 +- testsuite/tests/polykinds/T7230.stderr | 8 ++++---- testsuite/tests/polykinds/T7438.stderr | 2 +- testsuite/tests/polykinds/T7594.stderr | 2 +- testsuite/tests/polykinds/T8566.stderr | 4 ++-- testsuite/tests/polykinds/T9222.stderr | 2 +- testsuite/tests/typecheck/should_compile/T7220a.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc168.stderr | 2 +- .../should_fail/FailDueToGivenOverlapping.stderr | 2 +- testsuite/tests/typecheck/should_fail/IPFail.stderr | 2 +- testsuite/tests/typecheck/should_fail/T1897a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/T5853.stderr | 18 +++++++++--------- testsuite/tests/typecheck/should_fail/T7279.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7525.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/T7857.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8912.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9109.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail034.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail041.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail042.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/tcfail067.stderr | 8 ++++---- testsuite/tests/typecheck/should_fail/tcfail072.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail080.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail097.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail098.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail102.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail108.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail130.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail142.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail181.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail208.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail211.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail213.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail214.stderr | 2 +- 55 files changed, 85 insertions(+), 86 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 38abdab8e907300ab3110d0df117eb54e35913c2 From git at git.haskell.org Mon Jan 5 17:00:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 17:00:00 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Major patch to add -fwarn-redundant-constraints (d6c8da6) Message-ID: <20150105170000.5B8FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/d6c8da69ed75f0a046bfcf779e71a4ecd2dab106/ghc >--------------------------------------------------------------- commit d6c8da69ed75f0a046bfcf779e71a4ecd2dab106 Author: Simon Peyton Jones Date: Mon Jan 5 13:20:48 2015 +0000 Major patch to add -fwarn-redundant-constraints The idea was promted by Trac #9939, but it was Christmas, so I did some recreational programming that went much further. The idea is to warn when a constraint in a user-supplied context is redundant. Everything is described in detail in Note [Tracking redundant constraints] in TcSimplify. Main changes: * The new ic_status field in an implication, of type ImplicStatus. It replaces ic_insol, and includes information about redundant constraints. * New function TcSimplify.setImplicationStatus sets the ic_status. * TcSigInfo has sig_report_redundant field to say whenther a redundant constraint should be reported; and similarly the FunSigCtxt constructor of UserTypeCtxt * EvBinds has a field eb_is_given, to record whether it is a given or wanted binding. Some consequential chagnes to creating an evidence binding (so that we record whether it is given or wanted). * AbsBinds field abs_ev_binds is now a *list* of TcEvBiinds; see Note [Typechecking plan for instance declarations] in TcInstDcls * Some significant changes to the type checking of instance declarations; Note [Typechecking plan for instance declarations] in TcInstDcls. * I found that TcErrors.relevantBindings was failing to zonk the origin of the constraint it was looking at, and hence failing to find some relevant bindings. Easy to fix, and orthogonal to everything else, but hard to disentangle. Some minor refactorig: * TcMType.newSimpleWanteds moves to Inst, renamed as newWanteds * TcClassDcl and TcInstDcls now have their own code for typechecking a method body, rather than sharing a single function. The shared function (ws TcClassDcl.tcInstanceMethodBody) didn't have much code and the differences were growing confusing. * Add new function TcRnMonad.pushLevelAndCaptureConstraints, and use it * Add new function Bag.catBagMaybes, and use it in TcSimplify >--------------------------------------------------------------- d6c8da69ed75f0a046bfcf779e71a4ecd2dab106 compiler/basicTypes/BasicTypes.hs | 2 + compiler/deSugar/DsArrows.hs | 4 +- compiler/deSugar/DsBinds.hs | 27 +- compiler/deSugar/DsExpr.hs | 2 +- compiler/hsSyn/HsBinds.hs | 9 +- compiler/iface/BuildTyCl.hs | 2 +- compiler/iface/IfaceSyn.hs | 2 +- compiler/main/DynFlags.hs | 7 +- compiler/typecheck/Inst.hs | 18 +- compiler/typecheck/TcBinds.hs | 52 +- compiler/typecheck/TcCanonical.hs | 30 +- compiler/typecheck/TcClassDcl.hs | 139 ++-- compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcErrors.hs | 244 ++++--- compiler/typecheck/TcEvidence.hs | 42 +- compiler/typecheck/TcFlatten.hs | 6 +- compiler/typecheck/TcHsSyn.hs | 31 +- compiler/typecheck/TcInstDcls.hs | 751 +++++++++++++-------- compiler/typecheck/TcInteract.hs | 80 ++- compiler/typecheck/TcMType.hs | 35 +- compiler/typecheck/TcMatches.hs | 2 +- compiler/typecheck/TcPat.hs | 29 +- compiler/typecheck/TcPatSyn.hs | 16 +- compiler/typecheck/TcRnDriver.hs | 5 +- compiler/typecheck/TcRnMonad.hs | 33 +- compiler/typecheck/TcRnTypes.hs | 79 ++- compiler/typecheck/TcRules.hs | 36 +- compiler/typecheck/TcSMonad.hs | 42 +- compiler/typecheck/TcSimplify.hs | 270 +++++++- compiler/typecheck/TcTyClsDecls.hs | 6 +- compiler/typecheck/TcType.hs | 18 +- compiler/typecheck/TcUnify.hs | 37 +- compiler/typecheck/TcValidity.hs | 2 +- compiler/utils/Bag.hs | 15 +- compiler/utils/Util.hs | 2 + docs/users_guide/using.xml | 32 + testsuite/tests/arrows/should_compile/arrowpat.hs | 3 +- testsuite/tests/codeGen/should_compile/T3286.hs | 1 + testsuite/tests/deriving/should_compile/T2856.hs | 1 + testsuite/tests/deriving/should_compile/T4966.hs | 2 + .../tests/deriving/should_compile/T4966.stderr | 4 +- .../tests/deriving/should_compile/deriving-1935.hs | 2 + .../deriving/should_compile/deriving-1935.stderr | 6 +- testsuite/tests/deriving/should_compile/drv001.hs | 2 + testsuite/tests/deriving/should_compile/drv002.hs | 2 + testsuite/tests/deriving/should_compile/drv003.hs | 2 + .../tests/deriving/should_compile/drv003.stderr | 4 +- testsuite/tests/deriving/should_run/T9576.stderr | 2 +- testsuite/tests/gadt/Gadt17_help.hs | 2 +- testsuite/tests/ghci/scripts/T5045.hs | 1 + testsuite/tests/ghci/scripts/T8357.hs | 1 + testsuite/tests/ghci/scripts/T8931.script | 1 + testsuite/tests/ghci/scripts/ghci044.script | 1 + testsuite/tests/ghci/scripts/ghci044.stderr | 6 +- testsuite/tests/ghci/scripts/ghci047.script | 1 + testsuite/tests/ghci/scripts/ghci047.stderr | 4 +- testsuite/tests/haddock/haddock_examples/Test.hs | 1 + .../haddock/haddock_examples/haddock.Test.stderr | 8 +- .../should_compile_flag_haddock/haddockA023.hs | 2 + .../should_compile_flag_haddock/haddockA026.hs | 2 + .../should_compile_flag_haddock/haddockA027.hs | 2 + .../should_compile_noflag_haddock/haddockC026.hs | 2 + .../should_compile_noflag_haddock/haddockC027.hs | 2 + .../tests/indexed-types/should_compile/Class2.hs | 1 + .../tests/indexed-types/should_compile/Gentle.hs | 1 + .../should_compile/InstContextNorm.hs | 1 + .../indexed-types/should_compile/InstEqContext.hs | 1 + .../indexed-types/should_compile/InstEqContext2.hs | 1 + .../indexed-types/should_compile/InstEqContext3.hs | 1 + .../indexed-types/should_compile/NonLinearLHS.hs | 1 + .../tests/indexed-types/should_compile/Rules1.hs | 1 + .../tests/indexed-types/should_compile/Simple24.hs | 1 + .../tests/indexed-types/should_compile/T2448.hs | 1 + .../tests/indexed-types/should_compile/T3023.hs | 3 +- .../indexed-types/should_compile/T3023.stderr | 5 +- .../tests/indexed-types/should_compile/T3484.hs | 3 +- .../tests/indexed-types/should_compile/T4200.hs | 1 + .../tests/indexed-types/should_compile/T4497.hs | 1 + .../tests/indexed-types/should_compile/T4981-V1.hs | 2 + .../tests/indexed-types/should_compile/T4981-V2.hs | 2 + .../tests/indexed-types/should_compile/T4981-V3.hs | 2 + .../tests/indexed-types/should_compile/T5002.hs | 1 + .../tests/indexed-types/should_compile/T9090.hs | 2 + .../tests/indexed-types/should_compile/T9316.hs | 1 + .../tests/indexed-types/should_compile/T9747.hs | 2 + testsuite/tests/indexed-types/should_fail/T2239.hs | 1 + .../tests/indexed-types/should_fail/T3330c.stderr | 4 + testsuite/tests/indexed-types/should_fail/T7862.hs | 1 + .../tests/indexed-types/should_fail/T7862.stderr | 2 +- testsuite/tests/module/mod129.hs | 2 + testsuite/tests/module/mod71.stderr | 9 + testsuite/tests/parser/should_compile/mc15.hs | 2 +- testsuite/tests/parser/should_compile/read002.hs | 2 + testsuite/tests/partial-sigs/should_compile/all.T | 2 +- testsuite/tests/patsyn/should_compile/T8584-2.hs | 2 + testsuite/tests/patsyn/should_compile/T8968-1.hs | 1 + testsuite/tests/patsyn/should_compile/all.T | 4 +- testsuite/tests/patsyn/should_compile/ex-view.hs | 4 +- testsuite/tests/perf/compiler/T3064.hs | 2 + testsuite/tests/perf/compiler/T5030.hs | 6 +- testsuite/tests/polykinds/PolyKinds08.hs | 1 + testsuite/tests/polykinds/T6015a.hs | 1 + testsuite/tests/polykinds/T6020a.hs | 1 + testsuite/tests/polykinds/T6068.hs | 1 + testsuite/tests/polykinds/T7090.hs | 1 + testsuite/tests/polykinds/T7332.hs | 20 +- testsuite/tests/polykinds/T8359.hs | 2 + testsuite/tests/polykinds/T9569.hs | 1 + testsuite/tests/polykinds/T9750.hs | 1 + testsuite/tests/rebindable/T5821.hs | 3 +- testsuite/tests/rebindable/rebindable9.hs | 4 +- testsuite/tests/rename/should_fail/rnfail020.hs | 1 + testsuite/tests/simplCore/should_compile/T3831.hs | 1 + testsuite/tests/simplCore/should_compile/T4398.hs | 1 + .../tests/simplCore/should_compile/T4398.stderr | 2 +- testsuite/tests/simplCore/should_compile/T5329.hs | 1 + testsuite/tests/simplCore/should_compile/T5342.hs | 1 + testsuite/tests/simplCore/should_compile/T5359b.hs | 1 + .../tests/simplCore/should_compile/T5359b.stderr | 2 +- testsuite/tests/simplCore/should_compile/T8848.hs | 3 +- .../tests/simplCore/should_compile/T8848.stderr | 2 +- testsuite/tests/simplCore/should_compile/T8848a.hs | 1 + .../tests/simplCore/should_compile/simpl002.hs | 2 + .../tests/simplCore/should_compile/simpl007.hs | 1 + .../tests/simplCore/should_compile/simpl014.hs | 1 + .../tests/simplCore/should_compile/simpl016.hs | 2 + .../tests/simplCore/should_compile/simpl016.stderr | 2 +- .../tests/simplCore/should_compile/spec003.hs | 2 + testsuite/tests/th/T3100.hs | 1 + testsuite/tests/th/T7021a.hs | 1 + testsuite/tests/th/T8807.hs | 1 + testsuite/tests/th/TH_tf3.hs | 1 + .../typecheck/should_compile/GivenOverlapping.hs | 1 + .../typecheck/should_compile/LoopOfTheDay1.hs | 1 + .../typecheck/should_compile/LoopOfTheDay2.hs | 1 + .../typecheck/should_compile/LoopOfTheDay3.hs | 1 + testsuite/tests/typecheck/should_compile/T1470.hs | 1 + testsuite/tests/typecheck/should_compile/T2683.hs | 1 + testsuite/tests/typecheck/should_compile/T3018.hs | 1 + testsuite/tests/typecheck/should_compile/T3108.hs | 1 + testsuite/tests/typecheck/should_compile/T3692.hs | 1 + testsuite/tests/typecheck/should_compile/T3743.hs | 1 + testsuite/tests/typecheck/should_compile/T4361.hs | 1 + testsuite/tests/typecheck/should_compile/T4401.hs | 1 + testsuite/tests/typecheck/should_compile/T4524.hs | 1 + testsuite/tests/typecheck/should_compile/T4952.hs | 1 + testsuite/tests/typecheck/should_compile/T4969.hs | 2 +- testsuite/tests/typecheck/should_compile/T5514.hs | 1 + testsuite/tests/typecheck/should_compile/T5581.hs | 2 + testsuite/tests/typecheck/should_compile/T5676.hs | 1 + testsuite/tests/typecheck/should_compile/T6055.hs | 1 + testsuite/tests/typecheck/should_compile/T6134.hs | 1 + testsuite/tests/typecheck/should_compile/T7171a.hs | 1 + testsuite/tests/typecheck/should_compile/T7196.hs | 1 + testsuite/tests/typecheck/should_compile/T7220.hs | 1 + testsuite/tests/typecheck/should_compile/T7541.hs | 2 +- testsuite/tests/typecheck/should_compile/T7875.hs | 1 + testsuite/tests/typecheck/should_compile/T7903.hs | 1 + .../typecheck/should_compile/T7903.stderr-ghc | 4 +- .../tests/typecheck/should_compile/Tc170_Aux.hs | 1 + testsuite/tests/typecheck/should_compile/Tc173a.hs | 2 + testsuite/tests/typecheck/should_compile/tc045.hs | 1 + testsuite/tests/typecheck/should_compile/tc051.hs | 2 + .../tests/typecheck/should_compile/tc056.stderr | 6 +- testsuite/tests/typecheck/should_compile/tc058.hs | 2 + testsuite/tests/typecheck/should_compile/tc065.hs | 4 +- testsuite/tests/typecheck/should_compile/tc078.hs | 2 + .../typecheck/should_compile/tc078.stderr-ghc | 4 +- testsuite/tests/typecheck/should_compile/tc079.hs | 2 + testsuite/tests/typecheck/should_compile/tc088.hs | 2 + testsuite/tests/typecheck/should_compile/tc091.hs | 2 + testsuite/tests/typecheck/should_compile/tc092.hs | 1 + testsuite/tests/typecheck/should_compile/tc109.hs | 1 + testsuite/tests/typecheck/should_compile/tc113.hs | 2 + testsuite/tests/typecheck/should_compile/tc115.hs | 1 + .../typecheck/should_compile/tc115.stderr-ghc | 2 +- testsuite/tests/typecheck/should_compile/tc116.hs | 1 + .../typecheck/should_compile/tc116.stderr-ghc | 2 +- testsuite/tests/typecheck/should_compile/tc125.hs | 1 + .../typecheck/should_compile/tc125.stderr-ghc | 10 +- testsuite/tests/typecheck/should_compile/tc126.hs | 1 + .../typecheck/should_compile/tc126.stderr-ghc | 4 +- testsuite/tests/typecheck/should_compile/tc145.hs | 1 + testsuite/tests/typecheck/should_compile/tc152.hs | 1 + testsuite/tests/typecheck/should_compile/tc176.hs | 1 + testsuite/tests/typecheck/should_compile/tc178.hs | 1 + testsuite/tests/typecheck/should_compile/tc180.hs | 1 + testsuite/tests/typecheck/should_compile/tc181.hs | 1 + testsuite/tests/typecheck/should_compile/tc183.hs | 1 + testsuite/tests/typecheck/should_compile/tc187.hs | 1 + testsuite/tests/typecheck/should_compile/tc192.hs | 1 + testsuite/tests/typecheck/should_compile/tc203.hs | 1 + testsuite/tests/typecheck/should_compile/tc204.hs | 3 +- testsuite/tests/typecheck/should_compile/tc206.hs | 1 + testsuite/tests/typecheck/should_compile/tc208.hs | 1 + testsuite/tests/typecheck/should_compile/tc229.hs | 1 + testsuite/tests/typecheck/should_compile/tc230.hs | 1 + testsuite/tests/typecheck/should_compile/tc235.hs | 1 + testsuite/tests/typecheck/should_compile/tc237.hs | 1 + testsuite/tests/typecheck/should_compile/tc239.hs | 1 + testsuite/tests/typecheck/should_compile/twins.hs | 1 + testsuite/tests/typecheck/should_fail/T6161.stderr | 4 +- .../tests/typecheck/should_fail/tcfail017.stderr | 4 +- .../tests/typecheck/should_fail/tcfail020.stderr | 4 +- testsuite/tests/typecheck/should_fail/tcfail071.hs | 2 + testsuite/tests/typecheck/should_fail/tcfail138.hs | 1 + .../tests/typecheck/should_fail/tcfail143.stderr | 4 +- 207 files changed, 1595 insertions(+), 855 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d6c8da69ed75f0a046bfcf779e71a4ecd2dab106 From git at git.haskell.org Mon Jan 5 17:00:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 17:00:03 +0000 (UTC) Subject: [commit: ghc] wip/redundant-constraints: Remove redundant constraints in the compiler itself, found by -fwarn-redundant-constraints (0b3f53f) Message-ID: <20150105170003.2E7273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/redundant-constraints Link : http://ghc.haskell.org/trac/ghc/changeset/0b3f53fb8d86278ead96ea08bedd8990d3256dc4/ghc >--------------------------------------------------------------- commit 0b3f53fb8d86278ead96ea08bedd8990d3256dc4 Author: Simon Peyton Jones Date: Mon Jan 5 16:57:01 2015 +0000 Remove redundant constraints in the compiler itself, found by -fwarn-redundant-constraints >--------------------------------------------------------------- 0b3f53fb8d86278ead96ea08bedd8990d3256dc4 compiler/basicTypes/Name.hs | 3 ++- compiler/cmm/CmmExpr.hs | 8 ++++---- compiler/cmm/Hoopl/Dataflow.hs | 2 +- compiler/coreSyn/TrieMap.hs | 4 ++-- compiler/deSugar/MatchLit.hs | 2 +- compiler/ghci/ByteCodeItbls.hs | 6 ++++-- compiler/ghci/Linker.hs | 2 +- compiler/hsSyn/HsDecls.hs | 8 +++----- compiler/hsSyn/HsExpr.hs | 8 ++++---- compiler/main/CmdLineParser.hs | 2 +- compiler/main/GHC.hs | 10 +++++++--- compiler/main/GhcMonad.hs | 17 +++++++++++++---- compiler/main/InteractiveEval.hs | 2 +- compiler/nativeGen/RegAlloc/Graph/SpillClean.hs | 9 +++------ compiler/nativeGen/RegAlloc/Linear/Main.hs | 4 ++-- compiler/nativeGen/SPARC/Base.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 3 ++- compiler/types/CoAxiom.hs | 2 +- compiler/utils/Binary.hs | 2 +- compiler/utils/GraphColor.hs | 2 +- compiler/utils/GraphOps.hs | 20 ++++++++------------ compiler/utils/GraphPpr.hs | 7 +++---- compiler/utils/Maybes.hs | 4 ++++ compiler/utils/Serialized.hs | 4 ++-- compiler/utils/UniqSet.hs | 2 +- 25 files changed, 73 insertions(+), 62 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0b3f53fb8d86278ead96ea08bedd8990d3256dc4 From git at git.haskell.org Mon Jan 5 21:18:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 21:18:36 +0000 (UTC) Subject: [commit: nofib] master: Remove HTML generation from nofib-analyse, dropping 'html' dependency. (e8f5d80) Message-ID: <20150105211836.37C543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e8f5d80cb41b5267f23835909d06b4317cafd32f/nofib >--------------------------------------------------------------- commit e8f5d80cb41b5267f23835909d06b4317cafd32f Author: Edward Z. Yang Date: Fri Jan 2 14:27:30 2015 -0500 Remove HTML generation from nofib-analyse, dropping 'html' dependency. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- e8f5d80cb41b5267f23835909d06b4317cafd32f nofib-analyse/CmdLine.hs | 3 - nofib-analyse/Main.hs | 188 +---------------------------------------------- 2 files changed, 3 insertions(+), 188 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e8f5d80cb41b5267f23835909d06b4317cafd32f From git at git.haskell.org Mon Jan 5 21:19:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Jan 2015 21:19:48 +0000 (UTC) Subject: [commit: ghc] master: submodule update: remove html dependency from nofib. (696f2cf) Message-ID: <20150105211948.F333E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/696f2cfdea4ab87cc457b141323bb25ab4afe795/ghc >--------------------------------------------------------------- commit 696f2cfdea4ab87cc457b141323bb25ab4afe795 Author: Edward Z. Yang Date: Mon Jan 5 13:20:46 2015 -0800 submodule update: remove html dependency from nofib. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 696f2cfdea4ab87cc457b141323bb25ab4afe795 nofib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nofib b/nofib index 818d889..e8f5d80 160000 --- a/nofib +++ b/nofib @@ -1 +1 @@ -Subproject commit 818d8895242e888e1346b33a90ed9bb45295bf0c +Subproject commit e8f5d80cb41b5267f23835909d06b4317cafd32f From git at git.haskell.org Tue Jan 6 09:41:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 09:41:39 +0000 (UTC) Subject: [commit: packages/hoopl] master: Remove redundant constraints, discovered by -fwarn-redundant-constraints (b38e92f) Message-ID: <20150106094139.AF6C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hoopl On branch : master Link : http://git.haskell.org/packages/hoopl.git/commitdiff/b38e92f67cabfa0d0ed12ac93c2d431f2391de70 >--------------------------------------------------------------- commit b38e92f67cabfa0d0ed12ac93c2d431f2391de70 Author: Simon Peyton Jones Date: Tue Jan 6 09:36:37 2015 +0000 Remove redundant constraints, discovered by -fwarn-redundant-constraints >--------------------------------------------------------------- b38e92f67cabfa0d0ed12ac93c2d431f2391de70 src/Compiler/Hoopl/Dataflow.hs | 2 +- src/Compiler/Hoopl/Graph.hs | 5 ++--- src/Compiler/Hoopl/Show.hs | 4 ++-- 3 files changed, 5 insertions(+), 6 deletions(-) diff --git a/src/Compiler/Hoopl/Dataflow.hs b/src/Compiler/Hoopl/Dataflow.hs index 23254ca..d798f82 100644 --- a/src/Compiler/Hoopl/Dataflow.hs +++ b/src/Compiler/Hoopl/Dataflow.hs @@ -736,7 +736,7 @@ normalizeGraph g = (mapGraphBlocks dropFact g, facts g) exitFacts (JustO (DBlock f b)) = mapSingleton (entryLabel b) f bodyFacts :: LabelMap (DBlock f n C C) -> FactBase f bodyFacts body = mapFoldWithKey f noFacts body - where f :: forall t a x. (NonLocal t) => Label -> DBlock a t C x -> LabelMap a -> LabelMap a + where f :: forall t a x. Label -> DBlock a t C x -> LabelMap a -> LabelMap a f lbl (DBlock f _) fb = mapInsert lbl f fb --- implementation of the constructors (boring) diff --git a/src/Compiler/Hoopl/Graph.hs b/src/Compiler/Hoopl/Graph.hs index 79fbfbb..21ded58 100644 --- a/src/Compiler/Hoopl/Graph.hs +++ b/src/Compiler/Hoopl/Graph.hs @@ -67,7 +67,7 @@ bodyUnion :: forall a . LabelMap a -> LabelMap a -> LabelMap a bodyUnion = mapUnionWithKey nodups where nodups l _ _ = error $ "duplicate blocks with label " ++ show l -bodyList :: NonLocal (block n) => Body' block n -> [(Label,block n C C)] +bodyList :: Body' block n -> [(Label,block n C C)] bodyList body = mapToList body addBlock :: NonLocal thing @@ -308,8 +308,7 @@ preorder_dfs :: NonLocal (block n) => Graph' block n O x -> [block n C C] -- Better to get [A,B,C,D] -graphDfs :: (NonLocal (block n)) - => (LabelMap (block n C C) -> block n O C -> LabelSet -> [block n C C]) +graphDfs :: (LabelMap (block n C C) -> block n O C -> LabelSet -> [block n C C]) -> (Graph' block n O x -> [block n C C]) graphDfs _ (GNil) = [] graphDfs _ (GUnit{}) = [] diff --git a/src/Compiler/Hoopl/Show.hs b/src/Compiler/Hoopl/Show.hs index 877a530..8a8b35f 100644 --- a/src/Compiler/Hoopl/Show.hs +++ b/src/Compiler/Hoopl/Show.hs @@ -20,9 +20,9 @@ import Compiler.Hoopl.Label type Showing n = forall e x . n e x -> String -showGraph :: forall n e x . (NonLocal n) => Showing n -> Graph n e x -> String +showGraph :: forall n e x . Showing n -> Graph n e x -> String showGraph node = g - where g :: (NonLocal n) => Graph n e x -> String + where g :: Graph n e x -> String g GNil = "" g (GUnit block) = b block g (GMany g_entry g_blocks g_exit) = From git at git.haskell.org Tue Jan 6 12:15:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 12:15:35 +0000 (UTC) Subject: [commit: packages/array] master: Remove redundant constraints, discovered by -fwarn-redundant-constraints (c9f2071) Message-ID: <20150106121535.764BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/c9f207182d4c0a4fcfaaabffb5ed759b99913bb5 >--------------------------------------------------------------- commit c9f207182d4c0a4fcfaaabffb5ed759b99913bb5 Author: Simon Peyton Jones Date: Tue Jan 6 12:15:33 2015 +0000 Remove redundant constraints, discovered by -fwarn-redundant-constraints >--------------------------------------------------------------- c9f207182d4c0a4fcfaaabffb5ed759b99913bb5 Data/Array/Base.hs | 14 +++++++------- Data/Array/IO/Internals.hs | 8 ++++---- Data/Array/ST.hs | 8 +++----- 3 files changed, 14 insertions(+), 16 deletions(-) diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs index e00a97d..d632e10 100644 --- a/Data/Array/Base.hs +++ b/Data/Array/Base.hs @@ -1390,7 +1390,7 @@ freeze marr = do -- use the safe array creation function here. return (listArray (l,u) es) -freezeSTUArray :: Ix i => STUArray s i e -> ST s (UArray i e) +freezeSTUArray :: STUArray s i e -> ST s (UArray i e) freezeSTUArray (STUArray l u n marr#) = ST $ \s1# -> case sizeofMutableByteArray# marr# of { n# -> case newByteArray# n# s1# of { (# s2#, marr'# #) -> @@ -1465,7 +1465,7 @@ thaw arr = case bounds arr of | i <- [0 .. n - 1]] return marr -thawSTUArray :: Ix i => UArray i e -> ST s (STUArray s i e) +thawSTUArray :: UArray i e -> ST s (STUArray s i e) thawSTUArray (UArray l u n arr#) = ST $ \s1# -> case sizeofByteArray# arr# of { n# -> case newByteArray# n# s1# of { (# s2#, marr# #) -> @@ -1525,7 +1525,7 @@ unsafeThaw :: (Ix i, IArray a e, MArray b e m) => a i e -> m (b i e) unsafeThaw = thaw {-# INLINE unsafeThawSTUArray #-} -unsafeThawSTUArray :: Ix i => UArray i e -> ST s (STUArray s i e) +unsafeThawSTUArray :: UArray i e -> ST s (STUArray s i e) unsafeThawSTUArray (UArray l u n marr#) = return (STUArray l u n (unsafeCoerce# marr#)) @@ -1535,7 +1535,7 @@ unsafeThawSTUArray (UArray l u n marr#) = #-} {-# INLINE unsafeThawIOArray #-} -unsafeThawIOArray :: Ix ix => Arr.Array ix e -> IO (IOArray ix e) +unsafeThawIOArray :: Arr.Array ix e -> IO (IOArray ix e) unsafeThawIOArray arr = stToIO $ do marr <- ArrST.unsafeThawSTArray arr return (IOArray marr) @@ -1544,7 +1544,7 @@ unsafeThawIOArray arr = stToIO $ do "unsafeThaw/IOArray" unsafeThaw = unsafeThawIOArray #-} -thawIOArray :: Ix ix => Arr.Array ix e -> IO (IOArray ix e) +thawIOArray :: Arr.Array ix e -> IO (IOArray ix e) thawIOArray arr = stToIO $ do marr <- ArrST.thawSTArray arr return (IOArray marr) @@ -1553,7 +1553,7 @@ thawIOArray arr = stToIO $ do "thaw/IOArray" thaw = thawIOArray #-} -freezeIOArray :: Ix ix => IOArray ix e -> IO (Arr.Array ix e) +freezeIOArray :: IOArray ix e -> IO (Arr.Array ix e) freezeIOArray (IOArray marr) = stToIO (ArrST.freezeSTArray marr) {-# RULES @@ -1561,7 +1561,7 @@ freezeIOArray (IOArray marr) = stToIO (ArrST.freezeSTArray marr) #-} {-# INLINE unsafeFreezeIOArray #-} -unsafeFreezeIOArray :: Ix ix => IOArray ix e -> IO (Arr.Array ix e) +unsafeFreezeIOArray :: IOArray ix e -> IO (Arr.Array ix e) unsafeFreezeIOArray (IOArray marr) = stToIO (ArrST.unsafeFreezeSTArray marr) {-# RULES diff --git a/Data/Array/IO/Internals.hs b/Data/Array/IO/Internals.hs index 1a015d9..6c91d7c 100644 --- a/Data/Array/IO/Internals.hs +++ b/Data/Array/IO/Internals.hs @@ -375,7 +375,7 @@ castIOUArray (IOUArray marr) = stToIO $ do return (IOUArray marr') {-# INLINE unsafeThawIOUArray #-} -unsafeThawIOUArray :: Ix ix => UArray ix e -> IO (IOUArray ix e) +unsafeThawIOUArray :: UArray ix e -> IO (IOUArray ix e) unsafeThawIOUArray arr = stToIO $ do marr <- unsafeThawSTUArray arr return (IOUArray marr) @@ -384,7 +384,7 @@ unsafeThawIOUArray arr = stToIO $ do "unsafeThaw/IOUArray" unsafeThaw = unsafeThawIOUArray #-} -thawIOUArray :: Ix ix => UArray ix e -> IO (IOUArray ix e) +thawIOUArray :: UArray ix e -> IO (IOUArray ix e) thawIOUArray arr = stToIO $ do marr <- thawSTUArray arr return (IOUArray marr) @@ -394,14 +394,14 @@ thawIOUArray arr = stToIO $ do #-} {-# INLINE unsafeFreezeIOUArray #-} -unsafeFreezeIOUArray :: Ix ix => IOUArray ix e -> IO (UArray ix e) +unsafeFreezeIOUArray :: IOUArray ix e -> IO (UArray ix e) unsafeFreezeIOUArray (IOUArray marr) = stToIO (unsafeFreezeSTUArray marr) {-# RULES "unsafeFreeze/IOUArray" unsafeFreeze = unsafeFreezeIOUArray #-} -freezeIOUArray :: Ix ix => IOUArray ix e -> IO (UArray ix e) +freezeIOUArray :: IOUArray ix e -> IO (UArray ix e) freezeIOUArray (IOUArray marr) = stToIO (freezeSTUArray marr) {-# RULES diff --git a/Data/Array/ST.hs b/Data/Array/ST.hs index 29bfafb..31e1ed0 100644 --- a/Data/Array/ST.hs +++ b/Data/Array/ST.hs @@ -37,8 +37,7 @@ import GHC.Arr ( STArray, Array, unsafeFreezeSTArray ) -- the array before returning it - it uses 'unsafeFreeze' internally, but -- this wrapper is a safe interface to that function. -- -runSTArray :: (Ix i) - => (forall s . ST s (STArray s i e)) +runSTArray :: (forall s . ST s (STArray s i e)) -> Array i e runSTArray st = runST (st >>= unsafeFreezeSTArray) @@ -48,9 +47,8 @@ runSTArray st = runST (st >>= unsafeFreezeSTArray) -- 'unsafeFreeze' internally, but this wrapper is a safe interface to -- that function. -- -runSTUArray :: (Ix i) - => (forall s . ST s (STUArray s i e)) - -> UArray i e +runSTUArray :: (forall s . ST s (STUArray s i e)) + -> UArray i e runSTUArray st = runST (st >>= unsafeFreezeSTUArray) From git at git.haskell.org Tue Jan 6 13:01:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 13:01:23 +0000 (UTC) Subject: [commit: ghc] master: Make the location in TcLclEnv and CtLoc into a RealSrcSpan (d2b6e76) Message-ID: <20150106130123.CB6DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d2b6e7671e823fce0c0fbb2bed739fa948a23219/ghc >--------------------------------------------------------------- commit d2b6e7671e823fce0c0fbb2bed739fa948a23219 Author: Simon Peyton Jones Date: Tue Jan 6 12:28:37 2015 +0000 Make the location in TcLclEnv and CtLoc into a RealSrcSpan Previously it was a SrcSpan, which can be an UnhelpulSrcSpan, but actually for TcLclEnv and CtLoc we always know it is a real source location, and it's good to make the types reflect that fact. There is a continuing slight awkwardness (not new with this patch) about what "file name" to use for GHCi code. Current we say "" which seems just about OK. >--------------------------------------------------------------- d2b6e7671e823fce0c0fbb2bed739fa948a23219 compiler/ghci/RtClosureInspect.hs | 4 +-- compiler/main/HscMain.hs | 9 ++--- compiler/main/HscTypes.hs | 9 +++-- compiler/main/InteractiveEval.hs | 6 ++-- compiler/typecheck/TcErrors.hs | 4 +-- compiler/typecheck/TcRnDriver.hs | 41 ++++++++++++++-------- compiler/typecheck/TcRnMonad.hs | 33 ++++++++++------- compiler/typecheck/TcRnTypes.hs | 8 ++--- .../tests/ghci.debugger/scripts/break019.stderr | 2 +- testsuite/tests/ghci/scripts/T7894.stderr | 2 +- testsuite/tests/ghci/scripts/T9140.stdout | 2 +- testsuite/tests/ghci/scripts/ghci034.stderr | 2 +- 12 files changed, 69 insertions(+), 53 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d2b6e7671e823fce0c0fbb2bed739fa948a23219 From git at git.haskell.org Tue Jan 6 13:01:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 13:01:26 +0000 (UTC) Subject: [commit: ghc] master: Updaete perf numbers for 32-bit machines (f17992a) Message-ID: <20150106130126.5CA1F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f17992a4954ac14cc6a3fe6a61ec6544a098da93/ghc >--------------------------------------------------------------- commit f17992a4954ac14cc6a3fe6a61ec6544a098da93 Author: Simon Peyton Jones Date: Tue Jan 6 12:29:03 2015 +0000 Updaete perf numbers for 32-bit machines >--------------------------------------------------------------- f17992a4954ac14cc6a3fe6a61ec6544a098da93 testsuite/tests/perf/compiler/all.T | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index fab62c0..2d96497 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -120,13 +120,15 @@ else: test('T3294', [ compiler_stats_num_field('max_bytes_used', # Note [residency] - [(wordsize(32), 19882188, 15), + [(wordsize(32), 26525384, 15), # 17725476 (x86/OS X) # 14593500 (Windows) # 2013-02-10 20651576 (x86/Windows) # 2013-02-10 20772984 (x86/OSX) # 2013-11-13 24009436 (x86/Windows, 64bit machine) # 2014-04-24 19882188 (x86/Windows, 64bit machine) + # 2014-12-22 26525384 (x86/Windows) Increase due to silent superclasses? + (wordsize(64), 40000000, 15)]), # prev: 25753192 (amd64/Linux) # 29/08/2012: 37724352 (amd64/Linux) @@ -235,10 +237,11 @@ test('T4801', test('T3064', [# expect_broken( 3064 ), compiler_stats_num_field('peak_megabytes_allocated',# Note [residency] - [(wordsize(32), 23, 20), + [(wordsize(32), 16, 20), # expected value: 14 (x86/Linux 28-06-2012): # 2013-11-13: 18 (x86/Windows, 64bit machine) # 2014-01-22: 23 (x86/Linux) + # 2014-12-22: 23 (x86/Linux) death to silent superclasses (wordsize(64), 27, 20)]), # (amd64/Linux): 18 # (amd64/Linux) 2012-02-07: 26 @@ -253,12 +256,13 @@ test('T3064', # (amd64/Linux) 2014-12-22: 27: death to silent superclasses compiler_stats_num_field('bytes allocated', - [(wordsize(32), 188697088, 10), + [(wordsize(32), 122836340, 10), # 2011-06-28: 56380288 (x86/Linux) # 2012-10-30: 111189536 (x86/Windows) # 2013-11-13: 146626504 (x86/Windows, 64bit machine) # 2014-01-22: 162457940 (x86/Linux) # 2014-12-01: 162457940 (Windows) + # 2014-12-22: 122836340 (Windows) Death to silent superclasses (wordsize(64), 243670824, 5)]), # (amd64/Linux) (28/06/2011): 73259544 @@ -375,12 +379,13 @@ test('T783', [ only_ways(['normal']), # no optimisation for this one # expected value: 175,569,928 (x86/Linux) compiler_stats_num_field('bytes allocated', - [(wordsize(32), 223377364, 5), + [(wordsize(32), 235002220, 5), # 2012-10-08: 226907420 (x86/Linux) # 2013-02-10: 329202116 (x86/Windows) # 2013-02-10: 338465200 (x86/OSX) # 2014-04-04: 319179104 (x86 Windows, 64 bit machine) - # 2014-09-03: 223377364 (Windows, better specialisation, raft of core-to-core optimisations) + # 2014-09-03: 223377364 (Windows) better specialisation, raft of core-to-core optimisations + # 2014-12-22: 235002220 (Windows) not sure why (wordsize(64), 441932632, 10)]), # prev: 349263216 (amd64/Linux) @@ -543,6 +548,7 @@ test('T9675', # 2014-10-13 26570896 seq the DmdEnv in seqDmdType as well # 2014-10-13 18582472 different machines giving different results.. # 2014-10-13 22220552 use the mean + (wordsize(32), 11220552, 25) ]), compiler_stats_num_field('peak_megabytes_allocated', [(wordsize(64), 53, 15), @@ -550,6 +556,7 @@ test('T9675', # 2014-10-13 58 seq the DmdEnv in seqDmdType as well # 2014-10-13 49 different machines giving different results... # 2014-10-13 53 use the mean + (wordsize(32), 25, 15) ]), compiler_stats_num_field('bytes allocated', [(wordsize(64), 544489040, 10) @@ -563,10 +570,11 @@ test('T9675', test('T9872a', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 2680733672, 5) + [(wordsize(64), 2680733672, 5), # 2014-12-10 5521332656 Initally created # 2014-12-16 5848657456 Flattener parameterized over roles # 2014-12-18 2680733672 Reduce type families even more eagerly + (wordsize(32), 1400000000, 5) ]), ], compile_fail, @@ -575,10 +583,11 @@ test('T9872a', test('T9872b', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 3480212048, 5) + [(wordsize(64), 3480212048, 5), # 2014-12-10 6483306280 Initally created # 2014-12-16 6892251912 Flattener parameterized over roles # 2014-12-18 3480212048 Reduce type families even more eagerly + (wordsize(32), 1700000000, 5) ]), ], compile_fail, @@ -586,10 +595,11 @@ test('T9872b', test('T9872c', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 2963554096, 5) + [(wordsize(64), 2963554096, 5), # 2014-12-10 5495850096 Initally created # 2014-12-16 5842024784 Flattener parameterized over roles # 2014-12-18 2963554096 Reduce type families even more eagerly + (wordsize(32), 1500000000, 5) ]), ], compile_fail, @@ -597,9 +607,10 @@ test('T9872c', test('T9872d', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 739189056, 5) + [(wordsize(64), 739189056, 5), # 2014-12-18 796071864 Initally created # 2014-12-18 739189056 Reduce type families even more eagerly + (wordsize(32), 353644844, 5) ]), ], compile, From git at git.haskell.org Tue Jan 6 13:39:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 13:39:36 +0000 (UTC) Subject: [commit: packages/array] master: Remove unnecessary import (e69fab7) Message-ID: <20150106133936.25CF83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/e69fab76b5b15d7e7f413edb936faab30d05b8a0 >--------------------------------------------------------------- commit e69fab76b5b15d7e7f413edb936faab30d05b8a0 Author: Simon Peyton Jones Date: Tue Jan 6 13:40:57 2015 +0000 Remove unnecessary import >--------------------------------------------------------------- e69fab76b5b15d7e7f413edb936faab30d05b8a0 Data/Array/IO/Internals.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/Data/Array/IO/Internals.hs b/Data/Array/IO/Internals.hs index 6c91d7c..a7883f3 100644 --- a/Data/Array/IO/Internals.hs +++ b/Data/Array/IO/Internals.hs @@ -34,7 +34,6 @@ import Control.Monad.ST ( RealWorld, stToIO ) import Foreign.Ptr ( Ptr, FunPtr ) import Foreign.StablePtr ( StablePtr ) -import Data.Ix import Data.Array.Base import GHC.IOArray (IOArray(..)) From git at git.haskell.org Tue Jan 6 15:10:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 15:10:04 +0000 (UTC) Subject: [commit: ghc] master: Modify a couple of error messages slightly (00e1fc1) Message-ID: <20150106151004.915D43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/00e1fc1b18e1b5aa5db18bee9f9adc67435f00b0/ghc >--------------------------------------------------------------- commit 00e1fc1b18e1b5aa5db18bee9f9adc67435f00b0 Author: Simon Peyton Jones Date: Sat Jan 3 23:27:21 2015 +0000 Modify a couple of error messages slightly In particular In the type signature for: f :: Int -> Int I added the colon Also reword the "maybe you haven't applied a function to enough arguments?" suggestion to make grammatical sense. These tiny changes affect a lot of error messages. >--------------------------------------------------------------- 00e1fc1b18e1b5aa5db18bee9f9adc67435f00b0 compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 68 +++++++++++++--------- .../tests/annotations/should_fail/annfail08.stderr | 4 +- testsuite/tests/arrows/should_fail/T5380.stderr | 8 +-- .../tests/deriving/should_fail/drvfail007.stderr | 2 +- testsuite/tests/driver/T2182.stderr | 8 +-- testsuite/tests/gadt/T3169.stderr | 4 +- testsuite/tests/gadt/T3651.stderr | 6 +- testsuite/tests/gadt/T7293.stderr | 3 +- testsuite/tests/gadt/T7294.stderr | 3 +- testsuite/tests/gadt/T7558.stderr | 4 +- testsuite/tests/gadt/gadt-escape1.stderr | 3 +- testsuite/tests/gadt/gadt13.stderr | 3 +- testsuite/tests/gadt/gadt21.stderr | 2 +- testsuite/tests/gadt/gadt7.stderr | 3 +- testsuite/tests/gadt/rw.stderr | 4 +- .../tests/ghci.debugger/scripts/break003.stderr | 2 +- testsuite/tests/ghci/scripts/Defer02.stderr | 15 +++-- testsuite/tests/ghci/scripts/T2182ghci.stderr | 10 ++-- .../should_compile/PushedInAsGivens.stderr | 2 +- .../indexed-types/should_compile/Simple14.stderr | 4 +- .../indexed-types/should_compile/T3208b.stderr | 8 +-- .../indexed-types/should_fail/GADTwrong1.stderr | 5 +- .../indexed-types/should_fail/Overlap6.stderr | 2 +- .../indexed-types/should_fail/SimpleFail5a.stderr | 2 +- .../tests/indexed-types/should_fail/T2664.stderr | 6 +- .../tests/indexed-types/should_fail/T3330a.stderr | 6 +- .../tests/indexed-types/should_fail/T3440.stderr | 6 +- .../tests/indexed-types/should_fail/T4093a.stderr | 2 +- .../tests/indexed-types/should_fail/T4093b.stderr | 16 ++--- .../tests/indexed-types/should_fail/T4174.stderr | 8 +-- .../tests/indexed-types/should_fail/T4272.stderr | 2 +- .../tests/indexed-types/should_fail/T7194.stderr | 2 +- .../tests/indexed-types/should_fail/T7786.stderr | 3 +- .../tests/indexed-types/should_fail/T9662.stderr | 36 ++++++------ testsuite/tests/parser/should_fail/T7848.stderr | 2 +- .../should_fail/AnnotatedConstraint.stderr | 2 +- .../should_fail/NamedWildcardsNotEnabled.stderr | 4 +- testsuite/tests/polykinds/T7230.stderr | 10 ++-- testsuite/tests/polykinds/T7438.stderr | 2 +- testsuite/tests/polykinds/T8566.stderr | 2 +- testsuite/tests/rebindable/rebindable6.stderr | 6 +- .../tests/typecheck/should_compile/FD1.stderr | 2 +- .../tests/typecheck/should_compile/FD2.stderr | 8 +-- .../tests/typecheck/should_compile/FD3.stderr | 2 +- .../tests/typecheck/should_compile/T7220a.stderr | 4 +- .../tests/typecheck/should_compile/T9834.stderr | 20 +++---- .../tests/typecheck/should_compile/tc141.stderr | 2 +- .../typecheck/should_fail/FDsFromGivens.stderr | 2 +- .../should_fail/FailDueToGivenOverlapping.stderr | 2 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 3 +- .../tests/typecheck/should_fail/IPFail.stderr | 2 +- testsuite/tests/typecheck/should_fail/T1899.stderr | 2 +- testsuite/tests/typecheck/should_fail/T2714.stderr | 4 +- .../tests/typecheck/should_fail/T2846b.stderr | 2 +- testsuite/tests/typecheck/should_fail/T3592.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5236.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 10 ++-- testsuite/tests/typecheck/should_fail/T7453.stderr | 6 +- .../tests/typecheck/should_fail/T7748a.stderr | 2 +- .../tests/typecheck/should_fail/T8392a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8450.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9109.stderr | 3 +- .../should_fail/TcStaticPointersFail02.stderr | 4 +- testsuite/tests/typecheck/should_fail/mc22.stderr | 0 .../tests/typecheck/should_fail/tcfail034.stderr | 4 +- .../tests/typecheck/should_fail/tcfail065.stderr | 2 +- .../tests/typecheck/should_fail/tcfail067.stderr | 22 +++---- .../tests/typecheck/should_fail/tcfail068.stderr | 34 +++++------ .../tests/typecheck/should_fail/tcfail072.stderr | 4 +- .../tests/typecheck/should_fail/tcfail097.stderr | 2 +- .../tests/typecheck/should_fail/tcfail099.stderr | 3 +- .../tests/typecheck/should_fail/tcfail102.stderr | 4 +- .../tests/typecheck/should_fail/tcfail103.stderr | 4 +- .../tests/typecheck/should_fail/tcfail125.stderr | 2 +- .../tests/typecheck/should_fail/tcfail131.stderr | 2 +- .../tests/typecheck/should_fail/tcfail142.stderr | 2 +- .../tests/typecheck/should_fail/tcfail153.stderr | 2 +- .../tests/typecheck/should_fail/tcfail167.stderr | 3 +- .../tests/typecheck/should_fail/tcfail171.stderr | 2 +- .../tests/typecheck/should_fail/tcfail174.stderr | 2 +- .../tests/typecheck/should_fail/tcfail175.stderr | 2 +- .../tests/typecheck/should_fail/tcfail179.stderr | 4 +- .../tests/typecheck/should_fail/tcfail201.stderr | 2 +- .../tests/typecheck/should_fail/tcfail206.stderr | 4 +- .../tests/typecheck/should_fail/tcfail208.stderr | 4 +- 86 files changed, 245 insertions(+), 247 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 00e1fc1b18e1b5aa5db18bee9f9adc67435f00b0 From git at git.haskell.org Tue Jan 6 15:10:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 15:10:07 +0000 (UTC) Subject: [commit: ghc] master: Replace fixVarSet with transCloVarSet (8e2ed2c) Message-ID: <20150106151007.2B7A73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e2ed2c7b1eab2468a061af61fe69efbe959b091/ghc >--------------------------------------------------------------- commit 8e2ed2c7b1eab2468a061af61fe69efbe959b091 Author: Simon Peyton Jones Date: Sat Jan 3 23:36:09 2015 +0000 Replace fixVarSet with transCloVarSet I think the new implementation is a bit more efficient, because it uses a work-list, rather than iterating over the entire set every time >--------------------------------------------------------------- 8e2ed2c7b1eab2468a061af61fe69efbe959b091 compiler/basicTypes/VarSet.hs | 29 ++++++++++++++++++++++------- compiler/typecheck/TcSimplify.hs | 31 +++++++++++++++++-------------- 2 files changed, 39 insertions(+), 21 deletions(-) diff --git a/compiler/basicTypes/VarSet.hs b/compiler/basicTypes/VarSet.hs index c134124..6c920ba 100644 --- a/compiler/basicTypes/VarSet.hs +++ b/compiler/basicTypes/VarSet.hs @@ -16,7 +16,8 @@ module VarSet ( unionVarSet, unionVarSets, mapUnionVarSet, intersectVarSet, intersectsVarSet, disjointVarSet, isEmptyVarSet, delVarSet, delVarSetList, delVarSetByKey, - minusVarSet, foldVarSet, filterVarSet, fixVarSet, + minusVarSet, foldVarSet, filterVarSet, + transCloVarSet, lookupVarSet, mapVarSet, sizeVarSet, seqVarSet, elemVarSetByKey, partitionVarSet ) where @@ -69,7 +70,6 @@ extendVarSet_C :: (Var->Var->Var) -> VarSet -> Var -> VarSet delVarSetByKey :: VarSet -> Unique -> VarSet elemVarSetByKey :: Unique -> VarSet -> Bool -fixVarSet :: (VarSet -> VarSet) -> VarSet -> VarSet partitionVarSet :: (Var -> Bool) -> VarSet -> (VarSet, VarSet) emptyVarSet = emptyUniqSet @@ -110,11 +110,26 @@ intersectsVarSet s1 s2 = not (s1 `disjointVarSet` s2) disjointVarSet s1 s2 = isEmptyVarSet (s1 `intersectVarSet` s2) subVarSet s1 s2 = isEmptyVarSet (s1 `minusVarSet` s2) --- Iterate f to a fixpoint -fixVarSet f s | new_s `subVarSet` s = s - | otherwise = fixVarSet f new_s - where - new_s = f s +transCloVarSet :: (VarSet -> VarSet) + -- Map some variables in the set to + -- *extra* variables that should be in it + -> VarSet -> VarSet +-- (transCloVarSet f s) repeatedly applies f to the set s, adding any +-- new variables to s that it finds thereby, until it reaches a fixed +-- point. The actual algorithm is a bit more efficient. +transCloVarSet fn seeds + = go seeds seeds + where + go :: VarSet -- Accumulating result + -> VarSet -- Work-list; un-processed subset of accumulating result + -> VarSet + -- Specification: go acc vs = acc `union` transClo fn vs + + go acc candidates + | isEmptyVarSet new_vs = acc + | otherwise = go (acc `unionVarSet` new_vs) new_vs + where + new_vs = fn candidates `minusVarSet` acc seqVarSet :: VarSet -> () seqVarSet s = sizeVarSet s `seq` () diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 01da61f..0c9b093 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -468,17 +468,18 @@ quantifyPred qtvs pred growThetaTyVars :: ThetaType -> TyVarSet -> TyVarSet -- See Note [Growing the tau-tvs using constraints] growThetaTyVars theta tvs - | null theta = tvs - | isEmptyVarSet seed_tvs = tvs - | otherwise = fixVarSet mk_next seed_tvs + | null theta = tvs + | otherwise = transCloVarSet mk_next seed_tvs where seed_tvs = tvs `unionVarSet` tyVarsOfTypes ips (ips, non_ips) = partition isIPPred theta -- See note [Inheriting implicit parameters] - mk_next tvs = foldr grow_one tvs non_ips - grow_one pred tvs - | pred_tvs `intersectsVarSet` tvs = tvs `unionVarSet` pred_tvs - | otherwise = tvs + + mk_next :: VarSet -> VarSet -- Maps current set to newly-grown ones + mk_next so_far = foldr (grow_one so_far) emptyVarSet non_ips + grow_one so_far pred tvs + | pred_tvs `intersectsVarSet` so_far = tvs `unionVarSet` pred_tvs + | otherwise = tvs where pred_tvs = tyVarsOfType pred @@ -990,14 +991,16 @@ approximateWC wc = filterBag is_floatable simples `unionBags` do_bag (float_implic new_trapping_tvs) implics where - new_trapping_tvs = fixVarSet grow trapping_tvs is_floatable ct = tyVarsOfCt ct `disjointVarSet` new_trapping_tvs - - grow tvs = foldrBag grow_one tvs simples - grow_one ct tvs | ct_tvs `intersectsVarSet` tvs = tvs `unionVarSet` ct_tvs - | otherwise = tvs - where - ct_tvs = tyVarsOfCt ct + new_trapping_tvs = transCloVarSet grow trapping_tvs + + grow :: VarSet -> VarSet -- Maps current trapped tyvars to newly-trapped ones + grow so_far = foldrBag (grow_one so_far) emptyVarSet simples + grow_one so_far ct tvs + | ct_tvs `intersectsVarSet` so_far = tvs `unionVarSet` ct_tvs + | otherwise = tvs + where + ct_tvs = tyVarsOfCt ct float_implic :: TcTyVarSet -> Implication -> Cts float_implic trapping_tvs imp From git at git.haskell.org Tue Jan 6 15:10:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 15:10:09 +0000 (UTC) Subject: [commit: ghc] master: Always generalise a partial type signature (28299d6) Message-ID: <20150106151009.BD1073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/28299d6827b334f5337bf5931124abc1e534f33f/ghc >--------------------------------------------------------------- commit 28299d6827b334f5337bf5931124abc1e534f33f Author: Simon Peyton Jones Date: Mon Jan 5 10:39:46 2015 +0000 Always generalise a partial type signature This fixes an ASSERT failure in TcBinds. The problem was that we were generating NoGen plan for a function with a partial type signature, and that led to confusion and lost invariants. See Note [Partial type signatures and generalisation] in TcBinds >--------------------------------------------------------------- 28299d6827b334f5337bf5931124abc1e534f33f compiler/typecheck/TcBinds.hs | 56 ++++++++++++++++++++++++++++++++----------- 1 file changed, 42 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index 842ccfa..b4bb65d 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -769,6 +769,29 @@ completeTheta inferred_theta , typeSigCtxt (idName poly_id) sig ] {- +Note [Partial type signatures and generalisation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When we have a partial type signature, like + f :: _ -> Int +then we *always* use the InferGen plan, and hence tcPolyInfer. +We do this even for a local binding with -XMonoLocalBinds. +Reasons: + * The TcSigInfo for 'f' has a unification variable for the '_', + whose TcLevel is one level deeper than the current level. + (See pushTcLevelM in tcTySig.) But NoGen doesn't increase + the TcLevel like InferGen, so we lose the level invariant. + + * The signature might be f :: forall a. _ -> a + so it really is polymorphic. It's not clear what it would + mean to use NoGen on this, and indeed the ASSERT in tcLhs, + in the (Just sig) case, checks that if there is a signature + then we are using LetLclBndr, and hence a nested AbsBinds with + increased TcLevel + +It might be possible to fix these difficulties somehow, but there +doesn't seem much point. Indeed, adding a partial type signature is a +way to get per-binding inferred generalisation. + Note [Validity of inferred types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We need to check inferred type for validity, in case it uses language @@ -1196,14 +1219,17 @@ tcLhs :: TcSigFun -> LetBndrSpec -> HsBind Name -> TcM TcMonoBind tcLhs sig_fn no_gen (FunBind { fun_id = L nm_loc name, fun_infix = inf, fun_matches = matches }) | Just sig <- sig_fn name = ASSERT2( case no_gen of { LetLclBndr -> True; LetGblBndr {} -> False } - , ppr name ) -- { f :: ty; f x = e } is always done via CheckGen - -- which gives rise to LetLclBndr. It wouldn't make - -- sense to have a *polymorphic* function Id at this point + , ppr name ) + -- { f :: ty; f x = e } is always done via CheckGen (full signature) + -- or InferGen (partial signature) + -- see Note [Partial type signatures and generalisation] + -- Both InferGen and CheckGen gives rise to LetLclBndr do { mono_name <- newLocalName name ; let mono_id = mkLocalId mono_name (sig_tau sig) ; addErrCtxt (typeSigCtxt name sig) $ emitWildcardHoleConstraints (sig_nwcs sig) ; return (TcFunBind (name, Just sig, mono_id) nm_loc inf matches) } + | otherwise = do { mono_ty <- newFlexiTyVarTy openTypeKind ; mono_id <- newNoSigLetBndr no_gen name mono_ty @@ -1455,12 +1481,15 @@ decideGeneralisationPlan :: DynFlags -> TcTypeEnv -> [Name] -> [LHsBind Name] -> TcSigFun -> GeneralisationPlan decideGeneralisationPlan dflags type_env bndr_names lbinds sig_fn - | strict_pat_binds = NoGen - | Just (lbind, sig) <- one_funbind_with_sig lbinds = CheckGen lbind sig - | mono_local_binds = NoGen - | otherwise = InferGen mono_restriction closed_flag - + | strict_pat_binds = NoGen + | Just (lbind, sig) <- one_funbind_with_sig = if isPartialSig sig + -- See Note [Partial type signatures and generalisation] + then infer_plan + else CheckGen lbind sig + | mono_local_binds = NoGen + | otherwise = infer_plan where + infer_plan = InferGen mono_restriction closed_flag bndr_set = mkNameSet bndr_names binds = map unLoc lbinds @@ -1503,12 +1532,11 @@ decideGeneralisationPlan dflags type_env bndr_names lbinds sig_fn -- With OutsideIn, all nested bindings are monomorphic -- except a single function binding with a signature - one_funbind_with_sig [lbind@(L _ (FunBind { fun_id = v }))] - = case sig_fn (unLoc v) of - Nothing -> Nothing - Just sig | isPartialSig sig -> Nothing - Just sig | otherwise -> Just (lbind, sig) - one_funbind_with_sig _ + one_funbind_with_sig + | [lbind@(L _ (FunBind { fun_id = v }))] <- lbinds + , Just sig <- sig_fn (unLoc v) + = Just (lbind, sig) + | otherwise = Nothing -- The Haskell 98 monomorphism resetriction From git at git.haskell.org Tue Jan 6 15:10:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 15:10:12 +0000 (UTC) Subject: [commit: ghc] master: Use a less fragile method for defaulting (d4f460f) Message-ID: <20150106151012.5682C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d4f460feeb263f794774bf2fc330a48bde4ea81c/ghc >--------------------------------------------------------------- commit d4f460feeb263f794774bf2fc330a48bde4ea81c Author: Simon Peyton Jones Date: Mon Jan 5 10:53:37 2015 +0000 Use a less fragile method for defaulting When doing top-level defaulting, in TcSimplify.applyDefaultingRules, we were temporarily making a unification variable equal to the default type (Integer, say, or Float), as a 'given', and trying to solve. But this relied on the unification variable being untouchable, which seems complicated. It's much simpler just to generate a new set of constraints to solve, using newWantedEvVarNC in disambigGroup. (I tripped over an ASSERT failure, and this solved it in a robust way.) >--------------------------------------------------------------- d4f460feeb263f794774bf2fc330a48bde4ea81c compiler/typecheck/TcSimplify.hs | 82 ++++++++++++++++++++++++---------------- 1 file changed, 50 insertions(+), 32 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 0c9b093..68978df 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -20,6 +20,7 @@ import TcSMonad as TcS import TcInteract import Kind ( isKind, isSubKind, defaultKind_maybe ) import Inst +import Unify ( tcMatchTy ) import Type ( classifyPredType, isIPClass, PredTree(..) , getClassPredTys_maybe, EqRel(..) ) import TyCon ( isTypeFamilyTyCon ) @@ -101,7 +102,7 @@ simpl_top wanteds | isEmptyWC wc = return wc | otherwise -- See Note [When to do type-class defaulting] - = do { something_happened <- applyDefaultingRules (approximateWC wc) + = do { something_happened <- applyDefaultingRules wc -- See Note [Top-level Defaulting Plan] ; if something_happened then do { wc_residual <- nestTcS (solveWantedsAndDrop wc) @@ -1337,13 +1338,13 @@ to beta[1], and that means the (a ~ beta[1]) will be stuck, as it should be. ********************************************************************************* -} -applyDefaultingRules :: Cts -> TcS Bool +applyDefaultingRules :: WantedConstraints -> TcS Bool -- True <=> I did some defaulting, reflected in ty_binds -- Return some extra derived equalities, which express the -- type-class default choice. applyDefaultingRules wanteds - | isEmptyBag wanteds + | isEmptyWC wanteds = return False | otherwise = do { traceTcS "applyDefaultingRules { " $ @@ -1351,8 +1352,10 @@ applyDefaultingRules wanteds ; info@(default_tys, _) <- getDefaultInfo ; let groups = findDefaultableGroups info wanteds + ; traceTcS "findDefaultableGroups" $ vcat [ text "groups=" <+> ppr groups , text "info=" <+> ppr info ] + ; something_happeneds <- mapM (disambigGroup default_tys) groups ; traceTcS "applyDefaultingRules }" (ppr something_happeneds) @@ -1361,26 +1364,33 @@ applyDefaultingRules wanteds findDefaultableGroups :: ( [Type] - , (Bool,Bool) ) -- (Overloaded strings, extended default rules) - -> Cts -- Unsolved (wanted or derived) - -> [[(Ct,Class,TcTyVar)]] + , (Bool,Bool) ) -- (Overloaded strings, extended default rules) + -> WantedConstraints -- Unsolved (wanted or derived) + -> [(TyVar, [Ct])] findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds - | null default_tys = [] - | otherwise = defaultable_groups + | null default_tys + = [] + | otherwise + = [ (tv, map fstOf3 group) + | group@((_,_,tv):_) <- unary_groups + , defaultable_tyvar tv + , defaultable_classes (map sndOf3 group) ] where - defaultable_groups = filter is_defaultable_group groups - groups = equivClasses cmp_tv unaries - unaries :: [(Ct, Class, TcTyVar)] -- (C tv) constraints - non_unaries :: [Ct] -- and *other* constraints + simples = approximateWC wanteds + (unaries, non_unaries) = partitionWith find_unary (bagToList simples) + unary_groups = equivClasses cmp_tv unaries + + unary_groups :: [[(Ct, Class, TcTyVar)]] -- (C tv) constraints + unaries :: [(Ct, Class, TcTyVar)] -- (C tv) constraints + non_unaries :: [Ct] -- and *other* constraints - (unaries, non_unaries) = partitionWith find_unary (bagToList wanteds) -- Finds unary type-class constraints -- But take account of polykinded classes like Typeable, -- which may look like (Typeable * (a:*)) (Trac #8931) find_unary cc | Just (cls,tys) <- getClassPredTys_maybe (ctPred cc) - , Just (kinds, ty) <- snocView tys - , all isKind kinds + , Just (kinds, ty) <- snocView tys -- Ignore kind arguments + , all isKind kinds -- for this purpose , Just tv <- tcGetTyVar_maybe ty , isMetaTyVar tv -- We might have runtime-skolems in GHCi, and -- we definitely don't want to try to assign to those! @@ -1392,12 +1402,10 @@ findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds cmp_tv (_,_,tv1) (_,_,tv2) = tv1 `compare` tv2 - is_defaultable_group ds@((_,_,tv):_) + defaultable_tyvar tv = let b1 = isTyConableTyVar tv -- Note [Avoiding spurious errors] b2 = not (tv `elemVarSet` bad_tvs) - b4 = defaultable_classes [cls | (_,cls,_) <- ds] - in (b1 && b2 && b4) - is_defaultable_group [] = panic "defaultable_group" + in b1 && b2 defaultable_classes clss | extended_defaults = any isInteractiveClass clss @@ -1416,22 +1424,19 @@ findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds -- Similarly is_std_class ------------------------------ -disambigGroup :: [Type] -- The default types - -> [(Ct, Class, TcTyVar)] -- All classes of the form (C a) - -- sharing same type variable +disambigGroup :: [Type] -- The default types + -> (TcTyVar, [Ct]) -- All classes of the form (C a) + -- sharing same type variable -> TcS Bool -- True <=> something happened, reflected in ty_binds -disambigGroup [] _grp +disambigGroup [] _ = return False -disambigGroup (default_ty:default_tys) group - = do { traceTcS "disambigGroup {" (ppr group $$ ppr default_ty) +disambigGroup (default_ty:default_tys) group@(the_tv, wanteds) + = do { traceTcS "disambigGroup {" (vcat [ ppr default_ty, ppr the_tv, ppr wanteds ]) ; fake_ev_binds_var <- TcS.newTcEvBinds - ; given_ev_var <- TcS.newEvVar (mkTcEqPred (mkTyVarTy the_tv) default_ty) ; tclvl <- TcS.getTcLevel - ; success <- nestImplicTcS fake_ev_binds_var (pushTcLevel tclvl) $ - do { solveSimpleGivens loc [given_ev_var] - ; residual_wanted <- solveSimpleWanteds wanteds - ; return (isEmptyWC residual_wanted) } + ; success <- nestImplicTcS fake_ev_binds_var (pushTcLevel tclvl) + try_group ; if success then -- Success: record the type variable binding, and return @@ -1445,8 +1450,21 @@ disambigGroup (default_ty:default_tys) group (ppr default_ty) ; disambigGroup default_tys group } } where - wanteds = listToBag (map fstOf3 group) - ((_,_,the_tv):_) = group + try_group + | Just subst <- mb_subst + = do { wanted_evs <- mapM (newWantedEvVarNC loc . substTy subst . ctPred) + wanteds + ; residual_wanted <- solveSimpleWanteds $ listToBag $ + map mkNonCanonical wanted_evs + ; return (isEmptyWC residual_wanted) } + | otherwise + = return False + + tmpl_tvs = extendVarSet (tyVarsOfType (tyVarKind the_tv)) the_tv + mb_subst = tcMatchTy tmpl_tvs (mkTyVarTy the_tv) default_ty + -- Make sure the kinds match too; hence this call to tcMatchTy + -- E.g. suppose the only constraint was (Typeable k (a::k)) + loc = CtLoc { ctl_origin = GivenOrigin UnkSkol , ctl_env = panic "disambigGroup:env" , ctl_depth = initialSubGoalDepth } From git at git.haskell.org Tue Jan 6 15:10:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 15:10:15 +0000 (UTC) Subject: [commit: ghc] master: Print singleton consraints without parens (da9b2ec) Message-ID: <20150106151015.0773B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/da9b2ec3e19edb1de0e73e8f32aa0443743f072c/ghc >--------------------------------------------------------------- commit da9b2ec3e19edb1de0e73e8f32aa0443743f072c Author: Simon Peyton Jones Date: Mon Jan 5 12:56:46 2015 +0000 Print singleton consraints without parens The main change is in TypeRep.pprTheta, so we print Eq a for a singleton, but (Eq a, Show a) for multiple constraints. There are lots of trivial knock-on changes to error messages >--------------------------------------------------------------- da9b2ec3e19edb1de0e73e8f32aa0443743f072c compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcErrors.hs | 8 ++++---- compiler/types/TypeRep.hs | 2 +- testsuite/tests/deriving/should_fail/T5287.stderr | 2 +- .../tests/deriving/should_fail/drvfail-functor2.stderr | 2 +- testsuite/tests/gadt/gadt-escape1.stderr | 2 +- testsuite/tests/gadt/gadt13.stderr | 2 +- testsuite/tests/gadt/gadt21.stderr | 2 +- testsuite/tests/gadt/gadt7.stderr | 2 +- .../tests/indexed-types/should_compile/Simple14.stderr | 2 +- .../tests/indexed-types/should_compile/T3208b.stderr | 8 ++++---- testsuite/tests/indexed-types/should_fail/T2664.stderr | 4 ++-- testsuite/tests/indexed-types/should_fail/T3440.stderr | 4 ++-- .../tests/indexed-types/should_fail/T4093a.stderr | 4 ++-- .../tests/indexed-types/should_fail/T4093b.stderr | 6 +++--- testsuite/tests/indexed-types/should_fail/T8155.stderr | 2 +- testsuite/tests/module/mod47.stderr | 2 +- .../WarningWildcardInstantiations.stderr | 5 ++--- .../ExtraConstraintsWildcardNotEnabled.stderr | 2 +- .../InstantiatedNamedWildcardsInConstraints.stderr | 2 +- .../should_fail/WildcardInstantiations.stderr | 2 +- testsuite/tests/polykinds/T7230.stderr | 8 ++++---- testsuite/tests/polykinds/T7438.stderr | 2 +- testsuite/tests/polykinds/T7594.stderr | 2 +- testsuite/tests/polykinds/T8566.stderr | 4 ++-- testsuite/tests/polykinds/T9222.stderr | 2 +- testsuite/tests/typecheck/should_compile/T7220a.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc168.stderr | 2 +- .../should_fail/FailDueToGivenOverlapping.stderr | 2 +- testsuite/tests/typecheck/should_fail/IPFail.stderr | 2 +- testsuite/tests/typecheck/should_fail/T1897a.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/T5853.stderr | 18 +++++++++--------- testsuite/tests/typecheck/should_fail/T7279.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7525.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/T7857.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8912.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9109.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail034.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail041.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail042.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/tcfail067.stderr | 8 ++++---- testsuite/tests/typecheck/should_fail/tcfail072.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail080.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail097.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail098.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail102.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail108.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail130.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail142.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail181.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail208.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail211.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail213.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail214.stderr | 2 +- 55 files changed, 85 insertions(+), 86 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc da9b2ec3e19edb1de0e73e8f32aa0443743f072c From git at git.haskell.org Tue Jan 6 15:10:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 15:10:17 +0000 (UTC) Subject: [commit: ghc] master: Major patch to add -fwarn-redundant-constraints (32973bf) Message-ID: <20150106151017.CD6AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/32973bf3c2f6fe00e01b44a63ac1904080466938/ghc >--------------------------------------------------------------- commit 32973bf3c2f6fe00e01b44a63ac1904080466938 Author: Simon Peyton Jones Date: Mon Jan 5 13:20:48 2015 +0000 Major patch to add -fwarn-redundant-constraints The idea was promted by Trac #9939, but it was Christmas, so I did some recreational programming that went much further. The idea is to warn when a constraint in a user-supplied context is redundant. Everything is described in detail in Note [Tracking redundant constraints] in TcSimplify. Main changes: * The new ic_status field in an implication, of type ImplicStatus. It replaces ic_insol, and includes information about redundant constraints. * New function TcSimplify.setImplicationStatus sets the ic_status. * TcSigInfo has sig_report_redundant field to say whenther a redundant constraint should be reported; and similarly the FunSigCtxt constructor of UserTypeCtxt * EvBinds has a field eb_is_given, to record whether it is a given or wanted binding. Some consequential chagnes to creating an evidence binding (so that we record whether it is given or wanted). * AbsBinds field abs_ev_binds is now a *list* of TcEvBiinds; see Note [Typechecking plan for instance declarations] in TcInstDcls * Some significant changes to the type checking of instance declarations; Note [Typechecking plan for instance declarations] in TcInstDcls. * I found that TcErrors.relevantBindings was failing to zonk the origin of the constraint it was looking at, and hence failing to find some relevant bindings. Easy to fix, and orthogonal to everything else, but hard to disentangle. Some minor refactorig: * TcMType.newSimpleWanteds moves to Inst, renamed as newWanteds * TcClassDcl and TcInstDcls now have their own code for typechecking a method body, rather than sharing a single function. The shared function (ws TcClassDcl.tcInstanceMethodBody) didn't have much code and the differences were growing confusing. * Add new function TcRnMonad.pushLevelAndCaptureConstraints, and use it * Add new function Bag.catBagMaybes, and use it in TcSimplify >--------------------------------------------------------------- 32973bf3c2f6fe00e01b44a63ac1904080466938 compiler/basicTypes/BasicTypes.hs | 2 + compiler/deSugar/DsArrows.hs | 4 +- compiler/deSugar/DsBinds.hs | 27 +- compiler/deSugar/DsExpr.hs | 2 +- compiler/hsSyn/HsBinds.hs | 9 +- compiler/iface/BuildTyCl.hs | 2 +- compiler/iface/IfaceSyn.hs | 2 +- compiler/main/DynFlags.hs | 7 +- compiler/typecheck/Inst.hs | 18 +- compiler/typecheck/TcBinds.hs | 52 +- compiler/typecheck/TcCanonical.hs | 30 +- compiler/typecheck/TcClassDcl.hs | 139 ++-- compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcErrors.hs | 244 ++++--- compiler/typecheck/TcEvidence.hs | 42 +- compiler/typecheck/TcFlatten.hs | 6 +- compiler/typecheck/TcHsSyn.hs | 31 +- compiler/typecheck/TcInstDcls.hs | 751 +++++++++++++-------- compiler/typecheck/TcInteract.hs | 80 ++- compiler/typecheck/TcMType.hs | 35 +- compiler/typecheck/TcMatches.hs | 2 +- compiler/typecheck/TcPat.hs | 29 +- compiler/typecheck/TcPatSyn.hs | 16 +- compiler/typecheck/TcRnDriver.hs | 5 +- compiler/typecheck/TcRnMonad.hs | 33 +- compiler/typecheck/TcRnTypes.hs | 79 ++- compiler/typecheck/TcRules.hs | 36 +- compiler/typecheck/TcSMonad.hs | 42 +- compiler/typecheck/TcSimplify.hs | 270 +++++++- compiler/typecheck/TcTyClsDecls.hs | 6 +- compiler/typecheck/TcType.hs | 18 +- compiler/typecheck/TcUnify.hs | 37 +- compiler/typecheck/TcValidity.hs | 2 +- compiler/utils/Bag.hs | 15 +- compiler/utils/Util.hs | 2 + docs/users_guide/using.xml | 32 + testsuite/tests/arrows/should_compile/arrowpat.hs | 3 +- testsuite/tests/codeGen/should_compile/T3286.hs | 1 + testsuite/tests/deriving/should_compile/T2856.hs | 1 + testsuite/tests/deriving/should_compile/T4966.hs | 2 + .../tests/deriving/should_compile/T4966.stderr | 4 +- .../tests/deriving/should_compile/deriving-1935.hs | 2 + .../deriving/should_compile/deriving-1935.stderr | 6 +- testsuite/tests/deriving/should_compile/drv001.hs | 2 + testsuite/tests/deriving/should_compile/drv002.hs | 2 + testsuite/tests/deriving/should_compile/drv003.hs | 2 + .../tests/deriving/should_compile/drv003.stderr | 4 +- testsuite/tests/deriving/should_run/T9576.stderr | 2 +- testsuite/tests/gadt/Gadt17_help.hs | 2 +- testsuite/tests/ghci/scripts/T5045.hs | 1 + testsuite/tests/ghci/scripts/T8357.hs | 1 + testsuite/tests/ghci/scripts/T8931.script | 1 + testsuite/tests/ghci/scripts/ghci044.script | 1 + testsuite/tests/ghci/scripts/ghci044.stderr | 6 +- testsuite/tests/ghci/scripts/ghci047.script | 1 + testsuite/tests/ghci/scripts/ghci047.stderr | 4 +- testsuite/tests/haddock/haddock_examples/Test.hs | 1 + .../haddock/haddock_examples/haddock.Test.stderr | 8 +- .../should_compile_flag_haddock/haddockA023.hs | 2 + .../should_compile_flag_haddock/haddockA026.hs | 2 + .../should_compile_flag_haddock/haddockA027.hs | 2 + .../should_compile_noflag_haddock/haddockC026.hs | 2 + .../should_compile_noflag_haddock/haddockC027.hs | 2 + .../tests/indexed-types/should_compile/Class2.hs | 1 + .../tests/indexed-types/should_compile/Gentle.hs | 1 + .../should_compile/InstContextNorm.hs | 1 + .../indexed-types/should_compile/InstEqContext.hs | 1 + .../indexed-types/should_compile/InstEqContext2.hs | 1 + .../indexed-types/should_compile/InstEqContext3.hs | 1 + .../indexed-types/should_compile/NonLinearLHS.hs | 1 + .../tests/indexed-types/should_compile/Rules1.hs | 1 + .../tests/indexed-types/should_compile/Simple24.hs | 1 + .../tests/indexed-types/should_compile/T2448.hs | 1 + .../tests/indexed-types/should_compile/T3023.hs | 3 +- .../indexed-types/should_compile/T3023.stderr | 5 +- .../tests/indexed-types/should_compile/T3484.hs | 3 +- .../tests/indexed-types/should_compile/T4200.hs | 1 + .../tests/indexed-types/should_compile/T4497.hs | 1 + .../tests/indexed-types/should_compile/T4981-V1.hs | 2 + .../tests/indexed-types/should_compile/T4981-V2.hs | 2 + .../tests/indexed-types/should_compile/T4981-V3.hs | 2 + .../tests/indexed-types/should_compile/T5002.hs | 1 + .../tests/indexed-types/should_compile/T9090.hs | 2 + .../tests/indexed-types/should_compile/T9316.hs | 1 + .../tests/indexed-types/should_compile/T9747.hs | 2 + testsuite/tests/indexed-types/should_fail/T2239.hs | 1 + .../tests/indexed-types/should_fail/T3330c.stderr | 4 + testsuite/tests/indexed-types/should_fail/T7862.hs | 1 + .../tests/indexed-types/should_fail/T7862.stderr | 2 +- testsuite/tests/module/mod129.hs | 2 + testsuite/tests/module/mod71.stderr | 9 + testsuite/tests/parser/should_compile/mc15.hs | 2 +- testsuite/tests/parser/should_compile/read002.hs | 2 + testsuite/tests/partial-sigs/should_compile/all.T | 2 +- testsuite/tests/patsyn/should_compile/T8584-2.hs | 2 + testsuite/tests/patsyn/should_compile/T8968-1.hs | 1 + testsuite/tests/patsyn/should_compile/all.T | 4 +- testsuite/tests/patsyn/should_compile/ex-view.hs | 4 +- testsuite/tests/perf/compiler/T3064.hs | 2 + testsuite/tests/perf/compiler/T5030.hs | 6 +- testsuite/tests/polykinds/PolyKinds08.hs | 1 + testsuite/tests/polykinds/T6015a.hs | 1 + testsuite/tests/polykinds/T6020a.hs | 1 + testsuite/tests/polykinds/T6068.hs | 1 + testsuite/tests/polykinds/T7090.hs | 1 + testsuite/tests/polykinds/T7332.hs | 20 +- testsuite/tests/polykinds/T8359.hs | 2 + testsuite/tests/polykinds/T9569.hs | 1 + testsuite/tests/polykinds/T9750.hs | 1 + testsuite/tests/rebindable/T5821.hs | 3 +- testsuite/tests/rebindable/rebindable9.hs | 4 +- testsuite/tests/rename/should_fail/rnfail020.hs | 1 + testsuite/tests/simplCore/should_compile/T3831.hs | 1 + testsuite/tests/simplCore/should_compile/T4398.hs | 1 + .../tests/simplCore/should_compile/T4398.stderr | 2 +- testsuite/tests/simplCore/should_compile/T5329.hs | 1 + testsuite/tests/simplCore/should_compile/T5342.hs | 1 + testsuite/tests/simplCore/should_compile/T5359b.hs | 1 + .../tests/simplCore/should_compile/T5359b.stderr | 2 +- testsuite/tests/simplCore/should_compile/T8848.hs | 3 +- .../tests/simplCore/should_compile/T8848.stderr | 2 +- testsuite/tests/simplCore/should_compile/T8848a.hs | 1 + .../tests/simplCore/should_compile/simpl002.hs | 2 + .../tests/simplCore/should_compile/simpl007.hs | 1 + .../tests/simplCore/should_compile/simpl014.hs | 1 + .../tests/simplCore/should_compile/simpl016.hs | 2 + .../tests/simplCore/should_compile/simpl016.stderr | 2 +- .../tests/simplCore/should_compile/spec003.hs | 2 + testsuite/tests/th/T3100.hs | 1 + testsuite/tests/th/T7021a.hs | 1 + testsuite/tests/th/T8807.hs | 1 + testsuite/tests/th/TH_tf3.hs | 1 + .../typecheck/should_compile/GivenOverlapping.hs | 1 + .../typecheck/should_compile/LoopOfTheDay1.hs | 1 + .../typecheck/should_compile/LoopOfTheDay2.hs | 1 + .../typecheck/should_compile/LoopOfTheDay3.hs | 1 + testsuite/tests/typecheck/should_compile/T1470.hs | 1 + testsuite/tests/typecheck/should_compile/T2683.hs | 1 + testsuite/tests/typecheck/should_compile/T3018.hs | 1 + testsuite/tests/typecheck/should_compile/T3108.hs | 1 + testsuite/tests/typecheck/should_compile/T3692.hs | 1 + testsuite/tests/typecheck/should_compile/T3743.hs | 1 + testsuite/tests/typecheck/should_compile/T4361.hs | 1 + testsuite/tests/typecheck/should_compile/T4401.hs | 1 + testsuite/tests/typecheck/should_compile/T4524.hs | 1 + testsuite/tests/typecheck/should_compile/T4952.hs | 1 + testsuite/tests/typecheck/should_compile/T4969.hs | 2 +- testsuite/tests/typecheck/should_compile/T5514.hs | 1 + testsuite/tests/typecheck/should_compile/T5581.hs | 2 + testsuite/tests/typecheck/should_compile/T5676.hs | 1 + testsuite/tests/typecheck/should_compile/T6055.hs | 1 + testsuite/tests/typecheck/should_compile/T6134.hs | 1 + testsuite/tests/typecheck/should_compile/T7171a.hs | 1 + testsuite/tests/typecheck/should_compile/T7196.hs | 1 + testsuite/tests/typecheck/should_compile/T7220.hs | 1 + testsuite/tests/typecheck/should_compile/T7541.hs | 2 +- testsuite/tests/typecheck/should_compile/T7875.hs | 1 + testsuite/tests/typecheck/should_compile/T7903.hs | 1 + .../typecheck/should_compile/T7903.stderr-ghc | 4 +- .../tests/typecheck/should_compile/Tc170_Aux.hs | 1 + testsuite/tests/typecheck/should_compile/Tc173a.hs | 2 + testsuite/tests/typecheck/should_compile/tc045.hs | 1 + testsuite/tests/typecheck/should_compile/tc051.hs | 2 + .../tests/typecheck/should_compile/tc056.stderr | 6 +- testsuite/tests/typecheck/should_compile/tc058.hs | 2 + testsuite/tests/typecheck/should_compile/tc065.hs | 4 +- testsuite/tests/typecheck/should_compile/tc078.hs | 2 + .../typecheck/should_compile/tc078.stderr-ghc | 4 +- testsuite/tests/typecheck/should_compile/tc079.hs | 2 + testsuite/tests/typecheck/should_compile/tc088.hs | 2 + testsuite/tests/typecheck/should_compile/tc091.hs | 2 + testsuite/tests/typecheck/should_compile/tc092.hs | 1 + testsuite/tests/typecheck/should_compile/tc109.hs | 1 + testsuite/tests/typecheck/should_compile/tc113.hs | 2 + testsuite/tests/typecheck/should_compile/tc115.hs | 1 + .../typecheck/should_compile/tc115.stderr-ghc | 2 +- testsuite/tests/typecheck/should_compile/tc116.hs | 1 + .../typecheck/should_compile/tc116.stderr-ghc | 2 +- testsuite/tests/typecheck/should_compile/tc125.hs | 1 + .../typecheck/should_compile/tc125.stderr-ghc | 10 +- testsuite/tests/typecheck/should_compile/tc126.hs | 1 + .../typecheck/should_compile/tc126.stderr-ghc | 4 +- testsuite/tests/typecheck/should_compile/tc145.hs | 1 + testsuite/tests/typecheck/should_compile/tc152.hs | 1 + testsuite/tests/typecheck/should_compile/tc176.hs | 1 + testsuite/tests/typecheck/should_compile/tc178.hs | 1 + testsuite/tests/typecheck/should_compile/tc180.hs | 1 + testsuite/tests/typecheck/should_compile/tc181.hs | 1 + testsuite/tests/typecheck/should_compile/tc183.hs | 1 + testsuite/tests/typecheck/should_compile/tc187.hs | 1 + testsuite/tests/typecheck/should_compile/tc192.hs | 1 + testsuite/tests/typecheck/should_compile/tc203.hs | 1 + testsuite/tests/typecheck/should_compile/tc204.hs | 3 +- testsuite/tests/typecheck/should_compile/tc206.hs | 1 + testsuite/tests/typecheck/should_compile/tc208.hs | 1 + testsuite/tests/typecheck/should_compile/tc229.hs | 1 + testsuite/tests/typecheck/should_compile/tc230.hs | 1 + testsuite/tests/typecheck/should_compile/tc235.hs | 1 + testsuite/tests/typecheck/should_compile/tc237.hs | 1 + testsuite/tests/typecheck/should_compile/tc239.hs | 1 + testsuite/tests/typecheck/should_compile/twins.hs | 1 + testsuite/tests/typecheck/should_fail/T6161.stderr | 4 +- .../tests/typecheck/should_fail/tcfail017.stderr | 4 +- .../tests/typecheck/should_fail/tcfail020.stderr | 4 +- testsuite/tests/typecheck/should_fail/tcfail071.hs | 2 + testsuite/tests/typecheck/should_fail/tcfail138.hs | 1 + .../tests/typecheck/should_fail/tcfail143.stderr | 4 +- 207 files changed, 1595 insertions(+), 855 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 32973bf3c2f6fe00e01b44a63ac1904080466938 From git at git.haskell.org Tue Jan 6 15:10:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 15:10:20 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant constraints in the compiler itself, found by -fwarn-redundant-constraints (39337a6) Message-ID: <20150106151020.8BD803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/39337a6d97c853a88fa61d6b12a04eb8c2e5984f/ghc >--------------------------------------------------------------- commit 39337a6d97c853a88fa61d6b12a04eb8c2e5984f Author: Simon Peyton Jones Date: Mon Jan 5 16:57:01 2015 +0000 Remove redundant constraints in the compiler itself, found by -fwarn-redundant-constraints >--------------------------------------------------------------- 39337a6d97c853a88fa61d6b12a04eb8c2e5984f compiler/basicTypes/Name.hs | 3 ++- compiler/cmm/CmmExpr.hs | 8 ++++---- compiler/cmm/Hoopl/Dataflow.hs | 2 +- compiler/coreSyn/TrieMap.hs | 4 ++-- compiler/deSugar/MatchLit.hs | 2 +- compiler/ghci/ByteCodeItbls.hs | 6 ++++-- compiler/ghci/Linker.hs | 2 +- compiler/hsSyn/HsDecls.hs | 8 +++----- compiler/hsSyn/HsExpr.hs | 8 ++++---- compiler/main/CmdLineParser.hs | 2 +- compiler/main/GHC.hs | 10 +++++++--- compiler/main/GhcMonad.hs | 17 +++++++++++++---- compiler/main/InteractiveEval.hs | 3 +-- compiler/nativeGen/RegAlloc/Graph/SpillClean.hs | 11 ++++------- compiler/nativeGen/RegAlloc/Linear/Main.hs | 4 ++-- compiler/nativeGen/SPARC/Base.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 3 ++- compiler/types/CoAxiom.hs | 2 +- compiler/utils/Binary.hs | 2 +- compiler/utils/GraphColor.hs | 6 +++--- compiler/utils/GraphOps.hs | 24 ++++++++++-------------- compiler/utils/GraphPpr.hs | 9 ++++----- compiler/utils/Maybes.hs | 4 ++++ compiler/utils/Serialized.hs | 4 ++-- compiler/utils/UniqSet.hs | 2 +- 25 files changed, 79 insertions(+), 69 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 39337a6d97c853a88fa61d6b12a04eb8c2e5984f From git at git.haskell.org Tue Jan 6 15:10:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 15:10:23 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant constraints from libraries, discovered by -fwarn-redundant-constraints (c409b6f) Message-ID: <20150106151023.393343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c409b6f30373535b6eed92e55d4695688d32be9e/ghc >--------------------------------------------------------------- commit c409b6f30373535b6eed92e55d4695688d32be9e Author: Simon Peyton Jones Date: Tue Jan 6 13:46:35 2015 +0000 Remove redundant constraints from libraries, discovered by -fwarn-redundant-constraints This patch affects libraries, and requires a submodule update. Some other libraries, maintained by others, have redundant constraints, namely: containers haskeline transformers binary I have suppressed the redundant-constraint warnings by settings in validate-settings.mk (in this commit) >--------------------------------------------------------------- c409b6f30373535b6eed92e55d4695688d32be9e libraries/array | 2 +- libraries/base/Data/Data.hs | 8 +++---- libraries/base/Data/Foldable.hs | 4 ++-- libraries/base/GHC/Arr.hs | 46 +++++++++++++++++++-------------------- libraries/base/GHC/Event/Array.hs | 4 ++-- libraries/base/GHC/IOArray.hs | 4 ++-- libraries/base/GHC/Real.hs | 6 ++--- libraries/base/Text/Printf.hs | 2 +- libraries/deepseq | 2 +- libraries/hoopl | 2 +- libraries/parallel | 2 +- mk/validate-settings.mk | 3 +++ 12 files changed, 44 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c409b6f30373535b6eed92e55d4695688d32be9e From git at git.haskell.org Tue Jan 6 15:29:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 15:29:05 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9939 (c790fe8) Message-ID: <20150106152905.EB6043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c790fe87be648f420c63099934852013a4e8a8f7/ghc >--------------------------------------------------------------- commit c790fe87be648f420c63099934852013a4e8a8f7 Author: Simon Peyton Jones Date: Tue Jan 6 15:28:16 2015 +0000 Test Trac #9939 >--------------------------------------------------------------- c790fe87be648f420c63099934852013a4e8a8f7 compiler/typecheck/TcSimplify.hs | 10 ++++++++++ testsuite/tests/typecheck/should_compile/T9939.hs | 23 ++++++++++++++++++++++ .../should_compile/T9939.stderr} | 0 testsuite/tests/typecheck/should_compile/all.T | 1 + 4 files changed, 34 insertions(+) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 761a7a5..b226fde 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -1104,6 +1104,16 @@ works: so that we can discard implication constraints that we don't need. So ics_dead consists only of the *reportable* redundant givens. +----- Shortcomings + +Consider (see Trac #9939) + f2 :: (Eq a, Ord a) => a -> a -> Bool + -- Ord a redundant, but Eq a is reported + f2 x y = (x == y) + +We report (Eq a) as redundant, whereas actually (Ord a) is. But it's +really not easy to detect that! + Note [Cutting off simpl_loop] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/testsuite/tests/typecheck/should_compile/T9939.hs b/testsuite/tests/typecheck/should_compile/T9939.hs new file mode 100644 index 0000000..4ae370b --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9939.hs @@ -0,0 +1,23 @@ +{-# LANGUAGE GADTs #-} + +module T9939 where + +f1 :: (Eq a, Ord a) => a -> a -> Bool +-- Eq a redundant +f1 x y = (x == y) && (x > y) + +f2 :: (Eq a, Ord a) => a -> a -> Bool +-- Ord a redundant, but Eq a is reported +f2 x y = (x == y) + +f3 :: (Eq a, a ~ b, Eq b) => a -> b -> Bool +-- Eq b redundant +f3 x y = x==y + +data Equal a b where + EQUAL :: Equal a a + +f4 :: (Eq a, Eq b) => a -> b -> Equal a b -> Bool +-- Eq b redundant +f4 x y EQUAL = y==y + diff --git a/testsuite/tests/deSugar/should_run/T5472.stdout b/testsuite/tests/typecheck/should_compile/T9939.stderr similarity index 100% copy from testsuite/tests/deSugar/should_run/T5472.stdout copy to testsuite/tests/typecheck/should_compile/T9939.stderr diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index d1b3796..0860a35 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -437,4 +437,5 @@ test('T9497c', normal, compile, ['-fdefer-type-errors -fno-warn-typed-holes']) test('T7643', normal, compile, ['']) test('T9834', normal, compile, ['']) test('T9892', normal, compile, ['']) +test('T9939', normal, compile, ['']) From git at git.haskell.org Tue Jan 6 16:44:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 16:44:48 +0000 (UTC) Subject: [commit: ghc] master: Update haddock submodule, and fix haddock input file from genprimopcode (d57f507) Message-ID: <20150106164448.31B183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d57f507f6961494a23d88f748c030c5346250a3c/ghc >--------------------------------------------------------------- commit d57f507f6961494a23d88f748c030c5346250a3c Author: Simon Peyton Jones Date: Tue Jan 6 16:43:52 2015 +0000 Update haddock submodule, and fix haddock input file from genprimopcode * A module in haddock an unused constraint, now fixed and pushed to ghc-head This patch records the new commit in GHC repo * genprimopcode generates a dummy Prim.hs for haddock. But then Haddock was complaining about redundant constraints. So this patch makes genprimopcode generate a warning-suppression OPTIONS_GHC pragma in Prim.hs >--------------------------------------------------------------- d57f507f6961494a23d88f748c030c5346250a3c utils/genprimopcode/Main.hs | 6 ++++++ utils/haddock | 2 +- 2 files changed, 7 insertions(+), 1 deletion(-) diff --git a/utils/genprimopcode/Main.hs b/utils/genprimopcode/Main.hs index 67c2131..7d5205a 100644 --- a/utils/genprimopcode/Main.hs +++ b/utils/genprimopcode/Main.hs @@ -245,6 +245,12 @@ gen_hs_source (Info defaults entries) = ++ "{-# LANGUAGE MultiParamTypeClasses #-}\n" ++ "{-# LANGUAGE NoImplicitPrelude #-}\n" ++ "{-# LANGUAGE UnboxedTuples #-}\n" + ++ "{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}\n" + -- We generate a binding for coerce, like + -- coerce :: Coercible a b => a -> b + -- coerce = let x = x in x + -- and we don't want a complaint that the constraint is redundant + -- Remember, this silly file is only for Haddock's consumption ++ "module GHC.Prim (\n" ++ unlines (map ((" " ++) . hdr) entries') ++ ") where\n" diff --git a/utils/haddock b/utils/haddock index 56b9e6b..8b1d44f 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 56b9e6bcef33612b40d3f93f170397eff77411eb +Subproject commit 8b1d44fbdde141cf883f5ddcd337bbbab8433228 From git at git.haskell.org Tue Jan 6 17:24:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 17:24:58 +0000 (UTC) Subject: [commit: ghc] master: Another fix to genprimopcode, when generating Prim.hs (b0f8cb8) Message-ID: <20150106172458.EE86B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b0f8cb8aa3422fd0a7cef8eee630333fd9911d2f/ghc >--------------------------------------------------------------- commit b0f8cb8aa3422fd0a7cef8eee630333fd9911d2f Author: Simon Peyton Jones Date: Tue Jan 6 17:25:17 2015 +0000 Another fix to genprimopcode, when generating Prim.hs When haddock processes Prim.hs, it was calling TcEnv.tcGetDefaultTys, and that made it look for Integer and String, which are not in ghc-prim. Result was a crash. But we don't need defaulting in Prim.hs, so add default () >--------------------------------------------------------------- b0f8cb8aa3422fd0a7cef8eee630333fd9911d2f utils/genprimopcode/Main.hs | 18 +++++++++++++++++- 1 file changed, 17 insertions(+), 1 deletion(-) diff --git a/utils/genprimopcode/Main.hs b/utils/genprimopcode/Main.hs index 7d5205a..ed4871c 100644 --- a/utils/genprimopcode/Main.hs +++ b/utils/genprimopcode/Main.hs @@ -245,12 +245,14 @@ gen_hs_source (Info defaults entries) = ++ "{-# LANGUAGE MultiParamTypeClasses #-}\n" ++ "{-# LANGUAGE NoImplicitPrelude #-}\n" ++ "{-# LANGUAGE UnboxedTuples #-}\n" + ++ "{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}\n" -- We generate a binding for coerce, like -- coerce :: Coercible a b => a -> b -- coerce = let x = x in x -- and we don't want a complaint that the constraint is redundant -- Remember, this silly file is only for Haddock's consumption + ++ "module GHC.Prim (\n" ++ unlines (map ((" " ++) . hdr) entries') ++ ") where\n" @@ -259,7 +261,21 @@ gen_hs_source (Info defaults entries) = ++ unlines (map opt defaults) ++ "-}\n" ++ "import GHC.Types (Coercible)\n" - ++ unlines (concatMap ent entries') ++ "\n\n\n" + + ++ "default ()" -- If we don't say this then the default type include Integer + -- so that runs off and loads modules that are not part of + -- pacakge ghc-prim at all. And that in turn somehow ends up + -- with Declaration for $fEqMaybe: + -- attempting to use module ?GHC.Classes? + -- (libraries/ghc-prim/./GHC/Classes.hs) which is not loaded + -- coming from LoadIface.homeModError + -- I'm not sure precisely why; but I *am* sure that we don't need + -- any type-class defaulting; and it's clearly wrong to need + -- the base package when haddocking ghc-prim + + -- Now the main payload + ++ unlines (concatMap ent entries') ++ "\n\n\n" + where entries' = concatMap desugarVectorSpec entries opt (OptionFalse n) = n ++ " = False" From git at git.haskell.org Tue Jan 6 17:25:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Jan 2015 17:25:01 +0000 (UTC) Subject: [commit: ghc] master: Make comments less beautiful in order to pacify Haddock (8efaff1) Message-ID: <20150106172501.AF7FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8efaff11e89285c059c868b8a84deae7de3bf0f9/ghc >--------------------------------------------------------------- commit 8efaff11e89285c059c868b8a84deae7de3bf0f9 Author: Simon Peyton Jones Date: Tue Jan 6 17:26:03 2015 +0000 Make comments less beautiful in order to pacify Haddock >--------------------------------------------------------------- 8efaff11e89285c059c868b8a84deae7de3bf0f9 compiler/basicTypes/VarSet.hs | 2 +- compiler/typecheck/TcErrors.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/VarSet.hs b/compiler/basicTypes/VarSet.hs index 6c920ba..7b21487 100644 --- a/compiler/basicTypes/VarSet.hs +++ b/compiler/basicTypes/VarSet.hs @@ -112,7 +112,7 @@ subVarSet s1 s2 = isEmptyVarSet (s1 `minusVarSet` s2) transCloVarSet :: (VarSet -> VarSet) -- Map some variables in the set to - -- *extra* variables that should be in it + -- extra variables that should be in it -> VarSet -> VarSet -- (transCloVarSet f s) repeatedly applies f to the set s, adding any -- new variables to s that it finds thereby, until it reaches a fixed diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index d9b6fc7..21adab4 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -277,7 +277,7 @@ reportWanteds ctxt (WC { wc_simple = simples, wc_insol = insols, wc_impl = impli -- See Note [Do not report derived but soluble errors] ; mapBagM_ (reportImplic ctxt1) implics } -- NB ctxt1: don't suppress inner insolubles if there's only a - -- *wanted* insoluble here; but do suppress inner insolubles + -- wanted insoluble here; but do suppress inner insolubles -- if there's a *given* insoluble here (= inaccessible code) where env = cec_tidy ctxt From git at git.haskell.org Wed Jan 7 09:36:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jan 2015 09:36:37 +0000 (UTC) Subject: [commit: ghc] master: Fix undefined GHC.Real export with integer-simple (228902a) Message-ID: <20150107093637.788863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/228902aa4a3350a9c99e421c0c989c7de794b7b6/ghc >--------------------------------------------------------------- commit 228902aa4a3350a9c99e421c0c989c7de794b7b6 Author: Erik de Castro Lopo Date: Wed Jan 7 20:37:54 2015 +1100 Fix undefined GHC.Real export with integer-simple Test Plan: Check that GHC.Real compiles without OPTIMISE_INTEGER_GCD_LCM nor MIN_VERSION_integer_gmp defined. Reviewers: carter, ezyang, erikd, hvr, dfeuer, austin Reviewed By: erikd, hvr, dfeuer, austin Subscribers: erikd, dfeuer, carter, thomie Differential Revision: https://phabricator.haskell.org/D600 >--------------------------------------------------------------- 228902aa4a3350a9c99e421c0c989c7de794b7b6 libraries/base/GHC/Real.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs index 1a18e6a..1464709 100644 --- a/libraries/base/GHC/Real.hs +++ b/libraries/base/GHC/Real.hs @@ -25,7 +25,7 @@ module GHC.Real Rational, (%), (^), (^%^), (^^), (^^%^^), denominator, divZeroError, even, - fromIntegral, gcd, gcdInt', gcdWord', infinity, integralEnumFrom, + fromIntegral, gcd, infinity, integralEnumFrom, integralEnumFromThen, integralEnumFromThenTo, integralEnumFromTo, lcm, notANumber, numerator, numericEnumFrom, numericEnumFromThen, numericEnumFromThenTo, numericEnumFromTo, odd, overflowError, ratioPrec, From git at git.haskell.org Wed Jan 7 13:50:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jan 2015 13:50:16 +0000 (UTC) Subject: [commit: ghc] master: Fix stderr for T9939 (5bc99df) Message-ID: <20150107135016.A1EAC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5bc99df1e7369f6dfc882f5f12de1e840fa57fd6/ghc >--------------------------------------------------------------- commit 5bc99df1e7369f6dfc882f5f12de1e840fa57fd6 Author: Simon Peyton Jones Date: Wed Jan 7 13:51:27 2015 +0000 Fix stderr for T9939 >--------------------------------------------------------------- 5bc99df1e7369f6dfc882f5f12de1e840fa57fd6 testsuite/tests/typecheck/should_compile/T9939.stderr | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T9939.stderr b/testsuite/tests/typecheck/should_compile/T9939.stderr index 0519ecb..946fba9 100644 --- a/testsuite/tests/typecheck/should_compile/T9939.stderr +++ b/testsuite/tests/typecheck/should_compile/T9939.stderr @@ -1 +1,18 @@ +T9939.hs:5:7: + Redundant constraint: Eq a + In the type signature for: f1 :: (Eq a, Ord a) => a -> a -> Bool + +T9939.hs:9:7: + Redundant constraint: Eq a + In the type signature for: f2 :: (Eq a, Ord a) => a -> a -> Bool + +T9939.hs:13:7: + Redundant constraint: Eq b + In the type signature for: + f3 :: (Eq a, a ~ b, Eq b) => a -> b -> Bool + +T9939.hs:20:7: + Redundant constraint: Eq b + In the type signature for: + f4 :: (Eq a, Eq b) => a -> b -> Equal a b -> Bool From git at git.haskell.org Wed Jan 7 13:55:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Jan 2015 13:55:41 +0000 (UTC) Subject: [commit: ghc] master: Mark T9938 as expect_broken again (471891c) Message-ID: <20150107135541.A807B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/471891cb774a58769018ed5df2120d15bddffd28/ghc >--------------------------------------------------------------- commit 471891cb774a58769018ed5df2120d15bddffd28 Author: Simon Peyton Jones Date: Wed Jan 7 13:56:19 2015 +0000 Mark T9938 as expect_broken again It's failing reliable for me (as I think it should) and Edward. See Trac #9938. Reverts commit 633814f5 >--------------------------------------------------------------- 471891cb774a58769018ed5df2120d15bddffd28 testsuite/tests/driver/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index 0bd8d5b..ec4fdb4 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -411,7 +411,7 @@ test('write_interface_make', normal, run_command, ['$MAKE -s --no-print-director test('T9776', normal, compile_fail, ['-frule-check']) test('T9938', - [ extra_clean(['T9938.hi', 'T9938.o', 'T9938']) ], + [ extra_clean(['T9938.hi', 'T9938.o', 'T9938']), expect_broken(9938) ], run_command, ['$MAKE -s --no-print-directory T9938']) From git at git.haskell.org Thu Jan 8 00:45:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 00:45:25 +0000 (UTC) Subject: [commit: ghc] master: Compress TypeMap TrieMap leaves with singleton constructor. (da64ab5) Message-ID: <20150108004525.65DB13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/da64ab530512c36acd17c1dbcd3b5fcc681d128b/ghc >--------------------------------------------------------------- commit da64ab530512c36acd17c1dbcd3b5fcc681d128b Author: Edward Z. Yang Date: Tue Jan 6 13:34:18 2015 -0800 Compress TypeMap TrieMap leaves with singleton constructor. Suppose we have a handful H of entries in a TrieMap, each with a very large key, size K. If you fold over such a TrieMap you'd expect time O(H). That would certainly be true of an association list! But with TrieMap we actually have to navigate down a long singleton structure to get to the elements, so it takes time O(K*H). The point of a TrieMap is that you need to navigate to the point where only one key remains, and then things should be fast. This is a starting point: we can improve the patch by generalizing the singleton constructor so it applies to CoercionMap and CoreMap; I'll do this in a later commit. Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D606 GHC Trac Issues: #9960 >--------------------------------------------------------------- da64ab530512c36acd17c1dbcd3b5fcc681d128b compiler/coreSyn/TrieMap.hs | 59 ++++++++++++++++++++++++++++++++++++- testsuite/tests/perf/compiler/all.T | 3 +- 2 files changed, 60 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/TrieMap.hs b/compiler/coreSyn/TrieMap.hs index 9197386..a8ac2b1 100644 --- a/compiler/coreSyn/TrieMap.hs +++ b/compiler/coreSyn/TrieMap.hs @@ -622,6 +622,7 @@ mapR f = RM . mapTM f . unRM data TypeMap a = EmptyTM + | SingletonTM (CmEnv, Type) a | TM { tm_var :: VarMap a , tm_app :: TypeMap (TypeMap a) , tm_fun :: TypeMap (TypeMap a) @@ -630,6 +631,41 @@ data TypeMap a , tm_tylit :: TyLitMap a } +eqTypesModuloDeBruijn :: (CmEnv, [Type]) -> (CmEnv, [Type]) -> Bool +eqTypesModuloDeBruijn (_, []) (_, []) = True +eqTypesModuloDeBruijn (env, ty:tys) (env', ty':tys') = + eqTypeModuloDeBruijn (env, ty) (env', ty') && + eqTypesModuloDeBruijn (env, tys) (env', tys') +eqTypesModuloDeBruijn _ _ = False + +-- NB: need to coreView! +eqTypeModuloDeBruijn :: (CmEnv, Type) -> (CmEnv, Type) -> Bool +eqTypeModuloDeBruijn env_t@(env, t) env_t'@(env', t') + -- ToDo: I guess we can make this a little more efficient + | Just new_t <- coreView t = eqTypeModuloDeBruijn (env, new_t) env_t' + | Just new_t' <- coreView t' = eqTypeModuloDeBruijn env_t (env', new_t') +eqTypeModuloDeBruijn (env, t) (env', t') = + case (t, t') of + (TyVarTy v, TyVarTy v') + -> case (lookupCME env v, lookupCME env' v') of + (Just bv, Just bv') -> bv == bv' + (Nothing, Nothing) -> v == v' + _ -> False + (AppTy t1 t2, AppTy t1' t2') + -> eqTypeModuloDeBruijn (env, t1) (env', t1') && + eqTypeModuloDeBruijn (env, t2) (env', t2') + (FunTy t1 t2, FunTy t1' t2') + -> eqTypeModuloDeBruijn (env, t1) (env', t1') && + eqTypeModuloDeBruijn (env, t2) (env', t2') + (TyConApp tc tys, TyConApp tc' tys') + -> tc == tc' && eqTypesModuloDeBruijn (env, tys) (env', tys') + (LitTy l, LitTy l') + -> l == l' + (ForAllTy tv ty, ForAllTy tv' ty') + -> eqTypeModuloDeBruijn (env, tyVarKind tv) (env', tyVarKind tv') && + eqTypeModuloDeBruijn (extendCME env tv, ty) + (extendCME env' tv', ty') + _ -> False instance Outputable a => Outputable (TypeMap a) where ppr m = text "TypeMap elts" <+> ppr (foldTypeMap (:) [] m) @@ -647,6 +683,10 @@ lookupTypeMap cm t = lkT emptyCME t cm -- This only considers saturated applications (i.e. TyConApp ones). lookupTypeMapTyCon :: TypeMap a -> TyCon -> [a] lookupTypeMapTyCon EmptyTM _ = [] +lookupTypeMapTyCon (SingletonTM (_, TyConApp tc' _) v) tc + | tc' == tc = [v] + | otherwise = [] +lookupTypeMapTyCon SingletonTM{} _ = [] lookupTypeMapTyCon TM { tm_tc_app = cs } tc = case lookupUFM cs tc of Nothing -> [] @@ -673,6 +713,7 @@ instance TrieMap TypeMap where mapT :: (a->b) -> TypeMap a -> TypeMap b mapT _ EmptyTM = EmptyTM +mapT f (SingletonTM env_ty v) = SingletonTM env_ty (f v) mapT f (TM { tm_var = tvar, tm_app = tapp, tm_fun = tfun , tm_tc_app = ttcapp, tm_forall = tforall, tm_tylit = tlit }) = TM { tm_var = mapTM f tvar @@ -686,6 +727,10 @@ mapT f (TM { tm_var = tvar, tm_app = tapp, tm_fun = tfun lkT :: CmEnv -> Type -> TypeMap a -> Maybe a lkT env ty m | EmptyTM <- m = Nothing + | SingletonTM env_ty v <- m = + if eqTypeModuloDeBruijn env_ty (env, ty) + then Just v + else Nothing | otherwise = go ty m where go ty | Just ty' <- coreView ty = go ty' @@ -700,7 +745,18 @@ lkT env ty m ----------------- xtT :: CmEnv -> Type -> XT a -> TypeMap a -> TypeMap a xtT env ty f m - | EmptyTM <- m = xtT env ty f wrapEmptyTypeMap + | EmptyTM <- m = case f Nothing of + Just v -> SingletonTM (env, ty) v + Nothing -> EmptyTM + | SingletonTM env_ty@(env', ty') v' <- m + = if eqTypeModuloDeBruijn env_ty (env, ty) + then case f (Just v') of + Just v'' -> SingletonTM env_ty v'' + Nothing -> EmptyTM + else case f Nothing of + Nothing -> SingletonTM env_ty v' + Just v -> wrapEmptyTypeMap |> xtT env' ty' (const (Just v')) + >.> xtT env ty (const (Just v)) | Just ty' <- coreView ty = xtT env ty' f m xtT env (TyVarTy v) f m = m { tm_var = tm_var m |> xtVar env v f } @@ -714,6 +770,7 @@ xtT _ (LitTy l) f m = m { tm_tylit = tm_tylit m |> xtTyLit l f } fdT :: (a -> b -> b) -> TypeMap a -> b -> b fdT _ EmptyTM = \z -> z +fdT k (SingletonTM _ v) = \z -> k v z fdT k m = foldTM k (tm_var m) . foldTM (foldTM k) (tm_app m) . foldTM (foldTM k) (tm_fun m) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 2d96497..10136bb 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -607,9 +607,10 @@ test('T9872c', test('T9872d', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 739189056, 5), + [(wordsize(64), 687562440, 5), # 2014-12-18 796071864 Initally created # 2014-12-18 739189056 Reduce type families even more eagerly + # 2015-01-07 687562440 TrieMap leaf compression (wordsize(32), 353644844, 5) ]), ], From git at git.haskell.org Thu Jan 8 00:45:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 00:45:28 +0000 (UTC) Subject: [commit: ghc] master: Generalize TrieMap compression to GenMap. (197f4e5) Message-ID: <20150108004528.3A43D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/197f4e5aa3443c39e3ec2e53f8e595326ddaa524/ghc >--------------------------------------------------------------- commit 197f4e5aa3443c39e3ec2e53f8e595326ddaa524 Author: Edward Z. Yang Date: Wed Jan 7 13:48:10 2015 -0800 Generalize TrieMap compression to GenMap. I still haven't applied the optimization to anything besides TypeMap. Summary: Signed-off-by: Edward Z. Yang Depends On: D606 Reviewers: simonpj, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D607 GHC Trac Issues: #9960 >--------------------------------------------------------------- 197f4e5aa3443c39e3ec2e53f8e595326ddaa524 compiler/coreSyn/TrieMap.hs | 203 +++++++++++++++++++++++++++++++++----------- 1 file changed, 154 insertions(+), 49 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 197f4e5aa3443c39e3ec2e53f8e595326ddaa524 From git at git.haskell.org Thu Jan 8 06:48:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 06:48:49 +0000 (UTC) Subject: [commit: ghc] master: Fix out of date comment. (b14dae3) Message-ID: <20150108064849.3A0DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b14dae3cc43572a9dd5ca11241981105e4281aac/ghc >--------------------------------------------------------------- commit b14dae3cc43572a9dd5ca11241981105e4281aac Author: Edward Z. Yang Date: Wed Jan 7 22:49:36 2015 -0800 Fix out of date comment. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- b14dae3cc43572a9dd5ca11241981105e4281aac compiler/main/DynFlags.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index b8c2bb1..c18b868 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -770,7 +770,7 @@ data DynFlags = DynFlags { -- Package state -- NB. do not modify this field, it is calculated by - -- Packages.initPackages and Packages.updatePackages. + -- Packages.initPackages pkgDatabase :: Maybe [PackageConfig], pkgState :: PackageState, From git at git.haskell.org Thu Jan 8 11:55:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 11:55:59 +0000 (UTC) Subject: [commit: ghc] branch 'wip/gadtpm' created Message-ID: <20150108115559.0D20B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/gadtpm Referencing: 58220463d0a8c56f314ba4bacb0f9f8ab15d5804 From git at git.haskell.org Thu Jan 8 11:56:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 11:56:01 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: PM Check: Syntactic part (5822046) Message-ID: <20150108115601.C34C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/58220463d0a8c56f314ba4bacb0f9f8ab15d5804/ghc >--------------------------------------------------------------- commit 58220463d0a8c56f314ba4bacb0f9f8ab15d5804 Author: George Karachalias Date: Thu Jan 8 12:48:06 2015 +0100 PM Check: Syntactic part >--------------------------------------------------------------- 58220463d0a8c56f314ba4bacb0f9f8ab15d5804 compiler/deSugar/Check.hs | 1236 ++++++++++++++++++--------------------- compiler/deSugar/DsExpr.hs | 2 +- compiler/deSugar/DsMonad.hs | 24 +- compiler/deSugar/Match.hs | 214 ++++--- compiler/deSugar/MatchLit.hs | 61 ++ compiler/hsSyn/HsLit.hs | 22 + compiler/hsSyn/HsPat.hs | 35 ++ compiler/typecheck/TcMType.hs | 21 + compiler/typecheck/TcRnTypes.hs | 3 +- 9 files changed, 818 insertions(+), 800 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 58220463d0a8c56f314ba4bacb0f9f8ab15d5804 From git at git.haskell.org Thu Jan 8 15:56:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 15:56:20 +0000 (UTC) Subject: [commit: ghc] master: Improve documentation of -fwarn-redundant-constraints (2d15dc7) Message-ID: <20150108155620.B41A43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2d15dc7fa58a6516e75502f511adf077b6360475/ghc >--------------------------------------------------------------- commit 2d15dc7fa58a6516e75502f511adf077b6360475 Author: Simon Peyton Jones Date: Thu Jan 8 13:15:50 2015 +0000 Improve documentation of -fwarn-redundant-constraints >--------------------------------------------------------------- 2d15dc7fa58a6516e75502f511adf077b6360475 docs/users_guide/using.xml | 23 +++++++++++++++++++---- 1 file changed, 19 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 88dbdb7..499e486 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -1418,10 +1418,11 @@ foreign import "&f" f :: FunPtr t redundant constraints, warning - Have the compiler warn about redundant constraints in a type signature. For - example + Have the compiler warn about redundant constraints in a type signature. + In particular: + A redundant constraint within the type signature itself: f :: (Eq a, Ord a) => a -> a @@ -1429,6 +1430,7 @@ foreign import "&f" f :: FunPtr t it is subsumed by the Ord a constraint. + A constraint in the type signature is not used in the code it covers: f :: Eq a => a -> a -> Bool f x y = True @@ -1439,8 +1441,21 @@ foreign import "&f" f :: FunPtr t Similar warnings are given for a redundant constraint in an instance declaration. - - This option is on by default. + This option is on by default. As usual you can suppress it on a per-module basis + with . Occasionally you may specifically + want a function to have a more constrained signature than necessary, perhaps to + leave yourself wiggle-rooom for changing the implementation without changing the + API. In that case, you can suppress the warning on a per-function basis, using a + call in a dead binding. For example: + + f :: Eq a => a -> a -> Bool + f x y = True + where + _ = x == x -- Suppress the redundant-constraint warning for (Eq a) + + Here the call to (==) makes GHC think that the (Eq a) + constraint is needed, so no warning is issued. + From git at git.haskell.org Thu Jan 8 15:56:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 15:56:23 +0000 (UTC) Subject: [commit: ghc] master: Spelling error in comment (43e5a22) Message-ID: <20150108155623.5A2173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/43e5a2216494004d2073a472af13239d004f2ed6/ghc >--------------------------------------------------------------- commit 43e5a2216494004d2073a472af13239d004f2ed6 Author: Simon Peyton Jones Date: Thu Jan 8 13:16:13 2015 +0000 Spelling error in comment >--------------------------------------------------------------- 43e5a2216494004d2073a472af13239d004f2ed6 compiler/rename/RnSource.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index b94f73f..2c9331f 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -90,7 +90,7 @@ rnSrcDecls extra_deps group@(HsGroup { hs_valds = val_decls, = do { -- (A) Process the fixity declarations, creating a mapping from -- FastStrings to FixItems. - -- Also checks for duplcates. + -- Also checks for duplicates. local_fix_env <- makeMiniFixityEnv fix_decls ; -- (B) Bring top level binders (and their fixities) into scope, From git at git.haskell.org Thu Jan 8 15:56:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 15:56:26 +0000 (UTC) Subject: [commit: ghc] master: Improve HsBang (9564bb8) Message-ID: <20150108155626.14DB23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9564bb8c84cbc0397a414e946cc8c28801f0fbe7/ghc >--------------------------------------------------------------- commit 9564bb8c84cbc0397a414e946cc8c28801f0fbe7 Author: Simon Peyton Jones Date: Thu Jan 8 15:54:39 2015 +0000 Improve HsBang Provoked by questions from Johan - Improve comments, fix misleading stuff - Add commented synonyms for HsSrcBang, HsImplBang, and use them throughout - Rename HsUserBang to HsSrcBang - Rename dataConStrictMarks to dataConSrcBangs dataConRepBangs to dataConImplBangs This renaming affects Haddock in a trivial way, hence submodule update >--------------------------------------------------------------- 9564bb8c84cbc0397a414e946cc8c28801f0fbe7 compiler/basicTypes/DataCon.hs | 105 ++++++++++++++++--------- compiler/basicTypes/MkId.hs | 30 +++---- compiler/deSugar/DsMeta.hs | 6 +- compiler/hsSyn/Convert.hs | 4 +- compiler/hsSyn/HsTypes.hs | 10 +-- compiler/iface/BuildTyCl.hs | 2 +- compiler/iface/MkIface.hs | 6 +- compiler/main/GHC.hs | 2 +- compiler/parser/Parser.y | 10 +-- compiler/typecheck/TcExpr.hs | 2 +- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcSplice.hs | 16 ++-- compiler/typecheck/TcTyClsDecls.hs | 10 +-- compiler/vectorise/Vectorise/Type/TyConDecl.hs | 2 +- utils/haddock | 2 +- 15 files changed, 119 insertions(+), 90 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9564bb8c84cbc0397a414e946cc8c28801f0fbe7 From git at git.haskell.org Thu Jan 8 20:01:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 20:01:37 +0000 (UTC) Subject: [commit: ghc] master: Bump haddock.base according to whats observed on ghcspeed (8adc015) Message-ID: <20150108200137.8EE1E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8adc01596614e8711924cb9e4a84ac0dddd6de20/ghc >--------------------------------------------------------------- commit 8adc01596614e8711924cb9e4a84ac0dddd6de20 Author: Joachim Breitner Date: Thu Jan 8 21:02:56 2015 +0100 Bump haddock.base according to whats observed on ghcspeed >--------------------------------------------------------------- 8adc01596614e8711924cb9e4a84ac0dddd6de20 testsuite/tests/perf/haddock/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 905ab91..d50f58b 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -5,7 +5,7 @@ test('haddock.base', [unless(in_tree_compiler(), skip) ,stats_num_field('bytes allocated', - [(wordsize(64), 9502647104, 5) + [(wordsize(64), 9014511528, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -22,6 +22,7 @@ test('haddock.base', # 2014-09-10: 7901230808 (x86_64/Linux - Applicative/Monad changes, according to Joachim) # 2014-10-07: 8322584616 (x86_64/Linux) # 2014-12-14: 9502647104 (x86_64/Linux) - Update to Haddock 2.16 + # 2014-01-08: 9014511528 (x86_64/Linux) - Eliminate so-called "silent superclass parameters" (and others) ,(platform('i386-unknown-mingw32'), 4202377432, 5) # 2013-02-10: 3358693084 (x86/Windows) # 2013-11-13: 3097751052 (x86/Windows, 64bit machine) From git at git.haskell.org Thu Jan 8 21:29:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 21:29:35 +0000 (UTC) Subject: [commit: ghc] master: Recenter T6048 performance numbers (6d32c93) Message-ID: <20150108212935.7467F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6d32c93a3ccbe9bfa98d0d259b371301505a1cf3/ghc >--------------------------------------------------------------- commit 6d32c93a3ccbe9bfa98d0d259b371301505a1cf3 Author: Joachim Breitner Date: Thu Jan 8 22:30:20 2015 +0100 Recenter T6048 performance numbers >--------------------------------------------------------------- 6d32c93a3ccbe9bfa98d0d259b371301505a1cf3 testsuite/tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 10136bb..62fe32a 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -514,7 +514,7 @@ test('T6048', # 2014-09-03: 56315812 (x86 Windows, w/w for INLINEAVBLE) # 2014-12-01: 49987836 (x86 Windows) - (wordsize(64), 88186056, 12)]) + (wordsize(64), 95946688, 12)]) # 18/09/2012 97247032 amd64/Linux # 16/01/2014 108578664 amd64/Linux (unknown, likely foldl-via-foldr) # 18/01/2014 95960720 amd64/Linux Call Arity improvements @@ -523,6 +523,7 @@ test('T6048', # 14/07/2014 125431448 amd64/Linux unknown reason. Even worse in GHC-7.8.3. *shurg* # 29/08/2014 108354472 amd64/Linux w/w for INLINABLE things # 14/09/2014 88186056 amd64/Linux BPP part1 change (more NoImplicitPreludes in base) + # 08/01/2014 95946688 amd64/Linux Mostly 4c834fd. Occasional spikes to 103822120! ], compile,['']) From git at git.haskell.org Thu Jan 8 22:06:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 22:06:35 +0000 (UTC) Subject: [commit: ghc] master: Add 'DeBruijn' constructor, which generalizes "key modulo alpha-renaming." (ccef014) Message-ID: <20150108220635.AA5E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ccef01465366e11978fdad1bf28aeac2edde36c2/ghc >--------------------------------------------------------------- commit ccef01465366e11978fdad1bf28aeac2edde36c2 Author: Edward Z. Yang Date: Wed Jan 7 17:50:42 2015 -0800 Add 'DeBruijn' constructor, which generalizes "key modulo alpha-renaming." Summary: We need equality over Types, etc; and this equality has to be modulo alpha renaming. Previously, we baked CmEnv into the generic "empty, singleton, many" structure. This isn't great, really GenMap should be more generic than that. The insight: we've defined the key wrong: the key should be *equipped* with the alpha-renaming information (CmEnv) and a TrieMap queried with this. This is what the DeBruijn constructor does. Now, when we define TrieMap instances, we don't have to synthesize an emptyCME to pass to the helper functions: we have all the information we need. To make a recursive call, we construct a new DeBruijn with the updated CME and then call lookupTM on that. We can even define a plain old Eq instance on DeBruijn respecting alpha-renaming. There are number of other good knock-on effects. This patch does add a bit of boxing and unboxing, but nothing the optimizer shouldn't be able to eliminate. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D608 GHC Trac Issues: #9960 >--------------------------------------------------------------- ccef01465366e11978fdad1bf28aeac2edde36c2 compiler/coreSyn/TrieMap.hs | 213 ++++++++++++++++++++--------------------- compiler/typecheck/TcSMonad.hs | 11 ++- 2 files changed, 110 insertions(+), 114 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ccef01465366e11978fdad1bf28aeac2edde36c2 From git at git.haskell.org Thu Jan 8 22:06:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Jan 2015 22:06:38 +0000 (UTC) Subject: [commit: ghc] master: Apply GenMap to CoreMap and CoercionMap. (0bef02e) Message-ID: <20150108220638.6C5F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0bef02e49fb2907989127d77ae61ed48ba87ae18/ghc >--------------------------------------------------------------- commit 0bef02e49fb2907989127d77ae61ed48ba87ae18 Author: Edward Z. Yang Date: Wed Jan 7 19:13:28 2015 -0800 Apply GenMap to CoreMap and CoercionMap. Summary: The biggest chore is the Eq (DeBrujin a) instances (all the more a chore because we already have an implementation of them, but a CmEnv is not an RnEnv2), but otherwise a fairly mechanical transformation. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D609 GHC Trac Issues: #9960 >--------------------------------------------------------------- 0bef02e49fb2907989127d77ae61ed48ba87ae18 compiler/coreSyn/TrieMap.hs | 262 +++++++++++++++++++++++++++++++------------- 1 file changed, 183 insertions(+), 79 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0bef02e49fb2907989127d77ae61ed48ba87ae18 From git at git.haskell.org Fri Jan 9 10:07:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 10:07:27 +0000 (UTC) Subject: [commit: ghc] master: Return a [HsImplBang] from dataConImplBangs even with NoDataConRep (327ce1d) Message-ID: <20150109100727.846253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/327ce1d336c8fbdb068be900a187f96d1c60b851/ghc >--------------------------------------------------------------- commit 327ce1d336c8fbdb068be900a187f96d1c60b851 Author: Simon Peyton Jones Date: Fri Jan 9 09:46:37 2015 +0000 Return a [HsImplBang] from dataConImplBangs even with NoDataConRep This fixes Trac #9969, a new crash in T7562 that I somehow missed when fiddling with HsBang >--------------------------------------------------------------- 327ce1d336c8fbdb068be900a187f96d1c60b851 compiler/basicTypes/DataCon.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs index e77af96..3f27acd 100644 --- a/compiler/basicTypes/DataCon.hs +++ b/compiler/basicTypes/DataCon.hs @@ -830,9 +830,10 @@ dataConRepStrictness dc = case dcRep dc of dataConImplBangs :: DataCon -> [HsImplBang] -- The implementation decisions about the strictness/unpack of each -- source program argument to the data constructor -dataConImplBangs dc = case dcRep dc of - NoDataConRep -> dcSrcBangs dc - DCR { dcr_bangs = bangs } -> bangs +dataConImplBangs dc + = case dcRep dc of + NoDataConRep -> replicate (dcSourceArity dc) HsNoBang + DCR { dcr_bangs = bangs } -> bangs dataConBoxer :: DataCon -> Maybe DataConBoxer dataConBoxer (MkData { dcRep = DCR { dcr_boxer = boxer } }) = Just boxer From git at git.haskell.org Fri Jan 9 10:07:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 10:07:30 +0000 (UTC) Subject: [commit: ghc] master: Make TcRnMonad.reportWarning call makeIntoWarning (dfe62eb) Message-ID: <20150109100730.39F9D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dfe62eb05feab7ec4acb31bcd12fb68028eebcda/ghc >--------------------------------------------------------------- commit dfe62eb05feab7ec4acb31bcd12fb68028eebcda Author: Simon Peyton Jones Date: Fri Jan 9 09:47:57 2015 +0000 Make TcRnMonad.reportWarning call makeIntoWarning Previously the caller had do to that, and sometimes forgot >--------------------------------------------------------------- dfe62eb05feab7ec4acb31bcd12fb68028eebcda compiler/typecheck/TcBinds.hs | 2 +- compiler/typecheck/TcErrors.hs | 8 ++++---- compiler/typecheck/TcRnMonad.hs | 15 ++++++++++----- testsuite/tests/typecheck/should_compile/T9939.stderr | 8 ++++---- testsuite/tests/typecheck/should_compile/tc056.stderr | 2 +- 5 files changed, 20 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index 7d66d16..50bc62d 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -751,7 +751,7 @@ completeTheta inferred_theta ; warn_partial_sigs <- woptM Opt_WarnPartialTypeSignatures ; msg <- mkLongErrAt loc (mk_msg inferred_diff partial_sigs) empty ; case partial_sigs of - True | warn_partial_sigs -> reportWarning $ makeIntoWarning msg + True | warn_partial_sigs -> reportWarning msg | otherwise -> return () False -> reportError msg ; return final_theta } diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 21adab4..31772a2 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -32,7 +32,7 @@ import VarSet import VarEnv import NameEnv import Bag -import ErrUtils ( ErrMsg, makeIntoWarning, pprLocErrMsg ) +import ErrUtils ( ErrMsg, pprLocErrMsg ) import BasicTypes import Util import FastString @@ -418,7 +418,7 @@ maybeReportHoleError ctxt ct err -- only if -fwarn_partial_type_signatures is on case cec_type_holes ctxt of HoleError -> reportError err - HoleWarn -> reportWarning (makeIntoWarning err) + HoleWarn -> reportWarning err HoleDefer -> return () -- Otherwise this is a typed hole in an expression @@ -426,7 +426,7 @@ maybeReportHoleError ctxt ct err = -- If deferring, report a warning only if -fwarn-typed-holds is on case cec_expr_holes ctxt of HoleError -> reportError err - HoleWarn -> reportWarning (makeIntoWarning err) + HoleWarn -> reportWarning err HoleDefer -> return () maybeReportError :: ReportErrCtxt -> ErrMsg -> TcM () @@ -434,7 +434,7 @@ maybeReportError :: ReportErrCtxt -> ErrMsg -> TcM () maybeReportError ctxt err -- See Note [Always warn with -fdefer-type-errors] | cec_defer_type_errors ctxt - = reportWarning (makeIntoWarning err) + = reportWarning err | cec_suppress ctxt = return () | otherwise diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index 0f98726..b7038ec 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -753,11 +753,16 @@ reportError err writeTcRef errs_var (warns, errs `snocBag` err) } reportWarning :: ErrMsg -> TcRn () -reportWarning warn - = do { traceTc "Adding warning:" (pprLocErrMsg warn) ; - errs_var <- getErrsVar ; - (warns, errs) <- readTcRef errs_var ; - writeTcRef errs_var (warns `snocBag` warn, errs) } +reportWarning err + = do { let warn = makeIntoWarning err + -- 'err' was build by mkLongErrMsg or something like that, + -- so it's of error severity. For a warning we downgrade + -- its severity to SevWarning + + ; traceTc "Adding warning:" (pprLocErrMsg warn) + ; errs_var <- getErrsVar + ; (warns, errs) <- readTcRef errs_var + ; writeTcRef errs_var (warns `snocBag` warn, errs) } try_m :: TcRn r -> TcRn (Either IOEnvFailure r) -- Does try_m, with a debug-trace on failure diff --git a/testsuite/tests/typecheck/should_compile/T9939.stderr b/testsuite/tests/typecheck/should_compile/T9939.stderr index 946fba9..eda780a 100644 --- a/testsuite/tests/typecheck/should_compile/T9939.stderr +++ b/testsuite/tests/typecheck/should_compile/T9939.stderr @@ -1,18 +1,18 @@ -T9939.hs:5:7: +T9939.hs:5:7: Warning: Redundant constraint: Eq a In the type signature for: f1 :: (Eq a, Ord a) => a -> a -> Bool -T9939.hs:9:7: +T9939.hs:9:7: Warning: Redundant constraint: Eq a In the type signature for: f2 :: (Eq a, Ord a) => a -> a -> Bool -T9939.hs:13:7: +T9939.hs:13:7: Warning: Redundant constraint: Eq b In the type signature for: f3 :: (Eq a, a ~ b, Eq b) => a -> b -> Bool -T9939.hs:20:7: +T9939.hs:20:7: Warning: Redundant constraint: Eq b In the type signature for: f4 :: (Eq a, Eq b) => a -> b -> Equal a b -> Bool diff --git a/testsuite/tests/typecheck/should_compile/tc056.stderr b/testsuite/tests/typecheck/should_compile/tc056.stderr index 11641ff..a6f7cd4 100644 --- a/testsuite/tests/typecheck/should_compile/tc056.stderr +++ b/testsuite/tests/typecheck/should_compile/tc056.stderr @@ -1,4 +1,4 @@ -tc056.hs:16:10: +tc056.hs:16:10: Warning: Redundant constraints: (Eq' a, Eq' a) In the instance declaration for ?Eq' [a]? From git at git.haskell.org Fri Jan 9 10:07:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 10:07:33 +0000 (UTC) Subject: [commit: ghc] master: A little tidying up in ErrUtils (4425ab9) Message-ID: <20150109100733.06B2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4425ab99d6410839fa7567950b0a4696b0a3d70f/ghc >--------------------------------------------------------------- commit 4425ab99d6410839fa7567950b0a4696b0a3d70f Author: Simon Peyton Jones Date: Fri Jan 9 10:07:02 2015 +0000 A little tidying up in ErrUtils This module is a disorganised mess. For example, there is literally *no* documentation of what the *seven* different forms of 'Severity' are intended to connote. Anyway this patch makes a tiny step by not exporting unused functions pprMsgBag and isWarning, and a little bit of internal refactoring >--------------------------------------------------------------- 4425ab99d6410839fa7567950b0a4696b0a3d70f compiler/main/ErrUtils.hs | 59 ++++++++++++++++++----------------------------- 1 file changed, 23 insertions(+), 36 deletions(-) diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index 59bc01b..20d628f 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -13,8 +13,8 @@ module ErrUtils ( ErrMsg, WarnMsg, Severity(..), Messages, ErrorMessages, WarningMessages, errMsgSpan, errMsgContext, errMsgShortDoc, errMsgExtraInfo, - mkLocMessage, pprMessageBag, pprErrMsgBag, pprErrMsgBagWithLoc, - pprLocErrMsg, makeIntoWarning, isWarning, + mkLocMessage, pprMessageBag, pprErrMsgBagWithLoc, + pprLocErrMsg, makeIntoWarning, errorsFound, emptyMessages, isEmptyMessages, mkErrMsg, mkPlainErrMsg, mkLongErrMsg, mkWarnMsg, mkPlainWarnMsg, @@ -91,12 +91,12 @@ type WarningMessages = Bag WarnMsg type ErrorMessages = Bag ErrMsg data ErrMsg = ErrMsg { - errMsgSpan :: SrcSpan, - errMsgContext :: PrintUnqualified, - errMsgShortDoc :: MsgDoc, -- errMsgShort* should always - errMsgShortString :: String, -- contain the same text - errMsgExtraInfo :: MsgDoc, - errMsgSeverity :: Severity + errMsgSpan :: SrcSpan, + errMsgContext :: PrintUnqualified, + errMsgShortDoc :: MsgDoc, -- errMsgShort* should always + errMsgShortString :: String, -- contain the same text + errMsgExtraInfo :: MsgDoc, + errMsgSeverity :: Severity } -- The SrcSpan is used for sorting errors into line-number order @@ -111,6 +111,10 @@ data Severity | SevError | SevFatal +isWarning :: Severity -> Bool +isWarning SevWarning = True +isWarning _ = False + instance Show ErrMsg where show em = errMsgShortString em @@ -128,19 +132,14 @@ mkLocMessage severity locn msg else ppr (srcSpanStart locn) in hang (locn' <> colon <+> sev_info) 4 msg where - sev_info = case severity of - SevWarning -> ptext (sLit "Warning:") - _other -> empty + sev_info = ppWhen (isWarning severity) + (ptext (sLit "Warning:")) -- For warnings, print Foo.hs:34: Warning: -- makeIntoWarning :: ErrMsg -> ErrMsg makeIntoWarning err = err { errMsgSeverity = SevWarning } -isWarning :: ErrMsg -> Bool -isWarning err - | SevWarning <- errMsgSeverity err = True - | otherwise = False -- ----------------------------------------------------------------------------- -- Collecting up messages for later ordering and printing. @@ -181,16 +180,13 @@ errorsFound _dflags (_warns, errs) = not (isEmptyBag errs) printBagOfErrors :: DynFlags -> Bag ErrMsg -> IO () printBagOfErrors dflags bag_of_errors - = printMsgBag dflags bag_of_errors - -pprErrMsgBag :: Bag ErrMsg -> [SDoc] -pprErrMsgBag bag - = [ sdocWithDynFlags $ \dflags -> - let style = mkErrStyle dflags unqual - in withPprStyle style (d $$ e) - | ErrMsg { errMsgShortDoc = d, - errMsgExtraInfo = e, - errMsgContext = unqual } <- sortMsgBag bag ] + = sequence_ [ let style = mkErrStyle dflags unqual + in log_action dflags dflags sev s style (d $$ e) + | ErrMsg { errMsgSpan = s, + errMsgShortDoc = d, + errMsgSeverity = sev, + errMsgExtraInfo = e, + errMsgContext = unqual } <- sortMsgBag bag_of_errors ] pprErrMsgBagWithLoc :: Bag ErrMsg -> [SDoc] pprErrMsgBagWithLoc bag = [ pprLocErrMsg item | item <- sortMsgBag bag ] @@ -202,17 +198,8 @@ pprLocErrMsg (ErrMsg { errMsgSpan = s , errMsgSeverity = sev , errMsgContext = unqual }) = sdocWithDynFlags $ \dflags -> - withPprStyle (mkErrStyle dflags unqual) (mkLocMessage sev s (d $$ e)) - -printMsgBag :: DynFlags -> Bag ErrMsg -> IO () -printMsgBag dflags bag - = sequence_ [ let style = mkErrStyle dflags unqual - in log_action dflags dflags sev s style (d $$ e) - | ErrMsg { errMsgSpan = s, - errMsgShortDoc = d, - errMsgSeverity = sev, - errMsgExtraInfo = e, - errMsgContext = unqual } <- sortMsgBag bag ] + withPprStyle (mkErrStyle dflags unqual) $ + mkLocMessage sev s (d $$ e) sortMsgBag :: Bag ErrMsg -> [ErrMsg] sortMsgBag bag = sortBy (comparing errMsgSpan) $ bagToList bag From git at git.haskell.org Fri Jan 9 11:32:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 11:32:58 +0000 (UTC) Subject: [commit: ghc] master: Update syntax of pattern synonym type signature in documentation (fixes #9967) (68a5a78) Message-ID: <20150109113258.3EDD03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/68a5a784e71b7535aa7d739bf1b003e96267a021/ghc >--------------------------------------------------------------- commit 68a5a784e71b7535aa7d739bf1b003e96267a021 Author: Dr. ERDI Gergo Date: Fri Jan 9 19:29:28 2015 +0800 Update syntax of pattern synonym type signature in documentation (fixes #9967) >--------------------------------------------------------------- 68a5a784e71b7535aa7d739bf1b003e96267a021 docs/users_guide/glasgow_exts.xml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 424064e..0503561 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -1088,7 +1088,8 @@ would bring into scope the data constructor Just from the CReq are type contexts, and t1, t2, ..., tN and t are - types. + types. If CReq is empty + (()) it can be omitted. @@ -1118,7 +1119,7 @@ the inferred pattern type of ExNumPat is -pattern (Show b) => ExNumPat b :: (Num a, Eq a) => T a +pattern ExNumPat :: (Show b) => (Num a, Eq a) => b -> T a From git at git.haskell.org Fri Jan 9 11:33:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 11:33:00 +0000 (UTC) Subject: [commit: ghc] master: Pattern synonyms do work in GHCi now (see #9900) (6f818e0) Message-ID: <20150109113300.DD9153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6f818e083c8390b0c039bcebb6ec21b336d4173b/ghc >--------------------------------------------------------------- commit 6f818e083c8390b0c039bcebb6ec21b336d4173b Author: Dr. ERDI Gergo Date: Fri Jan 9 19:30:04 2015 +0800 Pattern synonyms do work in GHCi now (see #9900) >--------------------------------------------------------------- 6f818e083c8390b0c039bcebb6ec21b336d4173b docs/users_guide/glasgow_exts.xml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 0503561..61ab799 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -1025,8 +1025,7 @@ bidirectional. The syntax for unidirectional pattern synonyms is: Pattern synonym declarations can only occur in the top level of a module. In particular, they are not allowed as local - definitions. Currently, they also don't work in GHCi, but that is a - technical restriction that will be lifted in later versions. + definitions. The variables in the left-hand side of the definition are bound by From git at git.haskell.org Fri Jan 9 11:50:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 11:50:56 +0000 (UTC) Subject: [commit: ghc] master: Comments only (ee4ced4) Message-ID: <20150109115056.D650E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ee4ced43437391a6532a74211c8cab5ed27f2230/ghc >--------------------------------------------------------------- commit ee4ced43437391a6532a74211c8cab5ed27f2230 Author: Simon Peyton Jones Date: Fri Jan 9 10:53:26 2015 +0000 Comments only >--------------------------------------------------------------- ee4ced43437391a6532a74211c8cab5ed27f2230 compiler/main/GHC.hs | 1 + compiler/main/GhcMonad.hs | 2 ++ compiler/utils/Maybes.hs | 1 + 3 files changed, 4 insertions(+) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 2557ec4..877ae74 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -433,6 +433,7 @@ runGhc mb_top_dir ghc = do -- several threads. #if __GLASGOW_HASKELL__ < 710 +-- Pre-AMP change runGhcT :: (ExceptionMonad m, Functor m) => #else runGhcT :: (ExceptionMonad m) => diff --git a/compiler/main/GhcMonad.hs b/compiler/main/GhcMonad.hs index 6a3e107..5b2e422 100644 --- a/compiler/main/GhcMonad.hs +++ b/compiler/main/GhcMonad.hs @@ -185,6 +185,7 @@ instance ExceptionMonad m => ExceptionMonad (GhcT m) where unGhcT (f g_restore) s #if __GLASGOW_HASKELL__ < 710 +-- Pre-AMP change instance (ExceptionMonad m, Functor m) => HasDynFlags (GhcT m) where #else instance (ExceptionMonad m) => HasDynFlags (GhcT m) where @@ -192,6 +193,7 @@ instance (ExceptionMonad m) => HasDynFlags (GhcT m) where getDynFlags = getSessionDynFlags #if __GLASGOW_HASKELL__ < 710 +-- Pre-AMP change instance (ExceptionMonad m, Functor m) => GhcMonad (GhcT m) where #else instance (ExceptionMonad m) => GhcMonad (GhcT m) where diff --git a/compiler/utils/Maybes.hs b/compiler/utils/Maybes.hs index f5083fd..a2ddbdf 100644 --- a/compiler/utils/Maybes.hs +++ b/compiler/utils/Maybes.hs @@ -68,6 +68,7 @@ instance Functor m => Functor (MaybeT m) where fmap f x = MaybeT $ fmap (fmap f) $ runMaybeT x #if __GLASGOW_HASKELL__ < 710 +-- Pre-AMP change instance (Monad m, Functor m) => Applicative (MaybeT m) where #else instance (Monad m) => Applicative (MaybeT m) where From git at git.haskell.org Fri Jan 9 11:50:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 11:50:59 +0000 (UTC) Subject: [commit: ghc] master: A little tidying up in the flattener (3d44911) Message-ID: <20150109115059.8555E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3d449110fd992dc8ccbeb21f4bf8e522a57c2e22/ghc >--------------------------------------------------------------- commit 3d449110fd992dc8ccbeb21f4bf8e522a57c2e22 Author: Simon Peyton Jones Date: Fri Jan 9 11:51:52 2015 +0000 A little tidying up in the flattener Particularly, flatten_many was exported, but the caller was not doing runFlatten. Moreover it was always used at nominal role. This patch makes the API clearer, and more robust >--------------------------------------------------------------- 3d449110fd992dc8ccbeb21f4bf8e522a57c2e22 compiler/typecheck/TcCanonical.hs | 7 +- compiler/typecheck/TcFlatten.hs | 293 ++++++++++++++++++++------------------ compiler/typecheck/TcInteract.hs | 12 +- compiler/typecheck/TcRnTypes.hs | 6 +- 4 files changed, 166 insertions(+), 152 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3d449110fd992dc8ccbeb21f4bf8e522a57c2e22 From git at git.haskell.org Fri Jan 9 12:59:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 12:59:10 +0000 (UTC) Subject: [commit: ghc] master: Fix up test for T7861 (678df4c) Message-ID: <20150109125910.BD2263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/678df4c2930c4aef61b083edb0f5c4d8c8914a76/ghc >--------------------------------------------------------------- commit 678df4c2930c4aef61b083edb0f5c4d8c8914a76 Author: Simon Peyton Jones Date: Fri Jan 9 13:00:16 2015 +0000 Fix up test for T7861 Fixes Trac #9972 >--------------------------------------------------------------- 678df4c2930c4aef61b083edb0f5c4d8c8914a76 testsuite/tests/typecheck/should_run/T7861.hs | 10 +++++++++- testsuite/tests/typecheck/should_run/T7861.stderr | 2 +- testsuite/tests/typecheck/should_run/T7861.stdout | 3 ++- 3 files changed, 12 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/typecheck/should_run/T7861.hs b/testsuite/tests/typecheck/should_run/T7861.hs index 1f2066c..9ff9a43 100644 --- a/testsuite/tests/typecheck/should_run/T7861.hs +++ b/testsuite/tests/typecheck/should_run/T7861.hs @@ -10,4 +10,12 @@ doA = undefined f :: A a -> a f = doA -main = do { print "Hello"; f `seq` print "Bad" } +main = do { print "Hello 1" + + ; f `seq` print "Hello 2" + -- The casts are pushed inside the lambda + -- for f, so this seq succeds fine + + ; f (error "urk") `seq` print "Bad" + -- But when we *call* f we get a type error + } diff --git a/testsuite/tests/typecheck/should_run/T7861.stderr b/testsuite/tests/typecheck/should_run/T7861.stderr index b3e3140..f9f2386 100644 --- a/testsuite/tests/typecheck/should_run/T7861.stderr +++ b/testsuite/tests/typecheck/should_run/T7861.stderr @@ -1,7 +1,7 @@ T7861: T7861.hs:11:5: Couldn't match type ?a? with ?[a]? ?a? is a rigid type variable bound by - the type signature for f :: A a -> a at T7861.hs:10:6 + the type signature for: f :: A a -> a at T7861.hs:10:6 Expected type: A a -> a Actual type: A a -> [a] Relevant bindings include f :: A a -> a (bound at T7861.hs:11:1) diff --git a/testsuite/tests/typecheck/should_run/T7861.stdout b/testsuite/tests/typecheck/should_run/T7861.stdout index 4b849db..6578f43 100644 --- a/testsuite/tests/typecheck/should_run/T7861.stdout +++ b/testsuite/tests/typecheck/should_run/T7861.stdout @@ -1 +1,2 @@ -"Hello" +"Hello 1" +"Hello 2" From git at git.haskell.org Fri Jan 9 14:14:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 14:14:21 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Cabal submodule to 1.22.0.0 release tag (ab69f9f) Message-ID: <20150109141421.989683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/ab69f9f223f3e31071a9982fd73b030c2a44f36b/ghc >--------------------------------------------------------------- commit ab69f9f223f3e31071a9982fd73b030c2a44f36b Author: Herbert Valerio Riedel Date: Fri Jan 9 15:12:10 2015 +0100 Update Cabal submodule to 1.22.0.0 release tag >--------------------------------------------------------------- ab69f9f223f3e31071a9982fd73b030c2a44f36b libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 3a7f901..f71044b 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 3a7f9015828745932a65d95fa985c98073fc7d95 +Subproject commit f71044bb1f79f8a0b2f6926b1c04a9592932f1ee From git at git.haskell.org Fri Jan 9 14:14:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 14:14:24 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Release note entry for `-fdefer-typed-holes` (23a38fe) Message-ID: <20150109141424.45DC43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/23a38fe45b0b8afa4df3636d1ed4089c14782e9e/ghc >--------------------------------------------------------------- commit 23a38fe45b0b8afa4df3636d1ed4089c14782e9e Author: Merijn Verstraaten Date: Fri Jan 9 15:14:38 2015 +0100 Release note entry for `-fdefer-typed-holes` >--------------------------------------------------------------- 23a38fe45b0b8afa4df3636d1ed4089c14782e9e docs/users_guide/7.10.1-notes.xml | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 58d7bdf..22b1242 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -117,6 +117,23 @@ + The new flag turns + typed hole errors into typed hole warnings that produce + runtime errors when evaluated. + + The flag was + repurposed to silence the warnings produced when + is used. As a result, + it is no longer possible to disable typed holes like it was + in GHC 7.8. This only turned a self-explanatory error into + a cryptic parse error and was thus not very useful. + + For more details, consult and + . + + + + A new warning flag, has been added and is turned on with . It warns when a module that is From git at git.haskell.org Fri Jan 9 14:19:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 14:19:55 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix `heapSizeSuggesionAuto` typo (#9934) (224a48e) Message-ID: <20150109141955.34FF03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/224a48ebc1e4f6fb373884a6ae1de81b11a3f383/ghc >--------------------------------------------------------------- commit 224a48ebc1e4f6fb373884a6ae1de81b11a3f383 Author: Herbert Valerio Riedel Date: Mon Dec 29 09:14:05 2014 +0100 Fix `heapSizeSuggesionAuto` typo (#9934) This was introduced in 1617a10a (re #5364) (cherry picked from commit 40561cd235f07d41904d2604ff7f0c942af4d35e) >--------------------------------------------------------------- 224a48ebc1e4f6fb373884a6ae1de81b11a3f383 libraries/base/GHC/RTS/Flags.hsc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/RTS/Flags.hsc b/libraries/base/GHC/RTS/Flags.hsc index ff1bf69..16764e5 100644 --- a/libraries/base/GHC/RTS/Flags.hsc +++ b/libraries/base/GHC/RTS/Flags.hsc @@ -86,7 +86,7 @@ data GCFlags = GCFlags , minAllocAreaSize :: Nat , minOldGenSize :: Nat , heapSizeSuggestion :: Nat - , heapSizeSuggesionAuto :: Bool + , heapSizeSuggestionAuto :: Bool , oldGenFactor :: Double , pcFreeHeap :: Double , generations :: Nat From git at git.haskell.org Fri Jan 9 14:28:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 14:28:20 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update syntax of pattern synonym type signature in documentation (fixes #9967) (44815dd) Message-ID: <20150109142820.C0D183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/44815ddbf4f682067c50704dd8920b0e56d8238c/ghc >--------------------------------------------------------------- commit 44815ddbf4f682067c50704dd8920b0e56d8238c Author: Dr. ERDI Gergo Date: Fri Jan 9 19:29:28 2015 +0800 Update syntax of pattern synonym type signature in documentation (fixes #9967) (cherry picked from commit 68a5a784e71b7535aa7d739bf1b003e96267a021) >--------------------------------------------------------------- 44815ddbf4f682067c50704dd8920b0e56d8238c docs/users_guide/glasgow_exts.xml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 44577f9..96e3d28 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -1088,7 +1088,8 @@ would bring into scope the data constructor Just from the CReq are type contexts, and t1, t2, ..., tN and t are - types. + types. If CReq is empty + (()) it can be omitted. @@ -1118,7 +1119,7 @@ the inferred pattern type of ExNumPat is -pattern (Show b) => ExNumPat b :: (Num a, Eq a) => T a +pattern ExNumPat :: (Show b) => (Num a, Eq a) => b -> T a From git at git.haskell.org Fri Jan 9 14:31:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 14:31:16 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix system linker on Mac OS X (ee20cbf) Message-ID: <20150109143116.1D4DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/ee20cbf547e8d7651f94ce7516f088dabc872a3e/ghc >--------------------------------------------------------------- commit ee20cbf547e8d7651f94ce7516f088dabc872a3e Author: Peter Trommler Date: Mon Dec 29 11:33:24 2014 -0500 Fix system linker on Mac OS X Summary: Flag `-l:` is GNU ld specific and not supported by the Mac OS X link editor. So we create a temporary file name lib. and link with the standard -l option on Linux and OS X. Fixes #9875 Test Plan: validate on Mac OS X Reviewers: austin, hvr, ezyang Reviewed By: ezyang Subscribers: carter, thomie, ezyang Differential Revision: https://phabricator.haskell.org/D579 GHC Trac Issues: #9875 (cherry picked from commit b32c22760687a6a1a2e88fdba8de32f6951b5029) >--------------------------------------------------------------- ee20cbf547e8d7651f94ce7516f088dabc872a3e compiler/ghci/Linker.hs | 11 +++++------ compiler/main/SysTools.hs | 20 +++++++++++++++++++- 2 files changed, 24 insertions(+), 7 deletions(-) diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index 3a91fc1..91706da 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -120,7 +120,7 @@ data PersistentLinkerState -- we need to remember the name of the last temporary DLL/.so -- so we can link it - last_temp_so :: !(Maybe FilePath) } + last_temp_so :: !(Maybe (FilePath, String)) } emptyPLS :: DynFlags -> PersistentLinkerState @@ -818,7 +818,7 @@ dynLoadObjs :: DynFlags -> PersistentLinkerState -> [FilePath] dynLoadObjs _ pls [] = return pls dynLoadObjs dflags pls objs = do let platform = targetPlatform dflags - soFile <- newTempName dflags (soExt platform) + (soFile, libPath , libName) <- newTempLibName dflags (soExt platform) let -- When running TH for a non-dynamic way, we still need to make -- -l flags to link against the dynamic libraries, so we turn -- Opt_Static off @@ -833,12 +833,11 @@ dynLoadObjs dflags pls objs = do ldInputs = case last_temp_so pls of Nothing -> [] - Just so -> - let (lp, l) = splitFileName so in + Just (lp, l) -> [ Option ("-L" ++ lp) , Option ("-Wl,-rpath") , Option ("-Wl," ++ lp) - , Option ("-l:" ++ l) + , Option ("-l" ++ l) ], -- Even if we're e.g. profiling, we still want -- the vanilla dynamic libraries, so we set the @@ -851,7 +850,7 @@ dynLoadObjs dflags pls objs = do consIORef (filesToNotIntermediateClean dflags) soFile m <- loadDLL soFile case m of - Nothing -> return pls { last_temp_so = Just soFile } + Nothing -> return pls { last_temp_so = Just (libPath, libName) } Just err -> panic ("Loading temp shared object failed: " ++ err) rmDupLinkables :: [Linkable] -- Already loaded diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index 7b6c82f..af80051 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -40,7 +40,7 @@ module SysTools ( -- Temporary-file management setTmpDir, - newTempName, + newTempName, newTempLibName, cleanTempDirs, cleanTempFiles, cleanTempFilesExcept, addFilesToClean, @@ -1075,6 +1075,24 @@ newTempName dflags extn consIORef (filesToClean dflags) filename return filename +newTempLibName :: DynFlags -> Suffix -> IO (FilePath, FilePath, String) +newTempLibName dflags extn + = do d <- getTempDir dflags + x <- getProcessID + findTempName d ("ghc" ++ show x ++ "_") + where + findTempName :: FilePath -> String -> IO (FilePath, FilePath, String) + findTempName dir prefix + = do n <- newTempSuffix dflags + let libname = prefix ++ show n + filename = dir "lib" ++ libname <.> extn + b <- doesFileExist filename + if b then findTempName dir prefix + else do -- clean it up later + consIORef (filesToClean dflags) filename + return (filename, dir, libname) + + -- Return our temporary directory within tmp_dir, creating one if we -- don't have one yet. getTempDir :: DynFlags -> IO FilePath From git at git.haskell.org Fri Jan 9 15:22:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 15:22:01 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Support pattern synonyms in GHCi (fixes #9900) (14c198b) Message-ID: <20150109152201.C24913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/14c198b41ded6a172a52ec02a39f0933f6676f47/ghc >--------------------------------------------------------------- commit 14c198b41ded6a172a52ec02a39f0933f6676f47 Author: Dr. ERDI Gergo Date: Sun Dec 28 11:51:00 2014 +0800 Support pattern synonyms in GHCi (fixes #9900) This involves recognizing lines starting with `"pattern "` as declarations, keeping non-exported pattern synonyms in `deSugar`, and including pattern synonyms in the result of `hscDeclsWithLocation`. (cherry picked from commit 0cc0cc8688ddb53db65a73d7d562e9564cfad22b) >--------------------------------------------------------------- 14c198b41ded6a172a52ec02a39f0933f6676f47 compiler/deSugar/Desugar.hs | 3 +-- compiler/main/HscMain.hs | 6 ++++-- compiler/main/HscTypes.hs | 5 +++-- ghc/InteractiveUI.hs | 1 + testsuite/tests/patsyn/should_run/all.T | 5 +++++ testsuite/tests/patsyn/should_run/ghci.script | 8 ++++++++ testsuite/tests/patsyn/should_run/ghci.stderr | 2 ++ testsuite/tests/patsyn/should_run/ghci.stdout | 3 +++ 8 files changed, 27 insertions(+), 6 deletions(-) diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index ac35464..70fa88e 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -24,7 +24,6 @@ import Coercion import InstEnv import Class import Avail -import PatSyn import CoreSyn import CoreSubst import PprCore @@ -184,7 +183,7 @@ deSugar hsc_env mg_fam_insts = fam_insts, mg_inst_env = inst_env, mg_fam_inst_env = fam_inst_env, - mg_patsyns = filter ((`elemNameSet` export_set) . patSynName) patsyns, + mg_patsyns = patsyns, mg_rules = ds_rules_for_imps, mg_binds = ds_binds, mg_foreign = ds_fords, diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index c5cb9a1..4fe74c6 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -97,6 +97,7 @@ import CoreLint ( lintInteractiveExpr ) import DsMeta ( templateHaskellNames ) import VarEnv ( emptyTidyEnv ) import Panic +import ConLike import GHC.Exts #endif @@ -1505,6 +1506,7 @@ hscDeclsWithLocation hsc_env0 str source linenumber = liftIO $ linkDecls hsc_env src_span cbc let tcs = filterOut isImplicitTyCon (mg_tcs simpl_mg) + patsyns = mg_patsyns simpl_mg ext_ids = [ id | id <- bindersOfBinds core_binds , isExternalName (idName id) @@ -1515,11 +1517,11 @@ hscDeclsWithLocation hsc_env0 str source linenumber = -- The DFunIds are in 'cls_insts' (see Note [ic_tythings] in HscTypes -- Implicit Ids are implicit in tcs - tythings = map AnId ext_ids ++ map ATyCon tcs + tythings = map AnId ext_ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) patsyns let icontext = hsc_IC hsc_env ictxt = extendInteractiveContext icontext ext_ids tcs - cls_insts fam_insts defaults + cls_insts fam_insts defaults patsyns return (tythings, ictxt) hscImport :: HscEnv -> String -> IO (ImportDecl RdrName) diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 909004e..29ee78c 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -1403,8 +1403,9 @@ extendInteractiveContext :: InteractiveContext -> [Id] -> [TyCon] -> [ClsInst] -> [FamInst] -> Maybe [Type] + -> [PatSyn] -> InteractiveContext -extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults +extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults new_patsyns = ictxt { ic_mod_index = ic_mod_index ictxt + 1 -- Always bump this; even instances should create -- a new mod_index (Trac #9426) @@ -1413,7 +1414,7 @@ extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults , ic_instances = (new_cls_insts ++ old_cls_insts, new_fam_insts ++ old_fam_insts) , ic_default = defaults } where - new_tythings = map AnId ids ++ map ATyCon tcs + new_tythings = map AnId ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) new_patsyns old_tythings = filterOut (shadowed_by ids) (ic_tythings ictxt) -- Discard old instances that have been fully overrridden diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index ce73c48..7310dca 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -892,6 +892,7 @@ declPrefixes dflags = keywords ++ concat opt_keywords opt_keywords = [ ["foreign " | xopt Opt_ForeignFunctionInterface dflags] , ["deriving " | xopt Opt_StandaloneDeriving dflags] + , ["pattern " | xopt Opt_PatternSynonyms dflags] ] -- | Entry point to execute some haskell code from user. diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index 40ec3e3..2f496a6 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -1,3 +1,7 @@ +# We only want to run these tests with GHCi +def just_ghci( name, opts ): + opts.only_ways = ['ghci'] + test('eval', normal, compile_and_run, ['']) test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) @@ -6,3 +10,4 @@ test('bidir-explicit-scope', normal, compile_and_run, ['']) test('T9783', normal, compile_and_run, ['']) test('match-unboxed', normal, compile_and_run, ['']) test('unboxed-wrapper', normal, compile_and_run, ['']) +test('ghci', just_ghci, ghci_script, ['ghci.script']) diff --git a/testsuite/tests/patsyn/should_run/ghci.script b/testsuite/tests/patsyn/should_run/ghci.script new file mode 100644 index 0000000..cd71e33 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.script @@ -0,0 +1,8 @@ +:set -XPatternSynonyms + +pattern Single x = [x] +:i Single +let foo (Single x) = Single (not x) +:t foo +foo [True] +foo [True, False] diff --git a/testsuite/tests/patsyn/should_run/ghci.stderr b/testsuite/tests/patsyn/should_run/ghci.stderr new file mode 100644 index 0000000..9593b15 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.stderr @@ -0,0 +1,2 @@ +*** Exception: :6:5-35: Non-exhaustive patterns in function foo + diff --git a/testsuite/tests/patsyn/should_run/ghci.stdout b/testsuite/tests/patsyn/should_run/ghci.stdout new file mode 100644 index 0000000..796aa72 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.stdout @@ -0,0 +1,3 @@ +pattern Single :: t -> [t] -- Defined at :4:9 +foo :: [Bool] -> [Bool] +[False] From git at git.haskell.org Fri Jan 9 15:22:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 15:22:04 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Pattern synonyms do work in GHCi now (see #9900) (1f59f9a) Message-ID: <20150109152204.7F71E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/1f59f9a218d85ca1e8a13b3fdf6f4ed0d6fcb7e7/ghc >--------------------------------------------------------------- commit 1f59f9a218d85ca1e8a13b3fdf6f4ed0d6fcb7e7 Author: Dr. ERDI Gergo Date: Fri Jan 9 19:30:04 2015 +0800 Pattern synonyms do work in GHCi now (see #9900) (cherry picked from commit 6f818e083c8390b0c039bcebb6ec21b336d4173b) >--------------------------------------------------------------- 1f59f9a218d85ca1e8a13b3fdf6f4ed0d6fcb7e7 docs/users_guide/glasgow_exts.xml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 96e3d28..c413edd 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -1025,8 +1025,7 @@ bidirectional. The syntax for unidirectional pattern synonyms is: Pattern synonym declarations can only occur in the top level of a module. In particular, they are not allowed as local - definitions. Currently, they also don't work in GHCi, but that is a - technical restriction that will be lifted in later versions. + definitions. The variables in the left-hand side of the definition are bound by From git at git.haskell.org Fri Jan 9 15:47:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 15:47:07 +0000 (UTC) Subject: [commit: ghc] master: Pattern synonym names need to be in scope before renaming bindings (#9889) (5830fc4) Message-ID: <20150109154707.7538D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5830fc449af6b2c0ef5be409fd3457114ae938ca/ghc >--------------------------------------------------------------- commit 5830fc449af6b2c0ef5be409fd3457114ae938ca Author: Dr. ERDI Gergo Date: Wed Dec 17 22:09:06 2014 +0800 Pattern synonym names need to be in scope before renaming bindings (#9889) I did a bit of refactoring at the same time, needless to say >--------------------------------------------------------------- 5830fc449af6b2c0ef5be409fd3457114ae938ca compiler/hsSyn/HsBinds.hs | 10 ++ compiler/hsSyn/HsUtils.hs | 130 +++++++++++++-------- compiler/rename/RnBinds.hs | 28 +++-- compiler/rename/RnEnv.hs | 2 +- compiler/rename/RnNames.hs | 26 +++-- compiler/rename/RnPat.hs | 18 ++- compiler/rename/RnSource.hs | 26 +++-- compiler/typecheck/TcBinds.hs | 55 ++++----- testsuite/tests/ghci/scripts/T8776.stdout | 2 +- .../patsyn/should_compile/{num.hs => T9889.hs} | 6 +- testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/local.stderr | 4 +- testsuite/tests/patsyn/should_run/ghci.stdout | 2 +- 13 files changed, 185 insertions(+), 125 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5830fc449af6b2c0ef5be409fd3457114ae938ca From git at git.haskell.org Fri Jan 9 16:43:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 16:43:59 +0000 (UTC) Subject: [commit: ghc] master: Fix Trac #9973 (buglet in -fwarn-redundant-constraints) (dd3e1dd) Message-ID: <20150109164359.DA35D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dd3e1dd7f8d81e2585a7d63c06c1a1501810fcaa/ghc >--------------------------------------------------------------- commit dd3e1dd7f8d81e2585a7d63c06c1a1501810fcaa Author: Simon Peyton Jones Date: Fri Jan 9 16:45:03 2015 +0000 Fix Trac #9973 (buglet in -fwarn-redundant-constraints) >--------------------------------------------------------------- dd3e1dd7f8d81e2585a7d63c06c1a1501810fcaa compiler/typecheck/TcSimplify.hs | 35 ++++++++++++++--------- testsuite/tests/typecheck/should_compile/T9973.hs | 22 ++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 44 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index b226fde..75abf0a 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -906,16 +906,17 @@ setImplicationStatus :: Implication -> TcS (Maybe Implication) -- Return Nothing if we can discard the implication altogether setImplicationStatus implic@(Implic { ic_binds = EvBindsVar ev_binds_var _ , ic_info = info - , ic_wanted = wc, ic_given = givens }) + , ic_wanted = wc + , ic_given = givens }) | some_insoluble = return $ Just $ implic { ic_status = IC_Insoluble - , ic_wanted = trimmed_wc } + , ic_wanted = wc { wc_simple = pruned_simples } } | some_unsolved = return $ Just $ implic { ic_status = IC_Unsolved - , ic_wanted = trimmed_wc } + , ic_wanted = wc { wc_simple = pruned_simples } } | otherwise -- Everything is solved; look at the implications -- See Note [Tracking redundant constraints] @@ -928,27 +929,33 @@ setImplicationStatus implic@(Implic { ic_binds = EvBindsVar ev_binds_var _ final_needs = all_needs `delVarSetList` givens - discard_implic -- Can we discard the entire implication? + discard_entire_implication -- Can we discard the entire implication? = null dead_givens -- No warning from this implication - && isEmptyBag keep_implics -- No live children + && isEmptyBag pruned_implics -- No live children && isEmptyVarSet final_needs -- No needed vars to pass up to parent - final_implic = implic { ic_status = IC_Solved { ics_need = final_needs - , ics_dead = dead_givens } - , ic_wanted = trimmed_wc } - - ; return $ if discard_implic then Nothing else Just final_implic } + final_status = IC_Solved { ics_need = final_needs + , ics_dead = dead_givens } + final_implic = implic { ic_status = final_status + , ic_wanted = wc { wc_simple = pruned_simples + , wc_impl = pruned_implics } } + -- We can only prune the child implications (pruned_implics) + -- in the IC_Solved status case, because only then we can + -- accumulate their needed evidence variales into the + -- IC_Solved final_status field of the parent implication. + + ; return $ if discard_entire_implication + then Nothing + else Just final_implic } where WC { wc_simple = simples, wc_impl = implics, wc_insol = insols } = wc - trimmed_wc = wc { wc_simple = drop_der_simples - , wc_impl = keep_implics } some_insoluble = insolubleWC wc some_unsolved = not (isEmptyBag simples && isEmptyBag insols) || isNothing mb_implic_needs - drop_der_simples = filterBag isWantedCt simples - keep_implics = filterBag need_to_keep_implic implics + pruned_simples = filterBag isWantedCt simples -- Drop Derived constraints + pruned_implics = filterBag need_to_keep_implic implics mb_implic_needs :: Maybe VarSet -- Just vs => all implics are IC_Solved, with 'vs' needed diff --git a/testsuite/tests/typecheck/should_compile/T9973.hs b/testsuite/tests/typecheck/should_compile/T9973.hs new file mode 100644 index 0000000..1a2148f --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9973.hs @@ -0,0 +1,22 @@ +{-# OPTIONS_GHC -fwarn-redundant-constraints #-} + +module T9973 where + +duplicateDecl :: (Eq t) => t -> IO () +-- Trac #9973 was a bogus "redundant constraint" here +duplicateDecl sigs + = do { newSpan <- return typeSig + + -- **** commenting out the next three lines causes the original warning to disappear + ; let rowOffset = case typeSig of { _ -> 1 } + + ; undefined } + where + typeSig = definingSigsNames sigs + + +definingSigsNames :: (Eq t) => t -> () +definingSigsNames x = undefined + where + _ = x == x -- Suppress the complaint on this + diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 0860a35..2cf1755 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -438,4 +438,5 @@ test('T7643', normal, compile, ['']) test('T9834', normal, compile, ['']) test('T9892', normal, compile, ['']) test('T9939', normal, compile, ['']) +test('T9973', normal, compile, ['']) From git at git.haskell.org Fri Jan 9 18:36:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 18:36:03 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Don't do a half-hearted recompilation check in compileOne (6a0182d) Message-ID: <20150109183603.25E063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/6a0182dd6fcf0f27a960113c41efd1e3ee33b1a0/ghc >--------------------------------------------------------------- commit 6a0182dd6fcf0f27a960113c41efd1e3ee33b1a0 Author: Edward Z. Yang Date: Fri Dec 26 21:56:54 2014 -0800 Don't do a half-hearted recompilation check in compileOne The isNothing maybe_old_linkable check predates 48bc81ad466edfc80237015dbe5d78ba70eb5095, which fixed #481 by requiring recompilation information to be passed in as an argument to compileOne. As a result, the check here is redundant: the client has already taken a look at the object file to see if it is available or not. Signed-off-by: Edward Z. Yang (cherry picked from commit af4d99803ea7676f88f250ad56a8c31c1c8cd5bc) >--------------------------------------------------------------- 6a0182dd6fcf0f27a960113c41efd1e3ee33b1a0 compiler/main/DriverPipeline.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index fdec73e..e8be297 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -171,7 +171,7 @@ compileOne' m_tc_result mHscMessage -- -fforce-recomp should also work with --make let force_recomp = gopt Opt_ForceRecomp dflags source_modified - | force_recomp || isNothing maybe_old_linkable = SourceModified + | force_recomp = SourceModified | otherwise = source_modified0 object_filename = ml_obj_file location From git at git.haskell.org Fri Jan 9 18:36:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 18:36:07 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix #9243 so recompilation avoidance works with -fno-code (c2c6f64) Message-ID: <20150109183607.2BE353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/c2c6f64bc46cac42d24806e5663c8a93920568d8/ghc >--------------------------------------------------------------- commit c2c6f64bc46cac42d24806e5663c8a93920568d8 Author: Edward Z. Yang Date: Sat Dec 27 10:50:01 2014 -0800 Fix #9243 so recompilation avoidance works with -fno-code Where we track timestamps of object files, also track timestamps for interface files. When -fno-code -fwrite-interface is enabled, use the interface file timestamp as an extra check to see if the files are up-to-date. We had to apply this logic to one-shot and make modes. This fix would be good to merge into 7.10; it makes using -fno-code -fwrite-interface for flywheel type checking usable. Signed-off-by: Edward Z. Yang Addresses #9243 (cherry picked from commit 2223e196b2dc5340d70e58be011c279d381b4319) >--------------------------------------------------------------- c2c6f64bc46cac42d24806e5663c8a93920568d8 compiler/main/DriverPipeline.hs | 19 +++++++--- compiler/main/GhcMake.hs | 40 ++++++++++++++++++++-- compiler/main/HscTypes.hs | 4 +++ testsuite/.gitignore | 4 +++ testsuite/tests/driver/recomp001/Makefile | 1 - testsuite/tests/driver/{recomp001 => retc001}/A.hs | 0 .../tests/driver/{recomp001 => retc001}/B1.hs | 0 .../tests/driver/{recomp001 => retc001}/B2.hs | 0 testsuite/tests/driver/{recomp001 => retc001}/C.hs | 0 testsuite/tests/driver/retc001/Makefile | 24 +++++++++++++ testsuite/tests/driver/retc001/all.T | 5 +++ .../recomp001.stderr => retc001/retc001.stderr} | 0 testsuite/tests/driver/retc001/retc001.stdout | 7 ++++ .../tests/driver/{recomp002 => retc002}/Makefile | 6 ++-- testsuite/tests/driver/{recomp002 => retc002}/Q.hs | 2 -- testsuite/tests/driver/{recomp002 => retc002}/W.hs | 2 -- .../tests/driver/{recomp002 => retc002}/W.hs-boot | 2 -- .../tests/driver/{recomp001 => retc002}/all.T | 4 +-- .../recomp002.stderr => retc002/retc002.stderr} | 0 testsuite/tests/driver/retc002/retc002.stdout | 3 ++ testsuite/tests/driver/{recomp003 => retc003}/A.hs | 1 - .../tests/driver/{recomp003 => retc003}/Makefile | 12 ++++--- .../tests/driver/{recomp003 => retc003}/all.T | 4 +-- testsuite/tests/driver/retc003/retc003.stdout | 3 ++ 24 files changed, 117 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c2c6f64bc46cac42d24806e5663c8a93920568d8 From git at git.haskell.org Fri Jan 9 22:36:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 22:36:29 +0000 (UTC) Subject: [commit: ghc] master: Inline all of the .*[TCE] methods, and then rename .*[TCE]X to vacated name. (90dee6e) Message-ID: <20150109223629.C416A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/90dee6e134801e8d43233ab3e52e8ba69419585e/ghc >--------------------------------------------------------------- commit 90dee6e134801e8d43233ab3e52e8ba69419585e Author: Edward Z. Yang Date: Thu Jan 8 14:09:23 2015 -0800 Inline all of the .*[TCE] methods, and then rename .*[TCE]X to vacated name. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 90dee6e134801e8d43233ab3e52e8ba69419585e compiler/coreSyn/TrieMap.hs | 363 ++++++++++++++++++++++---------------------- 1 file changed, 183 insertions(+), 180 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 90dee6e134801e8d43233ab3e52e8ba69419585e From git at git.haskell.org Fri Jan 9 22:36:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 22:36:32 +0000 (UTC) Subject: [commit: ghc] master: Miscellaneous improvements to TrieMap, from D608 code review. (c4e1ccb) Message-ID: <20150109223632.6352F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c4e1ccb2fe6ca7a3100653aadd83f83722669e79/ghc >--------------------------------------------------------------- commit c4e1ccb2fe6ca7a3100653aadd83f83722669e79 Author: Edward Z. Yang Date: Thu Jan 8 13:33:23 2015 -0800 Miscellaneous improvements to TrieMap, from D608 code review. Summary: - Add SPECIALIZE pragmas for the lkG/xtG/mapG/fdG family of functions - Rename wrapEmptyXX to just emptyXX - New deBruijnize function for initializing DeBruijn elements - Some extra documentation Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D611 GHC Trac Issues: #9960 >--------------------------------------------------------------- c4e1ccb2fe6ca7a3100653aadd83f83722669e79 compiler/coreSyn/TrieMap.hs | 122 +++++++++++++++++++++++++++----------------- 1 file changed, 74 insertions(+), 48 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c4e1ccb2fe6ca7a3100653aadd83f83722669e79 From git at git.haskell.org Fri Jan 9 22:36:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 22:36:35 +0000 (UTC) Subject: [commit: ghc] master: Newtype CoreMap and TypeMap so their keys are user-friendly. (944329a) Message-ID: <20150109223635.0A1233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/944329accebc86cc5ec989cd6b3c267d32fb6f26/ghc >--------------------------------------------------------------- commit 944329accebc86cc5ec989cd6b3c267d32fb6f26 Author: Edward Z. Yang Date: Thu Jan 8 15:57:57 2015 -0800 Newtype CoreMap and TypeMap so their keys are user-friendly. Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D612 GHC Trac Issues: #9960 >--------------------------------------------------------------- 944329accebc86cc5ec989cd6b3c267d32fb6f26 compiler/coreSyn/TrieMap.hs | 201 ++++++++++++++++++++++++----------------- compiler/typecheck/TcSMonad.hs | 11 +-- 2 files changed, 122 insertions(+), 90 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 944329accebc86cc5ec989cd6b3c267d32fb6f26 From git at git.haskell.org Fri Jan 9 23:30:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 23:30:34 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update pretty submodule to 1.1.2.0 release (2b76240) Message-ID: <20150109233034.AF6AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/2b76240117aefb08c95b4b75df720ae1a4d4b5ef/ghc >--------------------------------------------------------------- commit 2b76240117aefb08c95b4b75df720ae1a4d4b5ef Author: Herbert Valerio Riedel Date: Fri Jan 9 23:53:19 2015 +0100 Update pretty submodule to 1.1.2.0 release >--------------------------------------------------------------- 2b76240117aefb08c95b4b75df720ae1a4d4b5ef libraries/pretty | 2 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/pretty b/libraries/pretty index c59e1df..7eb7c6c 160000 --- a/libraries/pretty +++ b/libraries/pretty @@ -1 +1 @@ -Subproject commit c59e1df384b2bc7710c5efcb80a9341d172a7ff1 +Subproject commit 7eb7c6c01be4596da3dae9ca57d8adac37cc33fc diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index adf820c..ccfe2f5 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -5,7 +5,7 @@ TYPE CONSTRUCTORS COERCION AXIOMS Dependent modules: [] Dependent packages: [array-0.5.0.1, base-4.8.0.0, deepseq-1.4.0.0, - ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.1.3, + ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.2.0, template-haskell-2.10.0.0] ==================== Typechecker ==================== From git at git.haskell.org Fri Jan 9 23:32:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Jan 2015 23:32:24 +0000 (UTC) Subject: [commit: ghc] master: Update pretty submodule to 1.1.2.0 release (4ec7fcc) Message-ID: <20150109233224.4FEE73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4ec7fccb15782aaef79841e9be1ae55d40bf0ef0/ghc >--------------------------------------------------------------- commit 4ec7fccb15782aaef79841e9be1ae55d40bf0ef0 Author: Herbert Valerio Riedel Date: Fri Jan 9 23:53:19 2015 +0100 Update pretty submodule to 1.1.2.0 release >--------------------------------------------------------------- 4ec7fccb15782aaef79841e9be1ae55d40bf0ef0 libraries/pretty | 2 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/pretty b/libraries/pretty index c59e1df..7eb7c6c 160000 --- a/libraries/pretty +++ b/libraries/pretty @@ -1 +1 @@ -Subproject commit c59e1df384b2bc7710c5efcb80a9341d172a7ff1 +Subproject commit 7eb7c6c01be4596da3dae9ca57d8adac37cc33fc diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index adf820c..ccfe2f5 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -5,7 +5,7 @@ TYPE CONSTRUCTORS COERCION AXIOMS Dependent modules: [] Dependent packages: [array-0.5.0.1, base-4.8.0.0, deepseq-1.4.0.0, - ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.1.3, + ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.2.0, template-haskell-2.10.0.0] ==================== Typechecker ==================== From git at git.haskell.org Sat Jan 10 07:10:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Jan 2015 07:10:44 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8584' deleted Message-ID: <20150110071044.B67D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T8584 From git at git.haskell.org Sat Jan 10 07:16:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Jan 2015 07:16:39 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9900' deleted Message-ID: <20150110071639.A207E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T9900 From git at git.haskell.org Sat Jan 10 07:17:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Jan 2015 07:17:30 +0000 (UTC) Subject: [commit: ghc] branch 'wip/desugar-unfold' deleted Message-ID: <20150110071730.207DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/desugar-unfold From git at git.haskell.org Sat Jan 10 07:18:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Jan 2015 07:18:41 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9732' deleted Message-ID: <20150110071841.9BE5C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T9732 From git at git.haskell.org Sun Jan 11 22:18:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 11 Jan 2015 22:18:11 +0000 (UTC) Subject: [commit: ghc] branch 'strict-data' created Message-ID: <20150111221811.B2E6A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : strict-data Referencing: 1cee34c71e807ff65b921b9062c3d03bac06e01c From git at git.haskell.org Sun Jan 11 22:18:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 11 Jan 2015 22:18:14 +0000 (UTC) Subject: [commit: ghc] strict-data: Temp (601e345) Message-ID: <20150111221814.92EB43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : strict-data Link : http://ghc.haskell.org/trac/ghc/changeset/601e345e5df64caa36e7823a6a01cb6c59252c97/ghc >--------------------------------------------------------------- commit 601e345e5df64caa36e7823a6a01cb6c59252c97 Author: Johan Tibell Date: Thu Jan 8 22:43:06 2015 +0100 Temp >--------------------------------------------------------------- 601e345e5df64caa36e7823a6a01cb6c59252c97 compiler/basicTypes/DataCon.hs | 24 ++++++++++++++++-------- compiler/basicTypes/MkId.hs | 38 ++++++++++++++++++++++---------------- compiler/main/DynFlags.hs | 2 ++ 3 files changed, 40 insertions(+), 24 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 601e345e5df64caa36e7823a6a01cb6c59252c97 From git at git.haskell.org Sun Jan 11 22:18:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 11 Jan 2015 22:18:17 +0000 (UTC) Subject: [commit: ghc] strict-data: Add Strict data language pragma (1cee34c) Message-ID: <20150111221817.C39723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : strict-data Link : http://ghc.haskell.org/trac/ghc/changeset/1cee34c71e807ff65b921b9062c3d03bac06e01c/ghc >--------------------------------------------------------------- commit 1cee34c71e807ff65b921b9062c3d03bac06e01c Author: Johan Tibell Date: Sun Jan 11 23:19:34 2015 +0100 Add Strict data language pragma >--------------------------------------------------------------- 1cee34c71e807ff65b921b9062c3d03bac06e01c compiler/basicTypes/DataCon.hs | 10 ++--- compiler/basicTypes/MkId.hs | 26 +++++++------ compiler/deSugar/DsMeta.hs | 10 +++-- compiler/hsSyn/Convert.hs | 5 ++- compiler/parser/Parser.y | 17 ++++---- compiler/typecheck/TcExpr.hs | 28 +++++++------- compiler/typecheck/TcSplice.hs | 13 ++++--- compiler/typecheck/TcTyClsDecls.hs | 10 +++-- testsuite/tests/deSugar/should_run/DsStrictData.hs | 45 ++++++++++++++++++++++ .../tests/deSugar/should_run/DsStrictData.stdout | 3 +- testsuite/tests/deSugar/should_run/all.T | 1 + 11 files changed, 114 insertions(+), 54 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1cee34c71e807ff65b921b9062c3d03bac06e01c From git at git.haskell.org Sun Jan 11 23:06:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 11 Jan 2015 23:06:43 +0000 (UTC) Subject: [commit: ghc] master: More comments on HsBang (c506f25) Message-ID: <20150111230643.631803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c506f254b8e14fe422186322a580f9f7effca7f8/ghc >--------------------------------------------------------------- commit c506f254b8e14fe422186322a580f9f7effca7f8 Author: Simon Peyton Jones Date: Sun Jan 11 23:07:24 2015 +0000 More comments on HsBang In particular about the dcSrcBangs field of an imported DataCon >--------------------------------------------------------------- c506f254b8e14fe422186322a580f9f7effca7f8 compiler/basicTypes/DataCon.hs | 74 ++++++++++++++++++++++++------------------ compiler/basicTypes/MkId.hs | 9 ++++- compiler/iface/BuildTyCl.hs | 2 +- compiler/iface/IfaceSyn.hs | 3 +- compiler/iface/TcIface.hs | 6 +++- 5 files changed, 58 insertions(+), 36 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c506f254b8e14fe422186322a580f9f7effca7f8 From git at git.haskell.org Mon Jan 12 10:23:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jan 2015 10:23:27 +0000 (UTC) Subject: [commit: ghc] branch 'strict-data' deleted Message-ID: <20150112102327.ADC643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: strict-data From git at git.haskell.org Mon Jan 12 15:57:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jan 2015 15:57:01 +0000 (UTC) Subject: [commit: ghc] master: inplace: Don't add empty component to LD_LIBRARY_PATH when it is empty (fe0d289) Message-ID: <20150112155701.C894C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fe0d289de466b0c34a04350c6f7c096d9a588ad0/ghc >--------------------------------------------------------------- commit fe0d289de466b0c34a04350c6f7c096d9a588ad0 Author: Reid Barton Date: Mon Jan 12 10:56:58 2015 -0500 inplace: Don't add empty component to LD_LIBRARY_PATH when it is empty Summary: Avoids a confusing inconsistency when testing #9386 (about ghci finding .so files in .). Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D593 GHC Trac Issues: #9386 >--------------------------------------------------------------- fe0d289de466b0c34a04350c6f7c096d9a588ad0 rules/library-path.mk | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rules/library-path.mk b/rules/library-path.mk index 5dd5588..dbfd4be 100644 --- a/rules/library-path.mk +++ b/rules/library-path.mk @@ -14,8 +14,8 @@ ifeq "$(TargetOS_CPP)" "mingw32" prependLibraryPath = $(error Do not know how to prependLibraryPath on Windows) else ifeq "$(TargetOS_CPP)" "darwin" -prependLibraryPath = export DYLD_LIBRARY_PATH="$1:$$DYLD_LIBRARY_PATH" +prependLibraryPath = export DYLD_LIBRARY_PATH="$1$${DYLD_LIBRARY_PATH:+:$$DYLD_LIBRARY_PATH}" else -prependLibraryPath = export LD_LIBRARY_PATH="$1:$$LD_LIBRARY_PATH" +prependLibraryPath = export LD_LIBRARY_PATH="$1$${LD_LIBRARY_PATH:+:$$LD_LIBRARY_PATH}" endif From git at git.haskell.org Mon Jan 12 17:02:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jan 2015 17:02:15 +0000 (UTC) Subject: [commit: ghc] master: Move libffi configuration after basic toolchain setup (a5bc257) Message-ID: <20150112170215.BF13F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a5bc2579afac3268c31626777406c295c7e67755/ghc >--------------------------------------------------------------- commit a5bc2579afac3268c31626777406c295c7e67755 Author: Reid Barton Date: Mon Jan 12 10:59:11 2015 -0500 Move libffi configuration after basic toolchain setup Summary: The relevant aspect is that the libffi configuration's AC_CHECK_LIB and AC_CHECK_HEADERS are moved after FIND_GCC. There are two reasons to do this: 1. We should detect the presence of libffi using the C compiler that we are eventually going to use to build GHC. 2. Running AC_CHECK_HEADERS before FIND_GCC pollutes the CPP variable with "gcc -E" (wrong when cross-compiling), and CPP is not reset by FIND_GCC. Thus this patch fixes x86_64 -> i386 cross-compilation of integer-gmp2. Test Plan: Local x86_64 -> i386 cross-compiling validate; Harbormaster Reviewers: austin Reviewed By: austin Subscribers: erikd, carter, thomie Differential Revision: https://phabricator.haskell.org/D597 >--------------------------------------------------------------- a5bc2579afac3268c31626777406c295c7e67755 configure.ac | 112 +++++++++++++++++++++++++++++------------------------------ 1 file changed, 56 insertions(+), 56 deletions(-) diff --git a/configure.ac b/configure.ac index 8fadf30..16d1605 100644 --- a/configure.ac +++ b/configure.ac @@ -355,62 +355,6 @@ then fi fi -# system libffi - -AC_ARG_WITH([system-libffi], -[AC_HELP_STRING([--with-system-libffi], - [Use system provided libffi for RTS [default=no]]) -]) - -AS_IF([test "x$with_system_libffi" = "xyes"], - [UseSystemLibFFI="YES"], [UseSystemLibFFI="NO"] -) - - -AC_SUBST(UseSystemLibFFI) - -AC_ARG_WITH([ffi-includes], -[AC_HELP_STRING([--with-ffi-includes=ARG], - [Find includes for libffi in ARG [default=system default]]) -], -[ - if test "x$UseSystemLibFFI" != "xYES"; then - AC_MSG_WARN([--with-ffi-includes will be ignored, --with-system-libffi not set]) - else - FFIIncludeDir="$withval" - LIBFFI_CFLAGS="-I$withval" - fi -]) - -AC_SUBST(FFIIncludeDir) - -AC_ARG_WITH([ffi-libraries], -[AC_HELP_STRING([--with-ffi-libraries=ARG], - [Find libffi in ARG [default=system default]]) -], -[ - if test "x$UseSystemLibFFI" != "xYES"; then - AC_MSG_WARN([--with-ffi-libraries will be ignored, --with-system-libffi not set]) - else - FFILibDir="$withval" LIBFFI_LDFLAGS="-L$withval" - fi -]) - -AC_SUBST(FFILibDir) - -AS_IF([test "$UseSystemLibFFI" = "YES"], [ - CFLAGS2="$CFLAGS" - CFLAGS="$LIBFFI_CFLAGS $CFLAGS" - LDFLAGS2="$LDFLAGS" - LDFLAGS="$LIBFFI_LDFLAGS $LDFLAGS" - AC_CHECK_LIB(ffi, ffi_call, - [AC_CHECK_HEADERS([ffi.h], [break], []) - AC_DEFINE([HAVE_LIBFFI], [1], [Define to 1 if you have libffi.])], - [AC_MSG_ERROR([Cannot find system libffi])]) - CFLAGS="$CFLAGS2" - LDFLAGS="$LDFLAGS2" -]) - FP_ICONV FP_GMP @@ -855,6 +799,62 @@ dnl ################################################################ dnl Check for libraries dnl ################################################################ +# system libffi + +AC_ARG_WITH([system-libffi], +[AC_HELP_STRING([--with-system-libffi], + [Use system provided libffi for RTS [default=no]]) +]) + +AS_IF([test "x$with_system_libffi" = "xyes"], + [UseSystemLibFFI="YES"], [UseSystemLibFFI="NO"] +) + + +AC_SUBST(UseSystemLibFFI) + +AC_ARG_WITH([ffi-includes], +[AC_HELP_STRING([--with-ffi-includes=ARG], + [Find includes for libffi in ARG [default=system default]]) +], +[ + if test "x$UseSystemLibFFI" != "xYES"; then + AC_MSG_WARN([--with-ffi-includes will be ignored, --with-system-libffi not set]) + else + FFIIncludeDir="$withval" + LIBFFI_CFLAGS="-I$withval" + fi +]) + +AC_SUBST(FFIIncludeDir) + +AC_ARG_WITH([ffi-libraries], +[AC_HELP_STRING([--with-ffi-libraries=ARG], + [Find libffi in ARG [default=system default]]) +], +[ + if test "x$UseSystemLibFFI" != "xYES"; then + AC_MSG_WARN([--with-ffi-libraries will be ignored, --with-system-libffi not set]) + else + FFILibDir="$withval" LIBFFI_LDFLAGS="-L$withval" + fi +]) + +AC_SUBST(FFILibDir) + +AS_IF([test "$UseSystemLibFFI" = "YES"], [ + CFLAGS2="$CFLAGS" + CFLAGS="$LIBFFI_CFLAGS $CFLAGS" + LDFLAGS2="$LDFLAGS" + LDFLAGS="$LIBFFI_LDFLAGS $LDFLAGS" + AC_CHECK_LIB(ffi, ffi_call, + [AC_CHECK_HEADERS([ffi.h], [break], []) + AC_DEFINE([HAVE_LIBFFI], [1], [Define to 1 if you have libffi.])], + [AC_MSG_ERROR([Cannot find system libffi])]) + CFLAGS="$CFLAGS2" + LDFLAGS="$LDFLAGS2" +]) + dnl ** check whether we need -ldl to get dlopen() AC_CHECK_LIB(dl, dlopen) From git at git.haskell.org Mon Jan 12 22:46:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jan 2015 22:46:47 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to latest 1.22.0.1 snapshot (8464fa2) Message-ID: <20150112224647.3B3023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8464fa29e677e6845ca96d21474840803218f0b9/ghc >--------------------------------------------------------------- commit 8464fa29e677e6845ca96d21474840803218f0b9 Author: Herbert Valerio Riedel Date: Mon Jan 12 22:37:19 2015 +0100 Update Cabal submodule to latest 1.22.0.1 snapshot Differential Revision: https://phabricator.haskell.org/D617 >--------------------------------------------------------------- 8464fa29e677e6845ca96d21474840803218f0b9 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 3a7f901..e4ea51c 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 3a7f9015828745932a65d95fa985c98073fc7d95 +Subproject commit e4ea51c3156c27b7dec40cb2733b8bfe37bca6a1 From git at git.haskell.org Mon Jan 12 22:49:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jan 2015 22:49:48 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Cabal submodule to latest 1.22.0.1 snapshot (d834464) Message-ID: <20150112224948.31DEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/d8344643cb9dfdc3cede479c552a5343b5ec798d/ghc >--------------------------------------------------------------- commit d8344643cb9dfdc3cede479c552a5343b5ec798d Author: Herbert Valerio Riedel Date: Mon Jan 12 22:37:19 2015 +0100 Update Cabal submodule to latest 1.22.0.1 snapshot (cherry picked from commit 8464fa29e677e6845ca96d21474840803218f0b9) >--------------------------------------------------------------- d8344643cb9dfdc3cede479c552a5343b5ec798d libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index f71044b..e4ea51c 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit f71044bb1f79f8a0b2f6926b1c04a9592932f1ee +Subproject commit e4ea51c3156c27b7dec40cb2733b8bfe37bca6a1 From git at git.haskell.org Mon Jan 12 23:38:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Jan 2015 23:38:46 +0000 (UTC) Subject: [commit: ghc] master: Event Manager: Make one-shot a per-registration property (0234399) Message-ID: <20150112233846.1F5BB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/023439980f6ef6ec051f676279ed2be5f031efe6/ghc >--------------------------------------------------------------- commit 023439980f6ef6ec051f676279ed2be5f031efe6 Author: Ben Gamari Date: Mon Jan 12 18:36:23 2015 -0500 Event Manager: Make one-shot a per-registration property Summary: Currently the event manager has a global flag for whether to create epoll-like notifications as one-shot (e.g. EPOLLONESHOT, where an fd will be deactivated after its first event) or standard multi-shot notifications. Unfortunately this means that the event manager may export either one-shot or multi-shot semantics to the user. Even worse, the user has no way of knowing which semantics are being delivered. This resulted in breakage in the usb[1] library which deadlocks after notifications on its fd are disabled after the first event is delivered. This patch reworks one-shot event support to allow the user to choose whether one-shot or multi-shot semantics are desired on a per-registration basis. The event manager can then decide whether to use a one-shot or multi-shot epoll. A registration is now defined by a set of Events (as before) as well as a Lifetime (either one-shot or multi-shot). We lend monoidal structure to Lifetime choosing OneShot as the identity. This allows us to combine Lifetime/Event pairs of an fd to give the longest desired lifetime of the registration and the full set of Events for which we want notification. [1] https://github.com/basvandijk/usb/issues/7 Test Plan: Add more test cases and validate Reviewers: tibbe, AndreasVoellmy, hvr, austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D347 >--------------------------------------------------------------- 023439980f6ef6ec051f676279ed2be5f031efe6 libraries/base/GHC/Event.hs | 1 - libraries/base/GHC/Event/IntTable.hs | 4 + libraries/base/GHC/Event/Internal.hs | 48 ++++++++ libraries/base/GHC/Event/Manager.hs | 224 +++++++++++++++++++---------------- libraries/base/GHC/Event/Thread.hs | 6 +- 5 files changed, 175 insertions(+), 108 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 023439980f6ef6ec051f676279ed2be5f031efe6 From git at git.haskell.org Tue Jan 13 12:56:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 12:56:02 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Changed LazyPat handling in PM Check (98e5217) Message-ID: <20150113125602.9C8BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/98e521721d270866569f477348b3eae7482a2b20/ghc >--------------------------------------------------------------- commit 98e521721d270866569f477348b3eae7482a2b20 Author: George Karachalias Date: Tue Jan 13 13:53:23 2015 +0100 Changed LazyPat handling in PM Check >--------------------------------------------------------------- 98e521721d270866569f477348b3eae7482a2b20 compiler/deSugar/Check.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 770cb40..c469d3b 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -167,7 +167,8 @@ mViewPat :: Pat Id -> PmM [PmPat Id] mViewPat pat@(WildPat _) = pure <$> varFromPat pat mViewPat pat@(VarPat id) = return [PmVarPat (patTypeExpanded pat) id] mViewPat (ParPat p) = mViewPat (unLoc p) -mViewPat pat@(LazyPat _) = pure <$> varFromPat pat +mViewPat (LazyPat p) = mViewPat (unLoc p) -- NOT SURE. +-- WAS: mViewPat pat@(LazyPat _) = pure <$> varFromPat pat mViewPat (BangPat p) = mViewPat (unLoc p) mViewPat (AsPat _ p) = mViewPat (unLoc p) mViewPat (SigPatOut p _) = mViewPat (unLoc p) From git at git.haskell.org Tue Jan 13 13:23:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 13:23:53 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Impement a satisfiability oracle (d2b720d) Message-ID: <20150113132353.741B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/d2b720da1d1e34e29026d6d44e8ce58886d51464/ghc >--------------------------------------------------------------- commit d2b720da1d1e34e29026d6d44e8ce58886d51464 Author: Simon Peyton Jones Date: Tue Jan 13 13:24:17 2015 +0000 Impement a satisfiability oracle The main checker is in TcSimplify.tcCheckSatisfiablity Observations * DsMonad.initTcDsForSolver is a bit of a kludge. We spin up a complete TcM monad only to immediately refine it to a TcS monad. Better perhaps to make TcS into its own monad, rather than building on TcS But that may in turn interact with plugins * I'm concerned about whether DataCons are properly instantiated in Check, but I don't understand the code well enough to be sure. >--------------------------------------------------------------- d2b720da1d1e34e29026d6d44e8ce58886d51464 compiler/deSugar/Check.hs | 73 ++++++++++++++++++++++++++++++---------- compiler/deSugar/DsMonad.hs | 37 +++++++++++++++++--- compiler/typecheck/TcRnTypes.hs | 2 +- compiler/typecheck/TcSMonad.hs | 13 ++++--- compiler/typecheck/TcSimplify.hs | 13 ++++++- 5 files changed, 110 insertions(+), 28 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d2b720da1d1e34e29026d6d44e8ce58886d51464 From git at git.haskell.org Tue Jan 13 16:09:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 16:09:55 +0000 (UTC) Subject: [commit: ghc] master: add -th-file which generates a th.hs file (07ace5c) Message-ID: <20150113160955.CA2993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/07ace5c221adbb1675413a0fac300a9f7913c234/ghc >--------------------------------------------------------------- commit 07ace5c221adbb1675413a0fac300a9f7913c234 Author: Greg Weber Date: Mon Jan 12 05:16:37 2015 -0600 add -th-file which generates a th.hs file Summary: see Trac #8624 similar functionality is now available with -ddump-to-file -ddump-splices However, users are already accustomed to -ddump-splices having a particular format, and this format is not completely valid code The goal of -th-file is to dump valid Haskell code Additionally, the convention of -ddump-to-file is to name the file after the flag, so the file is .dump-splices Given that the goal of the new flag is to generate valid Haskell, The extension should be .hs Additionally, -ddump-to-file effects all other dump flags Test Plan: look at the output of using the -th-file flag and compare it to the output of using -ddump-to-file and -ddump-splices I want to add test cases, but just need some pointers on getting started there Reviewers: thomie, goldfire, simonpj, austin Reviewed By: simonpj, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D518 GHC Trac Issues: #8624 >--------------------------------------------------------------- 07ace5c221adbb1675413a0fac300a9f7913c234 .gitignore | 8 +++ compiler/main/DynFlags.hs | 4 ++ compiler/main/ErrUtils.hs | 3 +- compiler/rename/RnSplice.hs | 63 +++++++++++++++++++--- compiler/typecheck/TcRnDriver.hs | 11 ++-- compiler/typecheck/TcRnMonad.hs | 11 ++-- compiler/typecheck/TcSplice.hs | 63 ++++++++++++++++++---- compiler/typecheck/TcSplice.hs-boot | 14 ++++- docs/users_guide/7.12.1-notes.xml | 7 ++- docs/users_guide/flags.xml | 6 +++ docs/users_guide/glasgow_exts.xml | 42 +++++++++++++-- .../tests/indexed-types/should_fail/T8129.stdout | 1 - testsuite/tests/th/Makefile | 6 +++ testsuite/tests/th/T3319.stderr | 3 +- testsuite/tests/th/T3600.stderr | 3 +- testsuite/tests/th/T5217.stderr | 3 +- testsuite/tests/th/T5290.stderr | 3 +- testsuite/tests/th/T5700.stderr | 3 +- testsuite/tests/th/T5883.stderr | 3 +- testsuite/tests/th/T5984.stderr | 6 +-- testsuite/tests/th/T7532.stderr | 3 +- testsuite/tests/th/T8624.hs | 7 +++ .../tests/th/T8624.stderr | 0 testsuite/tests/th/T8624.stdout | 2 + testsuite/tests/th/TH_TyInstWhere1.stderr | 3 +- .../tests/th/TH_foreignCallingConventions.stderr | 3 +- testsuite/tests/th/TH_foreignInterruptible.stderr | 3 +- testsuite/tests/th/TH_genEx.stderr | 3 +- testsuite/tests/th/TH_pragma.stderr | 6 +-- testsuite/tests/th/all.T | 1 + 30 files changed, 227 insertions(+), 67 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 07ace5c221adbb1675413a0fac300a9f7913c234 From git at git.haskell.org Tue Jan 13 16:09:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 16:09:59 +0000 (UTC) Subject: [commit: ghc] master: Fix panics of PartialTypeSignatures combined with extensions (c9532f8) Message-ID: <20150113160959.084DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c9532f810a82c6395bc08fb77f2a895a50da86b5/ghc >--------------------------------------------------------------- commit c9532f810a82c6395bc08fb77f2a895a50da86b5 Author: Thomas Winant Date: Mon Jan 12 05:29:50 2015 -0600 Fix panics of PartialTypeSignatures combined with extensions Summary: Disallow wildcards in stand-alone deriving instances (StandaloneDeriving), default signatures (DefaultSignatures) and instances signatures (InstanceSigs). Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: carter, thomie, monoidal Differential Revision: https://phabricator.haskell.org/D595 GHC Trac Issues: #9922 >--------------------------------------------------------------- c9532f810a82c6395bc08fb77f2a895a50da86b5 compiler/parser/Parser.y | 15 +++++++++++++-- .../should_fail/WildcardInDefaultSignature.hs | 4 ++++ .../should_fail/WildcardInDefaultSignature.stderr | 4 ++++ .../partial-sigs/should_fail/WildcardInInstanceSig.hs | 4 ++++ .../partial-sigs/should_fail/WildcardInInstanceSig.stderr | 4 ++++ .../should_fail/WildcardInStandaloneDeriving.hs | 4 ++++ .../should_fail/WildcardInStandaloneDeriving.stderr | 4 ++++ testsuite/tests/partial-sigs/should_fail/all.T | 3 +++ 8 files changed, 40 insertions(+), 2 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 4958e0c..36b27cf 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -798,6 +798,10 @@ inst_decl :: { LInstDecl RdrName } , cid_datafam_insts = adts } ; let err = text "In instance head:" <+> ppr $3 ; checkNoPartialType err $3 + ; sequence_ [ checkNoPartialType err ty + | sig@(L _ (TypeSig _ ty _ )) <- sigs + , let err = text "in instance signature" <> colon + <+> quotes (ppr sig) ] ; ams (L (comb3 $1 $3 $4) (ClsInstD { cid_inst = cid })) (mj AnnInstance $1 : (fst $ unLoc $4)) } } @@ -972,8 +976,12 @@ capi_ctype : '{-# CTYPE' STRING STRING '#-}' -- Glasgow extension: stand-alone deriving declarations stand_alone_deriving :: { LDerivDecl RdrName } : 'deriving' 'instance' overlap_pragma inst_type - {% ams (sLL $1 $> (DerivDecl $4 $3)) - [mj AnnDeriving $1,mj AnnInstance $2] } + {% do { + let err = text "in the stand-alone deriving instance" + <> colon <+> quotes (ppr $4) + ; checkNoPartialType err $4 + ; ams (sLL $1 $> (DerivDecl $4 $3)) + [mj AnnDeriving $1,mj AnnInstance $2] }} ----------------------------------------------------------------------------- -- Role annotations @@ -1070,6 +1078,9 @@ decl_cls : at_decl_cls { sLL $1 $> (unitOL $1) } -- A 'default' signature used with the generic-programming extension | 'default' infixexp '::' sigtypedoc {% do { (TypeSig l ty _) <- checkValSig $2 $4 + ; let err = text "in default signature" <> colon <+> + quotes (ppr ty) + ; checkNoPartialType err ty ; ams (sLL $1 $> $ unitOL (sLL $1 $> $ SigD (GenericSig l ty))) [mj AnnDefault $1,mj AnnDcolon $3] } } diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.hs b/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.hs new file mode 100644 index 0000000..5e85e59 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE DefaultSignatures #-} +module WildcardInDefaultSignature where + +class C a where default f :: _ diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.stderr b/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.stderr new file mode 100644 index 0000000..38cb4ce --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.stderr @@ -0,0 +1,4 @@ + +WildcardInDefaultSignature.hs:4:30: + Wildcard not allowed + in default signature: ?_? diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.hs b/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.hs new file mode 100644 index 0000000..cd36449 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE InstanceSigs #-} +module WildcardInInstanceSig where + +instance Num Bool where negate :: _ diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.stderr b/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.stderr new file mode 100644 index 0000000..e8148f1 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.stderr @@ -0,0 +1,4 @@ + +WildcardInInstanceSig.hs:4:35: + Wildcard not allowed + in instance signature: ?negate :: _? diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.hs b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.hs new file mode 100644 index 0000000..6348921 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE StandaloneDeriving #-} +module WildcardInStandaloneDeriving where + +deriving instance _ diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr new file mode 100644 index 0000000..921d7a0 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr @@ -0,0 +1,4 @@ + +WildcardInStandaloneDeriving.hs:4:19: + Wildcard not allowed + in the stand-alone deriving instance: ?_? diff --git a/testsuite/tests/partial-sigs/should_fail/all.T b/testsuite/tests/partial-sigs/should_fail/all.T index c275e93..7e56d15 100644 --- a/testsuite/tests/partial-sigs/should_fail/all.T +++ b/testsuite/tests/partial-sigs/should_fail/all.T @@ -26,15 +26,18 @@ test('WildcardInADT3', normal, compile_fail, ['']) test('WildcardInADTContext1', normal, compile_fail, ['']) test('WildcardInADTContext2', normal, compile_fail, ['']) test('WildcardInDefault', normal, compile_fail, ['']) +test('WildcardInDefaultSignature', normal, compile_fail, ['']) test('WildcardInDeriving', normal, compile_fail, ['']) test('WildcardInForeignExport', normal, compile_fail, ['']) test('WildcardInForeignImport', normal, compile_fail, ['']) test('WildcardInGADT1', normal, compile_fail, ['']) test('WildcardInGADT2', normal, compile_fail, ['']) test('WildcardInInstanceHead', normal, compile_fail, ['']) +test('WildcardInInstanceSig', normal, compile_fail, ['']) test('WildcardsInPatternAndExprSig', normal, compile_fail, ['']) test('WildcardInPatSynSig', normal, compile_fail, ['']) test('WildcardInNewtype', normal, compile_fail, ['']) +test('WildcardInStandaloneDeriving', normal, compile_fail, ['']) test('WildcardInstantiations', normal, compile_fail, ['']) test('WildcardInTypeBrackets', [req_interp, only_compiler_types(['ghc'])], compile_fail, ['']) test('WildcardInTypeFamilyInstanceLHS', normal, compile_fail, ['']) From git at git.haskell.org Tue Jan 13 16:10:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 16:10:01 +0000 (UTC) Subject: [commit: ghc] master: aclocal.m4: fix == bashism in FIND_LLVM_PROG (0fa4240) Message-ID: <20150113161001.B44E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0fa4240249058f327cfd283f9da2deb8dff664f1/ghc >--------------------------------------------------------------- commit 0fa4240249058f327cfd283f9da2deb8dff664f1 Author: Tuncer Ayaz Date: Mon Jan 12 05:14:45 2015 -0600 aclocal.m4: fix == bashism in FIND_LLVM_PROG Reviewers: austin, erikd Reviewed By: erikd Subscribers: erikd, carter, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D590 >--------------------------------------------------------------- 0fa4240249058f327cfd283f9da2deb8dff664f1 aclocal.m4 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 6caa10a..6933e6f 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2072,7 +2072,7 @@ AC_DEFUN([XCODE_VERSION],[ # AC_DEFUN([FIND_LLVM_PROG],[ FP_ARG_WITH_PATH_GNU_PROG_OPTIONAL_NOTARGET([$1], [$2], [$3]) - if test "$$1" == ""; then + if test "$$1" = ""; then save_IFS=$IFS IFS=":;" for p in ${PATH}; do From git at git.haskell.org Tue Jan 13 16:10:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 16:10:04 +0000 (UTC) Subject: [commit: ghc] master: Trac #9878: Have StaticPointers support dynamic loading. (7637810) Message-ID: <20150113161004.681FE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7637810a93441d29bc84bbeeeced0615bbb9d9e4/ghc >--------------------------------------------------------------- commit 7637810a93441d29bc84bbeeeced0615bbb9d9e4 Author: Alexander Vershilov Date: Mon Jan 12 05:29:18 2015 -0600 Trac #9878: Have StaticPointers support dynamic loading. Summary: A mutex is used to protect the SPT. unsafeLookupStaticPtr and staticPtrKeys in GHC.StaticPtr are made monadic. SPT entries are removed in a destructor function of modules. Authored-by: Facundo Dom?nguez Authored-by: Alexander Vershilov Test Plan: ./validate Reviewers: austin, simonpj, hvr Subscribers: carter, thomie, qnikst, mboes Differential Revision: https://phabricator.haskell.org/D587 GHC Trac Issues: #9878 >--------------------------------------------------------------- 7637810a93441d29bc84bbeeeced0615bbb9d9e4 compiler/deSugar/StaticPtrTable.hs | 23 ++++++++ includes/rts/StaticPtrTable.h | 8 +++ libraries/base/GHC/StaticPtr.hs | 33 +++++------- rts/Linker.c | 1 + rts/StaticPtrTable.c | 61 +++++++++++++++++++--- .../tests/codeGen/should_run/CgStaticPointers.hs | 11 ++-- testsuite/tests/rts/GcStaticPointers.hs | 2 +- testsuite/tests/rts/ListStaticPointers.hs | 10 ++-- 8 files changed, 113 insertions(+), 36 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7637810a93441d29bc84bbeeeced0615bbb9d9e4 From git at git.haskell.org Tue Jan 13 16:10:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 16:10:07 +0000 (UTC) Subject: [commit: ghc] master: Package environments (099b767) Message-ID: <20150113161007.228A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/099b76769f02432d8efcd7881348e5f5b6b50787/ghc >--------------------------------------------------------------- commit 099b76769f02432d8efcd7881348e5f5b6b50787 Author: Edsko de Vries Date: Mon Jan 12 05:22:22 2015 -0600 Package environments Summary: Package environments are files with package IDs that indicate which packages should be visible; see entry in user guide for details. Reviewers: duncan, austin Reviewed By: duncan, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D558 >--------------------------------------------------------------- 099b76769f02432d8efcd7881348e5f5b6b50787 compiler/main/CmdLineParser.hs | 8 +-- compiler/main/DynFlags.hs | 118 ++++++++++++++++++++++++++++++++++++++++- compiler/main/Packages.hs | 11 ++-- compiler/utils/Maybes.hs | 24 +++++++-- docs/users_guide/packages.xml | 86 ++++++++++++++++++++++++++++++ 5 files changed, 234 insertions(+), 13 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 099b76769f02432d8efcd7881348e5f5b6b50787 From git at git.haskell.org Tue Jan 13 16:10:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 16:10:09 +0000 (UTC) Subject: [commit: ghc] master: Dwarf generation fixed pt 2 (36df098) Message-ID: <20150113161009.E82763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/36df0988444bdf0555a842ce94f4d597b741923d/ghc >--------------------------------------------------------------- commit 36df0988444bdf0555a842ce94f4d597b741923d Author: Peter Wortmann Date: Thu Jan 8 22:19:56 2015 +0100 Dwarf generation fixed pt 2 - Don't bracket HsTick expression uneccessarily - Generate debug information in UTF8 - Reduce amount of information generated - we do not currently need block information, for example. Special thanks to slyfox for the reports! >--------------------------------------------------------------- 36df0988444bdf0555a842ce94f4d597b741923d compiler/hsSyn/HsExpr.hs | 2 +- compiler/nativeGen/Dwarf.hs | 5 ++++- compiler/nativeGen/Dwarf/Constants.hs | 3 ++- compiler/nativeGen/Dwarf/Types.hs | 35 ++++++++++++++++++++++------------- 4 files changed, 29 insertions(+), 16 deletions(-) diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs index a5a1aaf..129ed80 100644 --- a/compiler/hsSyn/HsExpr.hs +++ b/compiler/hsSyn/HsExpr.hs @@ -665,7 +665,7 @@ ppr_expr (HsStatic e) ppr_expr (HsTick tickish exp) = pprTicks (ppr exp) $ - ppr tickish <+> ppr exp + ppr tickish <+> ppr_lexpr exp ppr_expr (HsBinTick tickIdTrue tickIdFalse exp) = pprTicks (ppr exp) $ hcat [ptext (sLit "bintick<"), diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs index 70fca4f..d7c2f61 100644 --- a/compiler/nativeGen/Dwarf.hs +++ b/compiler/nativeGen/Dwarf.hs @@ -33,7 +33,10 @@ dwarfGen :: DynFlags -> ModLocation -> UniqSupply -> [DebugBlock] dwarfGen df modLoc us blocks = do -- Convert debug data structures to DWARF info records - let procs = debugSplitProcs blocks + -- We strip out block information, as it is not currently useful for + -- anything. In future we might want to only do this for -g1. + let procs = map stripBlocks $ debugSplitProcs blocks + stripBlocks dbg = dbg { dblBlocks = [] } compPath <- getCurrentDirectory let dwarfUnit = DwarfCompileUnit { dwChildren = map (procToDwarf df) procs diff --git a/compiler/nativeGen/Dwarf/Constants.hs b/compiler/nativeGen/Dwarf/Constants.hs index a5bbeac..2cd54a7 100644 --- a/compiler/nativeGen/Dwarf/Constants.hs +++ b/compiler/nativeGen/Dwarf/Constants.hs @@ -41,7 +41,7 @@ dW_TAG_arg_variable = 257 -- | Dwarf attributes dW_AT_name, dW_AT_stmt_list, dW_AT_low_pc, dW_AT_high_pc, dW_AT_language, dW_AT_comp_dir, dW_AT_producer, dW_AT_external, dW_AT_frame_base, - dW_AT_MIPS_linkage_name :: Word + dW_AT_use_UTF8, dW_AT_MIPS_linkage_name :: Word dW_AT_name = 0x03 dW_AT_stmt_list = 0x10 dW_AT_low_pc = 0x11 @@ -51,6 +51,7 @@ dW_AT_comp_dir = 0x1b dW_AT_producer = 0x25 dW_AT_external = 0x3f dW_AT_frame_base = 0x40 +dW_AT_use_UTF8 = 0x53 dW_AT_MIPS_linkage_name = 0x2007 -- | Abbrev declaration diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index 47e0bd1..520b5ae 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -21,6 +21,7 @@ module Dwarf.Types import Debug import CLabel import CmmExpr ( GlobalReg(..) ) +import Encoding import FastString import Outputable import Platform @@ -79,6 +80,7 @@ pprAbbrevDecls haveDebugLine = , (dW_AT_producer, dW_FORM_string) , (dW_AT_language, dW_FORM_data4) , (dW_AT_comp_dir, dW_FORM_string) + , (dW_AT_use_UTF8, dW_FORM_flag) ] ++ (if haveDebugLine then [ (dW_AT_stmt_list, dW_FORM_data4) ] @@ -115,6 +117,7 @@ pprDwarfInfoOpen haveSrc (DwarfCompileUnit _ name producer compDir lineLbl) = $$ pprString producer $$ pprData4 dW_LANG_Haskell $$ pprString compDir + $$ pprFlag True -- use UTF8 $$ if haveSrc then pprData4' (sectionOffset lineLbl dwarfLineLabel) else empty @@ -406,19 +409,25 @@ pprString' str = ptext (sLit "\t.asciz \"") <> str <> char '"' -- | Generate a string constant. We take care to escape the string. pprString :: String -> SDoc -pprString = pprString' . hcat . map escape - where escape '\\' = ptext (sLit "\\\\") - escape '\"' = ptext (sLit "\\\"") - escape '\n' = ptext (sLit "\\n") - escape c | isAscii c && isPrint c && c /= '?' - -- escaping '?' prevents trigraph warnings - = char c - | otherwise - = let ch = ord c - in char '\\' <> - char (intToDigit (ch `div` 64)) <> - char (intToDigit ((ch `div` 8) `mod` 8)) <> - char (intToDigit (ch `mod` 8)) +pprString str + = pprString' $ hcat $ map escapeChar $ + if utf8EncodedLength str == length str + then str + else map (chr . fromIntegral) $ bytesFS $ mkFastString str + +-- | Escape a single non-unicode character +escapeChar :: Char -> SDoc +escapeChar '\\' = ptext (sLit "\\\\") +escapeChar '\"' = ptext (sLit "\\\"") +escapeChar '\n' = ptext (sLit "\\n") +escapeChar c + | isAscii c && isPrint c && c /= '?' -- prevents trigraph warnings + = char c + | otherwise + = char '\\' <> char (intToDigit (ch `div` 64)) <> + char (intToDigit ((ch `div` 8) `mod` 8)) <> + char (intToDigit (ch `mod` 8)) + where ch = ord c -- | Generate an offset into another section. This is tricky because -- this is handled differently depending on platform: Mac Os expects From git at git.haskell.org Tue Jan 13 23:00:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 23:00:06 +0000 (UTC) Subject: [commit: ghc] master: Allow the linker to run concurrently with the GC (24bbc3e) Message-ID: <20150113230006.0A22C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/24bbc3e7077f5f6cd51f118393e5342a4047978c/ghc >--------------------------------------------------------------- commit 24bbc3e7077f5f6cd51f118393e5342a4047978c Author: Simon Marlow Date: Fri Dec 19 20:10:40 2014 +0000 Allow the linker to run concurrently with the GC >--------------------------------------------------------------- 24bbc3e7077f5f6cd51f118393e5342a4047978c rts/CheckUnload.c | 4 ++-- rts/Linker.c | 13 +++++++++++++ rts/LinkerInternals.h | 1 + 3 files changed, 16 insertions(+), 2 deletions(-) diff --git a/rts/CheckUnload.c b/rts/CheckUnload.c index 73573fb..2c01113 100644 --- a/rts/CheckUnload.c +++ b/rts/CheckUnload.c @@ -260,7 +260,7 @@ void checkUnload (StgClosure *static_objects) if (unloaded_objects == NULL) return; - ACQUIRE_LOCK(&linker_mutex); + ACQUIRE_LOCK(&linker_unloaded_mutex); // Mark every unloadable object as unreferenced initially for (oc = unloaded_objects; oc; oc = oc->next) { @@ -320,5 +320,5 @@ void checkUnload (StgClosure *static_objects) freeHashTable(addrs, NULL); - RELEASE_LOCK(&linker_mutex); + RELEASE_LOCK(&linker_unloaded_mutex); } diff --git a/rts/Linker.c b/rts/Linker.c index 6bf06ed..2ba84f8 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -156,7 +156,15 @@ ObjectCode *objects = NULL; /* initially empty */ ObjectCode *unloaded_objects = NULL; /* initially empty */ #ifdef THREADED_RTS +/* This protects all the Linker's global state except unloaded_objects */ Mutex linker_mutex; +/* + * This protects unloaded_objects. We have a separate mutex for this, because + * the GC needs to access unloaded_objects in checkUnload, while the linker only + * needs to access unloaded_objects in unloadObj(), so this allows most linker + * operations proceed concurrently with the GC. + */ +Mutex linker_unloaded_mutex; #endif /* Type of the initializer */ @@ -1648,6 +1656,7 @@ initLinker_ (int retain_cafs) #if defined(THREADED_RTS) initMutex(&linker_mutex); + initMutex(&linker_unloaded_mutex); #if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) initMutex(&dl_mutex); #endif @@ -3235,9 +3244,13 @@ static HsInt unloadObj_ (pathchar *path, rtsBool just_purge) } else { prev->next = oc->next; } + ACQUIRE_LOCK(&linker_unloaded_mutex); oc->next = unloaded_objects; unloaded_objects = oc; oc->status = OBJECT_UNLOADED; + RELEASE_LOCK(&linker_unloaded_mutex); + // We do not own oc any more; it can be released at any time by + // the GC in checkUnload(). } else { prev = oc; } diff --git a/rts/LinkerInternals.h b/rts/LinkerInternals.h index 4fe533b..4eab5de 100644 --- a/rts/LinkerInternals.h +++ b/rts/LinkerInternals.h @@ -146,6 +146,7 @@ extern ObjectCode *unloaded_objects; #ifdef THREADED_RTS extern Mutex linker_mutex; +extern Mutex linker_unloaded_mutex; #endif void exitLinker( void ); From git at git.haskell.org Tue Jan 13 23:00:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 23:00:08 +0000 (UTC) Subject: [commit: ghc] master: Compile the RTS with -g by default (adc542d) Message-ID: <20150113230008.A50B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/adc542df23fd4c1766606ffcdced92beb1a192ce/ghc >--------------------------------------------------------------- commit adc542df23fd4c1766606ffcdced92beb1a192ce Author: Simon Marlow Date: Tue Jan 13 20:23:35 2015 +0000 Compile the RTS with -g by default Having debugging info doesn't hurt performance, can be stripped from binaries, and it's useful for debugging and profiling. >--------------------------------------------------------------- adc542df23fd4c1766606ffcdced92beb1a192ce mk/config.mk.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 8f134bc..40c66d9 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -344,7 +344,7 @@ LAX_DEPENDENCIES = NO # the debugging RTS flavour, rts/ghc.mk overrides these to turn off # optimisation. GhcRtsHcOpts=-O2 -GhcRtsCcOpts=-O2 -fomit-frame-pointer +GhcRtsCcOpts=-O2 -fomit-frame-pointer -g # Include support for CPU performance counters via the PAPI library in the RTS? # (PAPI: http://icl.cs.utk.edu/papi/) From git at git.haskell.org Tue Jan 13 23:00:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 23:00:11 +0000 (UTC) Subject: [commit: ghc] master: Improve documentation for -N and -qa (#9890) (2a103c7) Message-ID: <20150113230011.543903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a103c7d763c22dc9b0562dac1184ffb950da5ce/ghc >--------------------------------------------------------------- commit 2a103c7d763c22dc9b0562dac1184ffb950da5ce Author: Simon Marlow Date: Tue Dec 16 11:42:42 2014 +0000 Improve documentation for -N and -qa (#9890) >--------------------------------------------------------------- 2a103c7d763c22dc9b0562dac1184ffb950da5ce docs/users_guide/using.xml | 54 ++++++++++++++++++++++++++++++++++------------ 1 file changed, 40 insertions(+), 14 deletions(-) diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 499e486..0504fb5 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -3308,13 +3308,29 @@ data D = D !C RTS option Use x simultaneous threads when - running the program. Normally x - should be chosen to match the number of CPU cores on the - machineWhether hyperthreading cores should be counted or not is an - open question; please feel free to experiment and let us know what - results you find.. For example, - on a dual-core machine we would probably use - +RTS -N2 -RTS. + running the program. + + The runtime manages a set of virtual processors, + which we call capabilities, the + number of which is determined by the + option. Each capability can run one Haskell thread at a + time, so the number of capabilities is equal to the + number of Haskell threads that can run physically in + parallel. A capability is animated by one or more OS + threads; the runtime manages a pool of OS threads for + each capability, so that if a Haskell thread makes a + foreign call (see ) + another OS thread can take over that capability. + + + Normally x should be + chosen to match the number of CPU cores on the + machineWhether hyperthreading cores + should be counted or not is an open question; please + feel free to experiment and let us know what results you + find.. For example, on a dual-core + machine we would probably use +RTS -N2 + -RTS. Omitting x, i.e. +RTS -N -RTS, lets the runtime @@ -3331,10 +3347,11 @@ data D = D !C ). The current value of the option - is available to the Haskell program - via Control.Concurrent.getNumCapabilities, and - it may be changed while the program is running by - calling Control.Concurrent.setNumCapabilities. + is available to the Haskell program via + Control.Concurrent.getNumCapabilities, + and it may be changed while the program is running by + calling + Control.Concurrent.setNumCapabilities. @@ -3349,9 +3366,18 @@ data D = D !C option Use the OS's affinity facilities to try to pin OS - threads to CPU cores. This is an experimental feature, - and may or may not be useful. Please let us know - whether it helps for you! + threads to CPU cores. + + When this option is enabled, the OS threads for a + capability i are bound to the CPU + core i using the API provided by the + OS for setting thread affinity. e.g. on Linux + GHC uses sched_setaffinity(). + + Depending on your workload and the other activity on + the machine, this may or may not result in a performance + improvement. We recommend trying it out and measuring the + difference. From git at git.haskell.org Tue Jan 13 23:00:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Jan 2015 23:00:14 +0000 (UTC) Subject: [commit: ghc] master: Optimise scavenge_large_srt_bitmap (cf8e669) Message-ID: <20150113230014.077C93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cf8e669ba622fade18f9977aa374fda25cb078e6/ghc >--------------------------------------------------------------- commit cf8e669ba622fade18f9977aa374fda25cb078e6 Author: Simon Marlow Date: Tue Jan 13 20:33:20 2015 +0000 Optimise scavenge_large_srt_bitmap Very large modules can sometimes contain very large SRT bitmaps (this is a separate problem that I need to look into). The large bitmaps often contain a lot of zeros, so this patch skips over empty words in the bitmap. It makes a dramatic difference in the particular example that I saw, where an old gen GC was taking 0.5s before this change and 0.07s after it. >--------------------------------------------------------------- cf8e669ba622fade18f9977aa374fda25cb078e6 rts/sm/Scav.c | 34 ++++++++++++++++++++++------------ 1 file changed, 22 insertions(+), 12 deletions(-) diff --git a/rts/sm/Scav.c b/rts/sm/Scav.c index 97c6589..2ecb23b 100644 --- a/rts/sm/Scav.c +++ b/rts/sm/Scav.c @@ -276,24 +276,34 @@ scavenge_AP (StgAP *ap) static void scavenge_large_srt_bitmap( StgLargeSRT *large_srt ) { - nat i, b, size; + nat i, j, size; StgWord bitmap; StgClosure **p; - b = 0; - bitmap = large_srt->l.bitmap[b]; size = (nat)large_srt->l.size; p = (StgClosure **)large_srt->srt; - for (i = 0; i < size; ) { - if ((bitmap & 1) != 0) { - evacuate(p); - } - i++; - p++; - if (i % BITS_IN(W_) == 0) { - b++; - bitmap = large_srt->l.bitmap[b]; + + for (i = 0; i < size / BITS_IN(W_); i++) { + bitmap = large_srt->l.bitmap[i]; + if (bitmap != 0) { + for (j = 0; j < BITS_IN(W_); j++) { + if ((bitmap & 1) != 0) { + evacuate(p); + } + p++; + bitmap = bitmap >> 1; + } } else { + p += BITS_IN(W_); + } + } + if (size % BITS_IN(W_) != 0) { + bitmap = large_srt->l.bitmap[i]; + for (j = 0; j < size % BITS_IN(W_); j++) { + if ((bitmap & 1) != 0) { + evacuate(p); + } + p++; bitmap = bitmap >> 1; } } From git at git.haskell.org Wed Jan 14 12:52:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 12:52:57 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Allow the linker to run concurrently with the GC (8608429) Message-ID: <20150114125257.582483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/860842904fc28406cea0cf070e06be6e07643abb/ghc >--------------------------------------------------------------- commit 860842904fc28406cea0cf070e06be6e07643abb Author: Simon Marlow Date: Fri Dec 19 20:10:40 2014 +0000 Allow the linker to run concurrently with the GC (cherry picked from commit 24bbc3e7077f5f6cd51f118393e5342a4047978c) >--------------------------------------------------------------- 860842904fc28406cea0cf070e06be6e07643abb rts/CheckUnload.c | 4 ++-- rts/Linker.c | 13 +++++++++++++ rts/LinkerInternals.h | 1 + 3 files changed, 16 insertions(+), 2 deletions(-) diff --git a/rts/CheckUnload.c b/rts/CheckUnload.c index 73573fb..2c01113 100644 --- a/rts/CheckUnload.c +++ b/rts/CheckUnload.c @@ -260,7 +260,7 @@ void checkUnload (StgClosure *static_objects) if (unloaded_objects == NULL) return; - ACQUIRE_LOCK(&linker_mutex); + ACQUIRE_LOCK(&linker_unloaded_mutex); // Mark every unloadable object as unreferenced initially for (oc = unloaded_objects; oc; oc = oc->next) { @@ -320,5 +320,5 @@ void checkUnload (StgClosure *static_objects) freeHashTable(addrs, NULL); - RELEASE_LOCK(&linker_mutex); + RELEASE_LOCK(&linker_unloaded_mutex); } diff --git a/rts/Linker.c b/rts/Linker.c index 4a0e5ea..29a4b75 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -156,7 +156,15 @@ ObjectCode *objects = NULL; /* initially empty */ ObjectCode *unloaded_objects = NULL; /* initially empty */ #ifdef THREADED_RTS +/* This protects all the Linker's global state except unloaded_objects */ Mutex linker_mutex; +/* + * This protects unloaded_objects. We have a separate mutex for this, because + * the GC needs to access unloaded_objects in checkUnload, while the linker only + * needs to access unloaded_objects in unloadObj(), so this allows most linker + * operations proceed concurrently with the GC. + */ +Mutex linker_unloaded_mutex; #endif /* Type of the initializer */ @@ -1647,6 +1655,7 @@ initLinker_ (int retain_cafs) #if defined(THREADED_RTS) initMutex(&linker_mutex); + initMutex(&linker_unloaded_mutex); #if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) initMutex(&dl_mutex); #endif @@ -3234,9 +3243,13 @@ static HsInt unloadObj_ (pathchar *path, rtsBool just_purge) } else { prev->next = oc->next; } + ACQUIRE_LOCK(&linker_unloaded_mutex); oc->next = unloaded_objects; unloaded_objects = oc; oc->status = OBJECT_UNLOADED; + RELEASE_LOCK(&linker_unloaded_mutex); + // We do not own oc any more; it can be released at any time by + // the GC in checkUnload(). } else { prev = oc; } diff --git a/rts/LinkerInternals.h b/rts/LinkerInternals.h index 4fe533b..4eab5de 100644 --- a/rts/LinkerInternals.h +++ b/rts/LinkerInternals.h @@ -146,6 +146,7 @@ extern ObjectCode *unloaded_objects; #ifdef THREADED_RTS extern Mutex linker_mutex; +extern Mutex linker_unloaded_mutex; #endif void exitLinker( void ); From git at git.haskell.org Wed Jan 14 12:52:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 12:52:59 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Improve documentation for -N and -qa (#9890) (bb56695) Message-ID: <20150114125259.E743D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/bb56695b98b20d0e28a30b360265e2b147cc2f24/ghc >--------------------------------------------------------------- commit bb56695b98b20d0e28a30b360265e2b147cc2f24 Author: Simon Marlow Date: Tue Dec 16 11:42:42 2014 +0000 Improve documentation for -N and -qa (#9890) (cherry picked from commit 2a103c7d763c22dc9b0562dac1184ffb950da5ce) >--------------------------------------------------------------- bb56695b98b20d0e28a30b360265e2b147cc2f24 docs/users_guide/using.xml | 54 ++++++++++++++++++++++++++++++++++------------ 1 file changed, 40 insertions(+), 14 deletions(-) diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 3059cff..83c69ce 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -3261,13 +3261,29 @@ data D = D !C RTS option Use x simultaneous threads when - running the program. Normally x - should be chosen to match the number of CPU cores on the - machineWhether hyperthreading cores should be counted or not is an - open question; please feel free to experiment and let us know what - results you find.. For example, - on a dual-core machine we would probably use - +RTS -N2 -RTS. + running the program. + + The runtime manages a set of virtual processors, + which we call capabilities, the + number of which is determined by the + option. Each capability can run one Haskell thread at a + time, so the number of capabilities is equal to the + number of Haskell threads that can run physically in + parallel. A capability is animated by one or more OS + threads; the runtime manages a pool of OS threads for + each capability, so that if a Haskell thread makes a + foreign call (see ) + another OS thread can take over that capability. + + + Normally x should be + chosen to match the number of CPU cores on the + machineWhether hyperthreading cores + should be counted or not is an open question; please + feel free to experiment and let us know what results you + find.. For example, on a dual-core + machine we would probably use +RTS -N2 + -RTS. Omitting x, i.e. +RTS -N -RTS, lets the runtime @@ -3284,10 +3300,11 @@ data D = D !C ). The current value of the option - is available to the Haskell program - via Control.Concurrent.getNumCapabilities, and - it may be changed while the program is running by - calling Control.Concurrent.setNumCapabilities. + is available to the Haskell program via + Control.Concurrent.getNumCapabilities, + and it may be changed while the program is running by + calling + Control.Concurrent.setNumCapabilities. @@ -3302,9 +3319,18 @@ data D = D !C option Use the OS's affinity facilities to try to pin OS - threads to CPU cores. This is an experimental feature, - and may or may not be useful. Please let us know - whether it helps for you! + threads to CPU cores. + + When this option is enabled, the OS threads for a + capability i are bound to the CPU + core i using the API provided by the + OS for setting thread affinity. e.g. on Linux + GHC uses sched_setaffinity(). + + Depending on your workload and the other activity on + the machine, this may or may not result in a performance + improvement. We recommend trying it out and measuring the + difference. From git at git.haskell.org Wed Jan 14 12:53:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 12:53:02 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Compile the RTS with -g by default (fb582ef) Message-ID: <20150114125302.96D463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/fb582eff577c0ec888716abc68fff2232a51f8d3/ghc >--------------------------------------------------------------- commit fb582eff577c0ec888716abc68fff2232a51f8d3 Author: Simon Marlow Date: Tue Jan 13 20:23:35 2015 +0000 Compile the RTS with -g by default Having debugging info doesn't hurt performance, can be stripped from binaries, and it's useful for debugging and profiling. (cherry picked from commit adc542df23fd4c1766606ffcdced92beb1a192ce) >--------------------------------------------------------------- fb582eff577c0ec888716abc68fff2232a51f8d3 mk/config.mk.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 8f134bc..40c66d9 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -344,7 +344,7 @@ LAX_DEPENDENCIES = NO # the debugging RTS flavour, rts/ghc.mk overrides these to turn off # optimisation. GhcRtsHcOpts=-O2 -GhcRtsCcOpts=-O2 -fomit-frame-pointer +GhcRtsCcOpts=-O2 -fomit-frame-pointer -g # Include support for CPU performance counters via the PAPI library in the RTS? # (PAPI: http://icl.cs.utk.edu/papi/) From git at git.haskell.org Wed Jan 14 12:53:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 12:53:05 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Optimise scavenge_large_srt_bitmap (a7060f9) Message-ID: <20150114125305.33CB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a7060f9946379f49dc906ba67a88f359cee44ca9/ghc >--------------------------------------------------------------- commit a7060f9946379f49dc906ba67a88f359cee44ca9 Author: Simon Marlow Date: Tue Jan 13 20:33:20 2015 +0000 Optimise scavenge_large_srt_bitmap Very large modules can sometimes contain very large SRT bitmaps (this is a separate problem that I need to look into). The large bitmaps often contain a lot of zeros, so this patch skips over empty words in the bitmap. It makes a dramatic difference in the particular example that I saw, where an old gen GC was taking 0.5s before this change and 0.07s after it. (cherry picked from commit cf8e669ba622fade18f9977aa374fda25cb078e6) >--------------------------------------------------------------- a7060f9946379f49dc906ba67a88f359cee44ca9 rts/sm/Scav.c | 34 ++++++++++++++++++++++------------ 1 file changed, 22 insertions(+), 12 deletions(-) diff --git a/rts/sm/Scav.c b/rts/sm/Scav.c index 97c6589..2ecb23b 100644 --- a/rts/sm/Scav.c +++ b/rts/sm/Scav.c @@ -276,24 +276,34 @@ scavenge_AP (StgAP *ap) static void scavenge_large_srt_bitmap( StgLargeSRT *large_srt ) { - nat i, b, size; + nat i, j, size; StgWord bitmap; StgClosure **p; - b = 0; - bitmap = large_srt->l.bitmap[b]; size = (nat)large_srt->l.size; p = (StgClosure **)large_srt->srt; - for (i = 0; i < size; ) { - if ((bitmap & 1) != 0) { - evacuate(p); - } - i++; - p++; - if (i % BITS_IN(W_) == 0) { - b++; - bitmap = large_srt->l.bitmap[b]; + + for (i = 0; i < size / BITS_IN(W_); i++) { + bitmap = large_srt->l.bitmap[i]; + if (bitmap != 0) { + for (j = 0; j < BITS_IN(W_); j++) { + if ((bitmap & 1) != 0) { + evacuate(p); + } + p++; + bitmap = bitmap >> 1; + } } else { + p += BITS_IN(W_); + } + } + if (size % BITS_IN(W_) != 0) { + bitmap = large_srt->l.bitmap[i]; + for (j = 0; j < size % BITS_IN(W_); j++) { + if ((bitmap & 1) != 0) { + evacuate(p); + } + p++; bitmap = bitmap >> 1; } } From git at git.haskell.org Wed Jan 14 16:08:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 16:08:34 +0000 (UTC) Subject: [commit: ghc] master: Correct typos in comments to mkDataCon (0afa37a) Message-ID: <20150114160834.1AEB23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0afa37aa342c5c2087b225de76afa23cc2229d9f/ghc >--------------------------------------------------------------- commit 0afa37aa342c5c2087b225de76afa23cc2229d9f Author: Simon Peyton Jones Date: Mon Jan 12 11:19:10 2015 +0000 Correct typos in comments to mkDataCon >--------------------------------------------------------------- 0afa37aa342c5c2087b225de76afa23cc2229d9f compiler/basicTypes/DataCon.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs index 593e0ed..200bf21 100644 --- a/compiler/basicTypes/DataCon.hs +++ b/compiler/basicTypes/DataCon.hs @@ -619,8 +619,8 @@ isMarkedStrict _ = True -- All others are strict -- | Build a new data constructor mkDataCon :: Name -> Bool -- ^ Is the constructor declared infix? - -> [HsBang] -- ^ Strictness/unpack annotations, from user, of - -- (for imported DataCons) from the interface file + -> [HsBang] -- ^ Strictness/unpack annotations, from user; + -- or, for imported DataCons, from the interface file -> [FieldLabel] -- ^ Field labels for the constructor, if it is a record, -- otherwise empty -> [TyVar] -- ^ Universally quantified type variables From git at git.haskell.org Wed Jan 14 16:08:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 16:08:36 +0000 (UTC) Subject: [commit: ghc] master: Tighten up constraint solve order for RULES (6b0cf0e) Message-ID: <20150114160836.B79633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6b0cf0e07605d2cde9b4e13b40f52628b6fe64ec/ghc >--------------------------------------------------------------- commit 6b0cf0e07605d2cde9b4e13b40f52628b6fe64ec Author: Simon Peyton Jones Date: Wed Jan 14 10:53:49 2015 +0000 Tighten up constraint solve order for RULES The main point is described in Note [Solve order for RULES]. I'm not sure if the potential bug described there could actually happen, but I bet it could. Anyway, this patch explicitly solves LHS constraints and *then* RHS constraints (see the Note). I also moved simplifyRule from TcSimplify (a large module) to TcRules (a small one), which brings related code together. It did mean I had to export runTcS from TcSimplify, but I think that's a price worth paying. >--------------------------------------------------------------- 6b0cf0e07605d2cde9b4e13b40f52628b6fe64ec compiler/typecheck/TcRules.hs | 243 ++++++++++++++------- compiler/typecheck/TcSimplify.hs | 67 +----- testsuite/tests/typecheck/should_fail/T5853.stderr | 19 +- 3 files changed, 181 insertions(+), 148 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6b0cf0e07605d2cde9b4e13b40f52628b6fe64ec From git at git.haskell.org Wed Jan 14 16:08:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 16:08:39 +0000 (UTC) Subject: [commit: ghc] master: Refactor handling of SPECIALISE pragmas (Trac #5821) (7884132) Message-ID: <20150114160839.7C79B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/788413297eaddfa259d2ab76459a916a62d2604c/ghc >--------------------------------------------------------------- commit 788413297eaddfa259d2ab76459a916a62d2604c Author: Simon Peyton Jones Date: Wed Jan 14 10:58:22 2015 +0000 Refactor handling of SPECIALISE pragmas (Trac #5821) The provoking cause was Trac #5821, which concerned type families, but in fixing it I did the usual round of tidying up and docmenting. The main comment is now Note [Handling SPECIALISE pragmas] in TcBinds. It is "wrinkle 2" that fixes #5821. >--------------------------------------------------------------- 788413297eaddfa259d2ab76459a916a62d2604c compiler/deSugar/DsBinds.hs | 42 +---- compiler/typecheck/TcBinds.hs | 218 +++++++++++++++++++----- compiler/typecheck/TcInstDcls.hs | 3 +- compiler/typecheck/TcRnTypes.hs | 14 +- testsuite/tests/parser/should_fail/T7848.stderr | 7 +- 5 files changed, 193 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 788413297eaddfa259d2ab76459a916a62d2604c From git at git.haskell.org Wed Jan 14 16:08:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 16:08:42 +0000 (UTC) Subject: [commit: ghc] master: Tiny refactoring (shorter, simpler code) (e4cb837) Message-ID: <20150114160842.283DD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e4cb8370eb910f187a536c208fba15dcf331c910/ghc >--------------------------------------------------------------- commit e4cb8370eb910f187a536c208fba15dcf331c910 Author: Simon Peyton Jones Date: Wed Jan 14 10:55:17 2015 +0000 Tiny refactoring (shorter, simpler code) >--------------------------------------------------------------- e4cb8370eb910f187a536c208fba15dcf331c910 compiler/typecheck/TcSimplify.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index a29e1dc..773a5e6 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -688,10 +688,9 @@ solveWantedsTcM :: WantedConstraints -> TcM (WantedConstraints, Bag EvBind) -- Discards all Derived stuff in result -- Postcondition: fully zonked and unflattened constraints solveWantedsTcM wanted - = do { ev_binds_var <- TcM.newTcEvBinds - ; wanteds' <- solveWantedsTcMWithEvBinds ev_binds_var wanted solveWantedsAndDrop - ; binds <- TcRnMonad.getTcEvBinds ev_binds_var - ; return (wanteds', binds) } + = do { (wanted1, binds) <- runTcS (solveWantedsAndDrop wanted) + ; wanted2 <- zonkWC wanted1 + ; return (wanted2, binds) } solveWantedsAndDrop :: WantedConstraints -> TcS (WantedConstraints) -- Since solveWanteds returns the residual WantedConstraints, From git at git.haskell.org Wed Jan 14 17:11:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 17:11:19 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #5821 (c823b73) Message-ID: <20150114171119.CF01C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c823b73cb2ca8e2392e2a4c48286879cc7baa51c/ghc >--------------------------------------------------------------- commit c823b73cb2ca8e2392e2a4c48286879cc7baa51c Author: Simon Peyton Jones Date: Wed Jan 14 17:12:29 2015 +0000 Test Trac #5821 And rename the wrongly named rebindable/T5821 to T5908 (Trac #5908) >--------------------------------------------------------------- c823b73cb2ca8e2392e2a4c48286879cc7baa51c testsuite/tests/rebindable/{T5821.hs => T5908.hs} | 2 +- testsuite/tests/rebindable/all.T | 2 +- testsuite/tests/simplCore/should_compile/T5821.hs | 11 +++++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 4 files changed, 14 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/rebindable/T5821.hs b/testsuite/tests/rebindable/T5908.hs similarity index 99% rename from testsuite/tests/rebindable/T5821.hs rename to testsuite/tests/rebindable/T5908.hs index 6adc356..32a4d4e 100644 --- a/testsuite/tests/rebindable/T5821.hs +++ b/testsuite/tests/rebindable/T5908.hs @@ -4,7 +4,7 @@ ExplicitForAll , GADTs , RebindableSyntax #-} -module T5821a +module T5908 ( Writer , runWriter , execWriter diff --git a/testsuite/tests/rebindable/all.T b/testsuite/tests/rebindable/all.T index a2a37d7..70628fa 100644 --- a/testsuite/tests/rebindable/all.T +++ b/testsuite/tests/rebindable/all.T @@ -30,4 +30,4 @@ test('DoParamM', reqlib('mtl'), compile_fail, ['']) test('T5038', normal, compile_and_run, ['']) test('T4851', normal, compile, ['']) -test('T5821', normal, compile, ['']) +test('T5908', normal, compile, ['']) diff --git a/testsuite/tests/simplCore/should_compile/T5821.hs b/testsuite/tests/simplCore/should_compile/T5821.hs new file mode 100644 index 0000000..762254c --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T5821.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -fno-warn-redundant-constraints #-} +module T5821 where + +type family T a +type instance T Int = Bool + +foo :: Num a => a -> T a +foo = undefined + +{-# SPECIALISE foo :: Int -> Bool #-} diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 2ce58ec..0ffe974 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -209,3 +209,4 @@ test('T6056', only_ways(['optasm']), multimod_compile, ['T6056', '-v0 -ddump-rul test('T9400', only_ways(['optasm']), compile, ['-O0 -ddump-simpl -dsuppress-uniques']) test('T9583', only_ways(['optasm']), compile, ['']) test('T9565', only_ways(['optasm']), compile, ['']) +test('T5821', only_ways(['optasm']), compile, ['']) From git at git.haskell.org Wed Jan 14 19:50:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 19:50:56 +0000 (UTC) Subject: [commit: ghc] master: Add Eq, Ord, Show, and Read instances for Const (c71fb84) Message-ID: <20150114195056.3D79A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c71fb84b8c9ec9c1e279df8c75ceb8a537801aa1/ghc >--------------------------------------------------------------- commit c71fb84b8c9ec9c1e279df8c75ceb8a537801aa1 Author: Fumiaki Kinoshita Date: Wed Jan 14 20:41:30 2015 +0900 Add Eq, Ord, Show, and Read instances for Const As suggested in https://www.haskell.org/pipermail/libraries/2013-October/021531.html this adds the following instances - `Show a => Show (Const a b)` - `Read a => Read (Const a b)` - `Eq a => Eq (Const a b)` - `Ord a => Ord (Const a b)` The Read/Show instances are defined in such a way as if `Const` was defined without record-syntax (i.e. as `newtype Const a b = Const a`) Addresses #9984 Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D619 >--------------------------------------------------------------- c71fb84b8c9ec9c1e279df8c75ceb8a537801aa1 libraries/base/Control/Applicative.hs | 14 +++++++++++--- libraries/base/changelog.md | 3 ++- 2 files changed, 13 insertions(+), 4 deletions(-) diff --git a/libraries/base/Control/Applicative.hs b/libraries/base/Control/Applicative.hs index a0627e4..02062e2 100644 --- a/libraries/base/Control/Applicative.hs +++ b/libraries/base/Control/Applicative.hs @@ -61,11 +61,19 @@ import Data.Functor ((<$>)) import GHC.Base import GHC.Generics import GHC.List (repeat, zipWith) -import GHC.Read (Read) -import GHC.Show (Show) +import GHC.Read (Read(readsPrec), readParen, lex) +import GHC.Show (Show(showsPrec), showParen, showString) newtype Const a b = Const { getConst :: a } - deriving (Generic, Generic1, Monoid) + deriving (Generic, Generic1, Monoid, Eq, Ord) + +instance Read a => Read (Const a b) where + readsPrec d = readParen (d > 10) + $ \r -> [(Const x,t) | ("Const", s) <- lex r, (x, t) <- readsPrec 11 s] + +instance Show a => Show (Const a b) where + showsPrec d (Const x) = showParen (d > 10) $ + showString "Const " . showsPrec 11 x instance Foldable (Const m) where foldMap _ _ = mempty diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 76a6a19..83ae5e4 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -176,7 +176,8 @@ * There are now `Foldable` and `Traversable` instances for `Either a`, `Const r`, and `(,) a`. - * There is now a `Monoid`, `Generic`, and `Generic1` instance for `Const`. + * There are now `Show`, `Read`, `Eq`, `Ord`, `Monoid`, `Generic`, and + `Generic1` instances for `Const`. * There is now a `Data` instance for `Data.Version`. From git at git.haskell.org Wed Jan 14 19:57:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Jan 2015 19:57:16 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Add Eq, Ord, Show, and Read instances for Const (aaca7bd) Message-ID: <20150114195716.EEA8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/aaca7bdfa6202895946ac253a3196c4efa5747b7/ghc >--------------------------------------------------------------- commit aaca7bdfa6202895946ac253a3196c4efa5747b7 Author: Fumiaki Kinoshita Date: Wed Jan 14 20:41:30 2015 +0900 Add Eq, Ord, Show, and Read instances for Const As suggested in https://www.haskell.org/pipermail/libraries/2013-October/021531.html this adds the following instances - `Show a => Show (Const a b)` - `Read a => Read (Const a b)` - `Eq a => Eq (Const a b)` - `Ord a => Ord (Const a b)` The Read/Show instances are defined in such a way as if `Const` was defined without record-syntax (i.e. as `newtype Const a b = Const a`) Addresses #9984 (cherry picked from commit c71fb84b8c9ec9c1e279df8c75ceb8a537801aa1) >--------------------------------------------------------------- aaca7bdfa6202895946ac253a3196c4efa5747b7 libraries/base/Control/Applicative.hs | 14 +++++++++++--- libraries/base/changelog.md | 3 ++- 2 files changed, 13 insertions(+), 4 deletions(-) diff --git a/libraries/base/Control/Applicative.hs b/libraries/base/Control/Applicative.hs index a0627e4..02062e2 100644 --- a/libraries/base/Control/Applicative.hs +++ b/libraries/base/Control/Applicative.hs @@ -61,11 +61,19 @@ import Data.Functor ((<$>)) import GHC.Base import GHC.Generics import GHC.List (repeat, zipWith) -import GHC.Read (Read) -import GHC.Show (Show) +import GHC.Read (Read(readsPrec), readParen, lex) +import GHC.Show (Show(showsPrec), showParen, showString) newtype Const a b = Const { getConst :: a } - deriving (Generic, Generic1, Monoid) + deriving (Generic, Generic1, Monoid, Eq, Ord) + +instance Read a => Read (Const a b) where + readsPrec d = readParen (d > 10) + $ \r -> [(Const x,t) | ("Const", s) <- lex r, (x, t) <- readsPrec 11 s] + +instance Show a => Show (Const a b) where + showsPrec d (Const x) = showParen (d > 10) $ + showString "Const " . showsPrec 11 x instance Foldable (Const m) where foldMap _ _ = mempty diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 76a6a19..83ae5e4 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -176,7 +176,8 @@ * There are now `Foldable` and `Traversable` instances for `Either a`, `Const r`, and `(,) a`. - * There is now a `Monoid`, `Generic`, and `Generic1` instance for `Const`. + * There are now `Show`, `Read`, `Eq`, `Ord`, `Monoid`, `Generic`, and + `Generic1` instances for `Const`. * There is now a `Data` instance for `Data.Version`. From git at git.haskell.org Fri Jan 16 10:48:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 10:48:11 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Fixed bug in DataCon instantiation, in PM Check (3bd3d32) Message-ID: <20150116104811.A92DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/3bd3d327f892660e8d2a52937ccae1b3b20f4ab3/ghc >--------------------------------------------------------------- commit 3bd3d327f892660e8d2a52937ccae1b3b20f4ab3 Author: George Karachalias Date: Fri Jan 16 11:49:03 2015 +0100 Fixed bug in DataCon instantiation, in PM Check also: * Made function `to_tc_type' a top-level function `toTcType' * Transformed DataCon's theta Types to TcTypes before storing in DsEnv Yet, the `impossible happened' is persistent. >--------------------------------------------------------------- 3bd3d327f892660e8d2a52937ccae1b3b20f4ab3 compiler/basicTypes/Var.hs | 3 +- compiler/deSugar/Check.hs | 67 +++++++++++++++++++++++++++++-------------- compiler/deSugar/Match.hs | 5 ++-- compiler/typecheck/TcMType.hs | 8 +----- 4 files changed, 51 insertions(+), 32 deletions(-) diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index 925ffe3..4cac5d5 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -307,7 +307,8 @@ mkTcTyVar name kind details tcTyVarDetails :: TyVar -> TcTyVarDetails tcTyVarDetails (TcTyVar { tc_tv_details = details }) = details -tcTyVarDetails var = pprPanic "tcTyVarDetails" (ppr var) +tcTyVarDetails tv@(TyVar {}) = pprPanic "tcTyVarDetails" (ptext (sLit "TyVar") $$ ppr tv) +tcTyVarDetails tv@(Id {}) = pprPanic "tcTyVarDetails" (ptext (sLit "Id") $$ ppr tv) setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVar setTcTyVarDetails tv details = tv { tc_tv_details = details } diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 3bc934a..2a8dbfe 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -7,7 +7,7 @@ {-# LANGUAGE CPP #-} -module Check ( checkpm, PmResult, pprUncovered ) where +module Check ( checkpm, PmResult, pprUncovered, toTcTypeBag ) where #include "HsVersions.h" @@ -32,19 +32,24 @@ import DsMonad ( DsM, initTcDsForSolver, getDictsDs, addDictsDs, DsGblEnv, DsLcl import TcSimplify( tcCheckSatisfiability ) import TcMType (freshTyVarPmM) import UniqSupply (MonadUnique(..)) -import TcType ( Type, TcType, mkTcEqPred, vanillaSkolemTv ) +import TcType ( TcType, mkTcEqPred, vanillaSkolemTv ) import Var ( EvVar, varType, tyVarKind, tyVarName, mkTcTyVar ) import VarSet -import Type( mkTyVarTys ) +import Type( substTys, substTyVars, substTheta, TvSubst, mkTopTvSubst ) import TypeRep ( Type(..) ) import Bag (Bag, unitBag, listToBag, emptyBag, unionBags, mapBag) import Type (expandTypeSynonyms, mkTyConApp) import TcRnTypes (TcRnIf) import ErrUtils -import Control.Monad ( forM, foldM, liftM2, filterM ) +import Control.Monad ( forM, foldM, liftM2, filterM, replicateM ) import Control.Applicative (Applicative(..), (<$>)) +-- Checking Things +import Bag (mapBagM) +import Type (tyVarsOfType) +import Var (setTyVarKind) + {- This module checks pattern matches for: \begin{enumerate} @@ -278,9 +283,12 @@ nameType name ty = do newEvVar :: Name -> Type -> PmM EvVar newEvVar name ty - = do { ty' <- to_tc_type emptyVarSet ty + = do { ty' <- toTcType ty ; return (mkLocalId name ty') } - where + +toTcType :: Type -> PmM TcType +toTcType ty = to_tc_type emptyVarSet ty + where to_tc_type :: VarSet -> Type -> PmM TcType -- The constraint solver expects EvVars to have TcType, in which the -- free type variables are TcTyVars. So we convert from Type to TcType here @@ -295,17 +303,34 @@ newEvVar name ty to_tc_type ftvs (ForAllTy tv ty) = ForAllTy tv <$> to_tc_type (ftvs `extendVarSet` tv) ty to_tc_type ftvs (LitTy l) = return (LitTy l) --- This is problematic. Everytime we call mkConFull, we use the same --- type variables that appear in the declaration of the constructor. --- What we actually want is to instantiate alla variables every time --- with fresh unification variables. -mkConFull :: DataCon -> PmM (PmPat Id) -mkConFull con = PmConPat ty con <$> mapM freshPmVar arg_tys +toTcTypeBag :: Bag EvVar -> DsM (Bag EvVar) +toTcTypeBag evvars = do + (Just ans) <- runPmM $ mapBagM toTc evvars + return ans + where + toTc tyvar = do + ty' <- toTcType (tyVarKind tyvar) + return (setTyVarKind tyvar ty') + +mkConFull :: DataCon -> PmM (PmPat Id, [EvVar]) +mkConFull con = do + subst <- mkConSigSubst con + let tycon = dataConOrigTyCon con -- Type constructors + arg_tys = substTys subst (dataConOrigArgTys con) -- Argument types + univ_tys = substTyVars subst (dataConUnivTyVars con) -- Universal variables (to instantiate tycon) + ty = mkTyConApp tycon univ_tys -- Type of the pattern + evvars <- mapM (nameType "varcon") $ substTheta subst (dataConTheta con) -- Constraints (all of them) + con_pat <- PmConPat ty con <$> mapM freshPmVar arg_tys + return (con_pat, evvars) + +mkConSigSubst :: DataCon -> PmM TvSubst +mkConSigSubst con = do + tvs <- replicateM notys (liftPmM freshTyVarPmM) + return (mkTopTvSubst (tyvars `zip` tvs)) where - tycon = dataConOrigTyCon con -- get the tycon - arg_tys = dataConOrigArgTys con -- types of the arguments - univ_tys = dataConUnivTyVars con -- to instantiate tycon - ty = mkTyConApp tycon (mkTyVarTys univ_tys) + -- Both existential and unviversal type variables + tyvars = dataConUnivTyVars con ++ dataConExTyVars con + notys = length tyvars {- %************************************************************************ @@ -469,11 +494,8 @@ one_step (delta, uvec@((PmConPat ty1 con1 ps1) : us)) ((PmConPat ty2 con2 ps2) : -- var-con one_step uvec@(_, (PmVarPat ty var):_) vec@((PmConPat _ con _) : _) = do all_con_pats <- mapM mkConFull (allConstructors con) - triples <- forM all_con_pats $ \con_pat -> do + triples <- forM all_con_pats $ \(con_pat, evvars) -> do evvar <- newEqPmM ty (pm_ty con_pat) -- The variable must match with the constructor pattern (alpha ~ T a b c) - let thetas = dataConTheta (pm_pat_con con_pat) -- all other constraints that the contructor has - -- SPJ: this doesn't look right; need to instantiate the DataCon - evvars <- mapM (nameType "varcon") thetas addDictsPm (listToBag (evvar:evvars)) $ one_step (substPmVec var con_pat uvec) vec let result = union_triples triples @@ -557,8 +579,9 @@ checkpm tys = runPmM . checkpmPmM tys -- the first set of uncovered vectors (i.e., a single wildcard-vector). checkpmPmM :: [Type] -> [EquationInfo] -> PmM PmResult checkpmPmM _ [] = return ([],[],[]) -checkpmPmM tys eq_infos = do - init_pats <- mapM freshPmVar tys +checkpmPmM tys' eq_infos = do + tys <- mapM toTcType tys' -- Not sure if this is correct + init_pats <- mapM (freshPmVar . expandTypeSynonyms) tys init_delta <- addEnvEvVars empty_delta checkpm' [(init_delta, init_pats)] eq_infos diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs index 8b4ea7b..646296a 100644 --- a/compiler/deSugar/Match.hs +++ b/compiler/deSugar/Match.hs @@ -705,8 +705,9 @@ matchWrapper ctxt (MG { mg_alts = matches ; return (new_vars, result_expr) } where mk_eqn_info (L _ (Match pats _ grhss)) - = do { let upats = map unLoc pats - dicts = collectEvVarsPats upats -- check rhs with constraints from match in scope + = do { let upats = map unLoc pats + dicts' = collectEvVarsPats upats -- check rhs with constraints from match in scope + ; dicts <- toTcTypeBag dicts' -- Only TcTyVars ; match_result <- addDictsDs dicts $ dsGRHSs ctxt upats grhss rhs_ty ; return (EqnInfo { eqn_pats = upats, eqn_rhs = match_result}) } diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 76f424f..e13d97f 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1005,15 +1005,9 @@ isWildcardVar _ = False % Generating fresh variables for pattern match check -} --- This needs to be checked again (too messy) freshTyVarPmM :: TcRnIf gbl lcl Type freshTyVarPmM = do uniq <- newUnique - ref <- newMutVar Flexi let name = mkTcTyVarName uniq (fsLit "r") - details = MetaTv { mtv_info = ReturnTv -- (is this better?) TauTv True -- All this seems really bad - , mtv_ref = ref - , mtv_tclvl = fskTcLevel } -- mtv_untch = noUntouchables } - tc_tyvar = mkTcTyVar name openTypeKind details + tc_tyvar = mkTcTyVar name openTypeKind vanillaSkolemTv return (TyVarTy tc_tyvar) - From git at git.haskell.org Fri Jan 16 13:31:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 13:31:00 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: aclocal.m4: fix == bashism in FIND_LLVM_PROG (4a4d179) Message-ID: <20150116133100.51AF03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/4a4d17975f10c8f696a91e881abc65daeb7bc733/ghc >--------------------------------------------------------------- commit 4a4d17975f10c8f696a91e881abc65daeb7bc733 Author: Tuncer Ayaz Date: Mon Jan 12 05:14:45 2015 -0600 aclocal.m4: fix == bashism in FIND_LLVM_PROG (cherry picked from commit 0fa4240249058f327cfd283f9da2deb8dff664f1) >--------------------------------------------------------------- 4a4d17975f10c8f696a91e881abc65daeb7bc733 aclocal.m4 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 6caa10a..6933e6f 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2072,7 +2072,7 @@ AC_DEFUN([XCODE_VERSION],[ # AC_DEFUN([FIND_LLVM_PROG],[ FP_ARG_WITH_PATH_GNU_PROG_OPTIONAL_NOTARGET([$1], [$2], [$3]) - if test "$$1" == ""; then + if test "$$1" = ""; then save_IFS=$IFS IFS=":;" for p in ${PATH}; do From git at git.haskell.org Fri Jan 16 14:17:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 14:17:34 +0000 (UTC) Subject: [commit: ghc] master: Repsect the package name when checking for self-import (fb7c311) Message-ID: <20150116141734.0B03C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fb7c311711c8851d0de1e40231150ad999ae9c2b/ghc >--------------------------------------------------------------- commit fb7c311711c8851d0de1e40231150ad999ae9c2b Author: Simon Peyton Jones Date: Fri Jan 16 14:17:14 2015 +0000 Repsect the package name when checking for self-import Fixes Trac #9997. In doing this I tripped across the specialness of "this" in PackageImports. The magic constant (fsLit "this") is scattered across the compiler and ought to be put in one place. But where? >--------------------------------------------------------------- fb7c311711c8851d0de1e40231150ad999ae9c2b compiler/rename/RnNames.hs | 10 +++++++++- testsuite/tests/module/T9997.hs | 5 +++++ testsuite/tests/module/all.T | 1 + 3 files changed, 15 insertions(+), 1 deletion(-) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index 5cb7b18..84a56f0 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -186,7 +186,15 @@ rnImportDecl this_mod -- at least not until TcIface.tcHiBootIface, which is too late to avoid -- typechecker crashes. ToDo: what about indirect self-import? -- But 'import {-# SOURCE #-} M' is ok, even if a bit odd - when (not want_boot && imp_mod_name == moduleName this_mod) + when (not want_boot && + imp_mod_name == moduleName this_mod && + (case mb_pkg of -- If we have import "" M, then we should + -- check that "" is "this" (which is magic) + -- or the name of this_mod's package. Yurgh! + -- c.f. GHC.findModule, and Trac #9997 + Nothing -> True + Just pkg_fs -> pkg_fs == fsLit "this" || + fsToPackageKey pkg_fs == modulePackageKey this_mod)) (addErr (ptext (sLit "A module cannot import itself:") <+> ppr imp_mod_name)) -- Check for a missing import list (Opt_WarnMissingImportList also diff --git a/testsuite/tests/module/T9997.hs b/testsuite/tests/module/T9997.hs new file mode 100644 index 0000000..acc82da --- /dev/null +++ b/testsuite/tests/module/T9997.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE PackageImports #-} +module Control.DeepSeq where + +import "deepseq" Control.DeepSeq + diff --git a/testsuite/tests/module/all.T b/testsuite/tests/module/all.T index c91d30c..58632be 100644 --- a/testsuite/tests/module/all.T +++ b/testsuite/tests/module/all.T @@ -344,3 +344,4 @@ test('T414a', normal, compile, ['']) test('T414b', normal, compile, ['']) test('T3776', normal, compile, ['']) test('T9061', normal, compile, ['']) +test('T9997', normal, compile, ['']) From git at git.haskell.org Fri Jan 16 14:17:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 14:17:37 +0000 (UTC) Subject: [commit: ghc] master: Fix a terrible bug in the canonicaliser which led to an infinite loop (854e7b8) Message-ID: <20150116141737.3AE7F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/854e7b8efdd7fe5fcba77e1e049e8a835f03b16a/ghc >--------------------------------------------------------------- commit 854e7b8efdd7fe5fcba77e1e049e8a835f03b16a Author: Simon Peyton Jones Date: Fri Jan 16 14:18:34 2015 +0000 Fix a terrible bug in the canonicaliser which led to an infinite loop This fixes Trac #9971 Merge into the 7.10 branch >--------------------------------------------------------------- 854e7b8efdd7fe5fcba77e1e049e8a835f03b16a compiler/typecheck/TcCanonical.hs | 50 +++++++++++++++-------- testsuite/tests/typecheck/should_compile/T9971.hs | 15 +++++++ testsuite/tests/typecheck/should_compile/all.T | 2 +- 3 files changed, 49 insertions(+), 18 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 62efe90..cdf5f09 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -528,12 +528,12 @@ can_eq_nc' _rdr_env _envs ev eq_rel s1@(ForAllTy {}) _ s2@(ForAllTy {}) _ pprEq s1 s2 -- See Note [Do not decompose given polytype equalities] ; stopWith ev "Discard given polytype equality" } -can_eq_nc' _rdr_env _envs ev eq_rel (AppTy {}) ps_ty1 _ ps_ty2 - | isGiven ev = try_decompose_app ev eq_rel ps_ty1 ps_ty2 - | otherwise = can_eq_wanted_app ev eq_rel ps_ty1 ps_ty2 -can_eq_nc' _rdr_env _envs ev eq_rel _ ps_ty1 (AppTy {}) ps_ty2 - | isGiven ev = try_decompose_app ev eq_rel ps_ty1 ps_ty2 - | otherwise = can_eq_wanted_app ev eq_rel ps_ty1 ps_ty2 +can_eq_nc' _rdr_env _envs ev eq_rel ty1@(AppTy {}) _ ty2 _ + | isGiven ev = try_decompose_app ev eq_rel ty1 ty2 + | otherwise = can_eq_wanted_app ev eq_rel ty1 ty2 +can_eq_nc' _rdr_env _envs ev eq_rel ty1 _ ty2@(AppTy {}) _ + | isGiven ev = try_decompose_app ev eq_rel ty1 ty2 + | otherwise = can_eq_wanted_app ev eq_rel ty1 ty2 -- Everything else is a definite type error, eg LitTy ~ TyConApp can_eq_nc' _rdr_env _envs ev eq_rel _ ps_ty1 _ ps_ty2 @@ -658,29 +658,38 @@ can_eq_wanted_app ev eq_rel ty1 ty2 `andWhenContinue` \ new_ev -> try_decompose_app new_ev eq_rel xi1 xi2 } +--------- try_decompose_app :: CtEvidence -> EqRel -> TcType -> TcType -> TcS (StopOrContinue Ct) --- Preconditions: neither is a type variable +-- Preconditions: one or the other is an App; +-- but neither is a type variable -- so can't turn it into an application if it -- doesn't look like one already -- See Note [Canonicalising type applications] -try_decompose_app ev NomEq ty1 ty2 - = try_decompose_nom_app ev ty1 ty2 - -try_decompose_app ev ReprEq ty1 ty2 +try_decompose_app ev eq_rel ty1 ty2 + = case eq_rel of + NomEq -> try_decompose_nom_app ev ty1 ty2 + ReprEq -> try_decompose_repr_app ev ty1 ty2 + +--------- +try_decompose_repr_app :: CtEvidence + -> TcType -> TcType -> TcS (StopOrContinue Ct) +-- Preconditions: like try_decompose_app, but also +-- ev has a representational +try_decompose_repr_app ev ty1 ty2 | ty1 `eqType` ty2 -- See Note [AppTy reflexivity check] = canEqReflexive ev ReprEq ty1 | otherwise = canEqFailure ev ReprEq ty1 ty2 +--------- try_decompose_nom_app :: CtEvidence -> TcType -> TcType -> TcS (StopOrContinue Ct) -- Preconditions: like try_decompose_app, but also -- ev has a nominal role --- See Note [Canonicalising type applications] try_decompose_nom_app ev ty1 ty2 - | AppTy s1 t1 <- ty1 + | AppTy s1 t1 <- ty1 = case tcSplitAppTy_maybe ty2 of Nothing -> canEqHardFailure ev NomEq ty1 ty2 Just (s2,t2) -> do_decompose s1 t1 s2 t2 @@ -690,8 +699,14 @@ try_decompose_nom_app ev ty1 ty2 Nothing -> canEqHardFailure ev NomEq ty1 ty2 Just (s1,t1) -> do_decompose s1 t1 s2 t2 - | otherwise -- Neither is an AppTy - = canEqNC ev NomEq ty1 ty2 + | otherwise -- Neither is an AppTy; but one or other started that way + -- (precondition to can_eq_wanted_app) + -- So presumably one has become a TyConApp, which + -- is good: See Note [Canonicalising type applications] + = ASSERT2( isJust (tcSplitTyConApp_maybe ty1) || isJust (tcSplitTyConApp_maybe ty2) + , ppr ty1 $$ ppr ty2 ) -- If this assertion fails, we may fall + -- into an inifinite loop (Trac #9971) + canEqNC ev NomEq ty1 ty2 where -- Recurses to try_decompose_nom_app to decompose a chain of AppTys do_decompose s1 t1 s2 t2 @@ -864,8 +879,9 @@ decompose the application eagerly, yielding we get an error "Can't match Array ~ Maybe", but we'd prefer to get "Can't match Array b ~ Maybe c". -So instead can_eq_wanted_app flattens the LHS and RHS before using -try_decompose_app to decompose it. +So instead can_eq_wanted_app flattens the LHS and RHS, in the hope of +replacing (a b) by (Array b), before using try_decompose_app to +decompose it. Note [Make sure that insolubles are fully rewritten] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/testsuite/tests/typecheck/should_compile/T9971.hs b/testsuite/tests/typecheck/should_compile/T9971.hs new file mode 100644 index 0000000..e02b21e --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9971.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE FunctionalDependencies #-} +module T9971 where + +type Vertex v = v Double + +class C a b | b->a where + op :: a -> b + +foo :: Vertex x +foo = error "urk" + +bar x = [op foo, op foo] + -- This gives rise to a [D] Vertex a1 ~ Vertex a2 + -- And that made the canonicaliser go into a loop (Trac #9971) + diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 2cf1755..38c41f1 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -439,4 +439,4 @@ test('T9834', normal, compile, ['']) test('T9892', normal, compile, ['']) test('T9939', normal, compile, ['']) test('T9973', normal, compile, ['']) - +test('T9971', normal, compile, ['']) From git at git.haskell.org Fri Jan 16 15:42:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 15:42:39 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Repsect the package name when checking for self-import (b5789df) Message-ID: <20150116154239.12B543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/b5789dfc0720b1b67d3fdc3c9a77f19011a828d5/ghc >--------------------------------------------------------------- commit b5789dfc0720b1b67d3fdc3c9a77f19011a828d5 Author: Simon Peyton Jones Date: Fri Jan 16 14:17:14 2015 +0000 Repsect the package name when checking for self-import Fixes Trac #9997. In doing this I tripped across the specialness of "this" in PackageImports. The magic constant (fsLit "this") is scattered across the compiler and ought to be put in one place. But where? (cherry picked from commit fb7c311711c8851d0de1e40231150ad999ae9c2b) >--------------------------------------------------------------- b5789dfc0720b1b67d3fdc3c9a77f19011a828d5 compiler/rename/RnNames.hs | 10 +++++++++- testsuite/tests/module/T9997.hs | 5 +++++ testsuite/tests/module/all.T | 1 + 3 files changed, 15 insertions(+), 1 deletion(-) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index 145d6fc..b268881 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -186,7 +186,15 @@ rnImportDecl this_mod -- at least not until TcIface.tcHiBootIface, which is too late to avoid -- typechecker crashes. ToDo: what about indirect self-import? -- But 'import {-# SOURCE #-} M' is ok, even if a bit odd - when (not want_boot && imp_mod_name == moduleName this_mod) + when (not want_boot && + imp_mod_name == moduleName this_mod && + (case mb_pkg of -- If we have import "" M, then we should + -- check that "" is "this" (which is magic) + -- or the name of this_mod's package. Yurgh! + -- c.f. GHC.findModule, and Trac #9997 + Nothing -> True + Just pkg_fs -> pkg_fs == fsLit "this" || + fsToPackageKey pkg_fs == modulePackageKey this_mod)) (addErr (ptext (sLit "A module cannot import itself:") <+> ppr imp_mod_name)) -- Check for a missing import list (Opt_WarnMissingImportList also diff --git a/testsuite/tests/module/T9997.hs b/testsuite/tests/module/T9997.hs new file mode 100644 index 0000000..acc82da --- /dev/null +++ b/testsuite/tests/module/T9997.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE PackageImports #-} +module Control.DeepSeq where + +import "deepseq" Control.DeepSeq + diff --git a/testsuite/tests/module/all.T b/testsuite/tests/module/all.T index c91d30c..58632be 100644 --- a/testsuite/tests/module/all.T +++ b/testsuite/tests/module/all.T @@ -344,3 +344,4 @@ test('T414a', normal, compile, ['']) test('T414b', normal, compile, ['']) test('T3776', normal, compile, ['']) test('T9061', normal, compile, ['']) +test('T9997', normal, compile, ['']) From git at git.haskell.org Fri Jan 16 16:14:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 16:14:51 +0000 (UTC) Subject: [commit: ghc] master: Trac #9878: Make the static form illegal in interpreted mode. (fffbf06) Message-ID: <20150116161451.06AEB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fffbf0627c2c2ee4bc49f9d26a226b39a066945e/ghc >--------------------------------------------------------------- commit fffbf0627c2c2ee4bc49f9d26a226b39a066945e Author: Alexander Vershilov Date: Wed Jan 14 17:58:30 2015 -0600 Trac #9878: Make the static form illegal in interpreted mode. Summary: The entries of the static pointers table are expected to exist as object code. Thus we have ghci complain with an intelligible error message if the static form is used in interpreted mode. It also includes a fix to keysHashTable in Hash.c which could cause a crash. The iteration of the hashtable internals was incorrect. This patch has the function keysHashTable imitate the iteration in freeHashTable. Finally, we submit here some minor edits to comments and GHC.StaticPtr.StaticPtrInfo field names. Authored-by: Alexander Vershilov Test Plan: ./validate Reviewers: simonpj, hvr, austin Reviewed By: austin Subscribers: carter, thomie, qnikst, mboes Differential Revision: https://phabricator.haskell.org/D586 GHC Trac Issues: #9878 >--------------------------------------------------------------- fffbf0627c2c2ee4bc49f9d26a226b39a066945e compiler/deSugar/DsExpr.hs | 4 ++-- compiler/rename/RnExpr.hs | 9 ++++++++ includes/rts/StaticPtrTable.h | 4 ++-- libraries/base/GHC/StaticPtr.hs | 4 ++-- rts/Hash.c | 24 ++++++++++++++-------- .../deSugar/should_run/DsStaticPointers.stdout | 10 ++++----- testsuite/tests/ghci/scripts/T9878.hs | 6 ++++++ testsuite/tests/ghci/scripts/T9878.script | 1 + testsuite/tests/ghci/scripts/T9878.stderr | 4 ++++ testsuite/tests/ghci/scripts/T9878b.script | 2 ++ .../tests/ghci/scripts/T9878b.stdout | 0 testsuite/tests/ghci/scripts/all.T | 7 +++++++ 12 files changed, 56 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fffbf0627c2c2ee4bc49f9d26a226b39a066945e From git at git.haskell.org Fri Jan 16 16:14:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 16:14:53 +0000 (UTC) Subject: [commit: ghc] master: Don't hardcode the name "ghc" in versionedAppDir (6392df0) Message-ID: <20150116161453.A008C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6392df07e89304a4daeb1af379c051b03a39cda7/ghc >--------------------------------------------------------------- commit 6392df07e89304a4daeb1af379c051b03a39cda7 Author: Edsko de Vries Date: Wed Jan 14 17:58:13 2015 -0600 Don't hardcode the name "ghc" in versionedAppDir Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D618 >--------------------------------------------------------------- 6392df07e89304a4daeb1af379c051b03a39cda7 compiler/main/CmdLineParser.hs | 2 +- compiler/main/DynFlags.hs | 8 ++++---- compiler/main/Packages.hs | 5 ++--- 3 files changed, 7 insertions(+), 8 deletions(-) diff --git a/compiler/main/CmdLineParser.hs b/compiler/main/CmdLineParser.hs index e80f688..422fa13 100644 --- a/compiler/main/CmdLineParser.hs +++ b/compiler/main/CmdLineParser.hs @@ -18,7 +18,7 @@ module CmdLineParser Flag(..), defFlag, defGhcFlag, defGhciFlag, defHiddenFlag, errorsToGhcException, - EwM(..), runEwM, addErr, addWarn, getArg, getCurLoc, liftEwM, deprecate + EwM, runEwM, addErr, addWarn, getArg, getCurLoc, liftEwM, deprecate ) where #include "HsVersions.h" diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 5ef6ce4..eccb14e 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1022,9 +1022,9 @@ opt_lc dflags = sOpt_lc (settings dflags) -- | The directory for this version of ghc in the user's app directory -- (typically something like @~/.ghc/x86_64-linux-7.6.3@) -- -versionedAppDir :: IO FilePath -versionedAppDir = do - appdir <- getAppUserDataDirectory "ghc" +versionedAppDir :: DynFlags -> IO FilePath +versionedAppDir dflags = do + appdir <- getAppUserDataDirectory (programName dflags) return $ appdir (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion) -- | The target code type of the compilation (if any). @@ -3771,7 +3771,7 @@ interpretPackageEnv dflags = do namedEnvPath :: String -> MaybeT IO FilePath namedEnvPath name = do - appdir <- liftMaybeT $ versionedAppDir + appdir <- liftMaybeT $ versionedAppDir dflags return $ appdir "environments" name loadEnvName :: String -> MaybeT IO String diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index e081a31..dec7b5b 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -354,10 +354,9 @@ getPackageConfRefs dflags = do resolvePackageConfig :: DynFlags -> PkgConfRef -> IO (Maybe FilePath) resolvePackageConfig dflags GlobalPkgConf = return $ Just (systemPackageConfig dflags) -resolvePackageConfig _ UserPkgConf = handleIO (\_ -> return Nothing) $ do - dir <- versionedAppDir +resolvePackageConfig dflags UserPkgConf = handleIO (\_ -> return Nothing) $ do + dir <- versionedAppDir dflags let pkgconf = dir "package.conf.d" - exist <- doesDirectoryExist pkgconf return $ if exist then Just pkgconf else Nothing resolvePackageConfig _ (PkgConfFile name) = return $ Just name From git at git.haskell.org Fri Jan 16 16:14:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 16:14:56 +0000 (UTC) Subject: [commit: ghc] master: API Annotations tweaks. (11881ec) Message-ID: <20150116161456.819973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/11881ec6f8d4db881671173441df87c2457409f4/ghc >--------------------------------------------------------------- commit 11881ec6f8d4db881671173441df87c2457409f4 Author: Alan Zimmerman Date: Thu Jan 15 13:11:21 2015 -0600 API Annotations tweaks. Summary: HsTyLit now has SourceText Update documentation of HsSyn to reflect which annotations are attached to which element. Ensure that the parser always keeps HsSCC and HsTickPragma values, to be ignored in the desugar phase if not needed Bringing in SourceText for pragmas Add Location in NPlusKPat Add Location in FunDep Make RecCon payload Located Explicitly add AnnVal to RdrName where it is compound Add Location in IPBind Add Location to name in IEThingAbs Add Maybe (Located id,Bool) to Match to track fun_id,infix This includes converting Match into a record and adding a note about why the fun_id needs to be replicated in the Match. Add Location in KindedTyVar Sort out semi-colons for parsing - import statements - stmts - decls - decls_cls - decls_inst This updates the haddock submodule. Test Plan: ./validate Reviewers: hvr, austin, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D538 >--------------------------------------------------------------- 11881ec6f8d4db881671173441df87c2457409f4 compiler/basicTypes/BasicTypes.hs | 135 +++- compiler/basicTypes/DataCon.hs | 21 +- compiler/basicTypes/MkId.hs | 14 +- compiler/basicTypes/RdrName.hs | 14 + compiler/basicTypes/SrcLoc.hs | 11 + compiler/deSugar/Check.hs | 8 +- compiler/deSugar/Coverage.hs | 22 +- compiler/deSugar/Desugar.hs | 8 +- compiler/deSugar/DsArrows.hs | 9 +- compiler/deSugar/DsExpr.hs | 27 +- compiler/deSugar/DsForeign.hs | 2 +- compiler/deSugar/DsMeta.hs | 61 +- compiler/deSugar/Match.hs | 9 +- compiler/deSugar/MatchLit.hs | 6 +- compiler/ghc.mk | 2 - compiler/hsSyn/Convert.hs | 70 +- compiler/hsSyn/HsBinds.hs | 48 +- compiler/hsSyn/HsDecls.hs | 161 ++-- compiler/hsSyn/HsExpr.hs | 171 ++-- compiler/hsSyn/HsImpExp.hs | 12 +- compiler/hsSyn/HsLit.hs | 39 +- compiler/hsSyn/HsPat.hs | 23 +- compiler/hsSyn/HsTypes.hs | 70 +- compiler/hsSyn/HsUtils.hs | 18 +- compiler/main/GHC.hs | 3 +- compiler/main/HeaderInfo.hs | 3 +- compiler/main/HscMain.hs | 6 +- compiler/main/HscTypes.hs | 1 + compiler/main/InteractiveEval.hs | 1 + compiler/parser/ApiAnnotation.hs | 55 +- compiler/parser/Lexer.x | 157 ++-- compiler/parser/Parser.y | 891 ++++++++++++--------- compiler/parser/RdrHsSyn.hs | 128 +-- compiler/prelude/ForeignCall.hs | 20 +- compiler/prelude/TysWiredIn.hs | 20 +- compiler/rename/RnBinds.hs | 12 +- compiler/rename/RnExpr.hs | 14 +- compiler/rename/RnNames.hs | 24 +- compiler/rename/RnPat.hs | 14 +- compiler/rename/RnSource.hs | 86 +- compiler/rename/RnTypes.hs | 10 +- compiler/stranal/WorkWrap.hs | 6 +- compiler/typecheck/Inst.hs | 6 +- compiler/typecheck/TcAnnotations.hs | 8 +- compiler/typecheck/TcArrows.hs | 6 +- compiler/typecheck/TcBinds.hs | 20 +- compiler/typecheck/TcClassDcl.hs | 4 +- compiler/typecheck/TcExpr.hs | 12 +- compiler/typecheck/TcGenGenerics.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 42 +- compiler/typecheck/TcHsType.hs | 15 +- compiler/typecheck/TcInstDcls.hs | 6 +- compiler/typecheck/TcMatches.hs | 6 +- compiler/typecheck/TcPat.hs | 8 +- compiler/typecheck/TcPatSyn.hs | 5 +- compiler/typecheck/TcRnDriver.hs | 3 +- compiler/typecheck/TcRules.hs | 9 +- compiler/typecheck/TcSplice.hs | 12 +- compiler/typecheck/TcTyClsDecls.hs | 32 +- compiler/types/Class.hs | 10 +- compiler/types/InstEnv.hs | 6 +- compiler/utils/Binary.hs | 42 +- compiler/utils/OrdList.hs | 10 +- .../tests/ghc-api/annotations/AnnotationLet.hs | 7 +- testsuite/tests/ghc-api/annotations/Makefile | 1 + .../tests/ghc-api/annotations/annotations.stdout | 86 +- .../tests/ghc-api/annotations/parseTree.stdout | 46 +- testsuite/tests/ghc-api/landmines/landmines.stdout | 8 +- utils/haddock | 2 +- 69 files changed, 1735 insertions(+), 1091 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 11881ec6f8d4db881671173441df87c2457409f4 From git at git.haskell.org Fri Jan 16 16:35:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 16:35:58 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix a terrible bug in the canonicaliser which led to an infinite loop (c9ab42f) Message-ID: <20150116163558.530A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/c9ab42f84531f71056cfdf686cf548481b0af389/ghc >--------------------------------------------------------------- commit c9ab42f84531f71056cfdf686cf548481b0af389 Author: Simon Peyton Jones Date: Fri Jan 16 14:18:34 2015 +0000 Fix a terrible bug in the canonicaliser which led to an infinite loop This fixes Trac #9971 (cherry picked from commit 854e7b8efdd7fe5fcba77e1e049e8a835f03b16a) >--------------------------------------------------------------- c9ab42f84531f71056cfdf686cf548481b0af389 compiler/typecheck/TcCanonical.hs | 50 +++++++++++++++-------- testsuite/tests/typecheck/should_compile/T9971.hs | 15 +++++++ testsuite/tests/typecheck/should_compile/all.T | 2 +- 3 files changed, 49 insertions(+), 18 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 493e742..75263fa 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -490,12 +490,12 @@ can_eq_nc' _rdr_env _envs ev eq_rel s1@(ForAllTy {}) _ s2@(ForAllTy {}) _ pprEq s1 s2 -- See Note [Do not decompose given polytype equalities] ; stopWith ev "Discard given polytype equality" } -can_eq_nc' _rdr_env _envs ev eq_rel (AppTy {}) ps_ty1 _ ps_ty2 - | isGiven ev = try_decompose_app ev eq_rel ps_ty1 ps_ty2 - | otherwise = can_eq_wanted_app ev eq_rel ps_ty1 ps_ty2 -can_eq_nc' _rdr_env _envs ev eq_rel _ ps_ty1 (AppTy {}) ps_ty2 - | isGiven ev = try_decompose_app ev eq_rel ps_ty1 ps_ty2 - | otherwise = can_eq_wanted_app ev eq_rel ps_ty1 ps_ty2 +can_eq_nc' _rdr_env _envs ev eq_rel ty1@(AppTy {}) _ ty2 _ + | isGiven ev = try_decompose_app ev eq_rel ty1 ty2 + | otherwise = can_eq_wanted_app ev eq_rel ty1 ty2 +can_eq_nc' _rdr_env _envs ev eq_rel ty1 _ ty2@(AppTy {}) _ + | isGiven ev = try_decompose_app ev eq_rel ty1 ty2 + | otherwise = can_eq_wanted_app ev eq_rel ty1 ty2 -- Everything else is a definite type error, eg LitTy ~ TyConApp can_eq_nc' _rdr_env _envs ev eq_rel _ ps_ty1 _ ps_ty2 @@ -620,29 +620,38 @@ can_eq_wanted_app ev eq_rel ty1 ty2 `andWhenContinue` \ new_ev -> try_decompose_app new_ev eq_rel xi1 xi2 } +--------- try_decompose_app :: CtEvidence -> EqRel -> TcType -> TcType -> TcS (StopOrContinue Ct) --- Preconditions: neither is a type variable +-- Preconditions: one or the other is an App; +-- but neither is a type variable -- so can't turn it into an application if it -- doesn't look like one already -- See Note [Canonicalising type applications] -try_decompose_app ev NomEq ty1 ty2 - = try_decompose_nom_app ev ty1 ty2 - -try_decompose_app ev ReprEq ty1 ty2 +try_decompose_app ev eq_rel ty1 ty2 + = case eq_rel of + NomEq -> try_decompose_nom_app ev ty1 ty2 + ReprEq -> try_decompose_repr_app ev ty1 ty2 + +--------- +try_decompose_repr_app :: CtEvidence + -> TcType -> TcType -> TcS (StopOrContinue Ct) +-- Preconditions: like try_decompose_app, but also +-- ev has a representational +try_decompose_repr_app ev ty1 ty2 | ty1 `eqType` ty2 -- See Note [AppTy reflexivity check] = canEqReflexive ev ReprEq ty1 | otherwise = canEqFailure ev ReprEq ty1 ty2 +--------- try_decompose_nom_app :: CtEvidence -> TcType -> TcType -> TcS (StopOrContinue Ct) -- Preconditions: like try_decompose_app, but also -- ev has a nominal role --- See Note [Canonicalising type applications] try_decompose_nom_app ev ty1 ty2 - | AppTy s1 t1 <- ty1 + | AppTy s1 t1 <- ty1 = case tcSplitAppTy_maybe ty2 of Nothing -> canEqHardFailure ev NomEq ty1 ty2 Just (s2,t2) -> do_decompose s1 t1 s2 t2 @@ -652,8 +661,14 @@ try_decompose_nom_app ev ty1 ty2 Nothing -> canEqHardFailure ev NomEq ty1 ty2 Just (s1,t1) -> do_decompose s1 t1 s2 t2 - | otherwise -- Neither is an AppTy - = canEqNC ev NomEq ty1 ty2 + | otherwise -- Neither is an AppTy; but one or other started that way + -- (precondition to can_eq_wanted_app) + -- So presumably one has become a TyConApp, which + -- is good: See Note [Canonicalising type applications] + = ASSERT2( isJust (tcSplitTyConApp_maybe ty1) || isJust (tcSplitTyConApp_maybe ty2) + , ppr ty1 $$ ppr ty2 ) -- If this assertion fails, we may fall + -- into an inifinite loop (Trac #9971) + canEqNC ev NomEq ty1 ty2 where -- do_decompose is like xCtEvidence, but recurses -- to try_decompose_nom_app to decompose a chain of AppTys @@ -827,8 +842,9 @@ decompose the application eagerly, yielding we get an error "Can't match Array ~ Maybe", but we'd prefer to get "Can't match Array b ~ Maybe c". -So instead can_eq_wanted_app flattens the LHS and RHS before using -try_decompose_app to decompose it. +So instead can_eq_wanted_app flattens the LHS and RHS, in the hope of +replacing (a b) by (Array b), before using try_decompose_app to +decompose it. Note [Make sure that insolubles are fully rewritten] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/testsuite/tests/typecheck/should_compile/T9971.hs b/testsuite/tests/typecheck/should_compile/T9971.hs new file mode 100644 index 0000000..e02b21e --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9971.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE FunctionalDependencies #-} +module T9971 where + +type Vertex v = v Double + +class C a b | b->a where + op :: a -> b + +foo :: Vertex x +foo = error "urk" + +bar x = [op foo, op foo] + -- This gives rise to a [D] Vertex a1 ~ Vertex a2 + -- And that made the canonicaliser go into a loop (Trac #9971) + diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index d1b3796..9d915eb 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -437,4 +437,4 @@ test('T9497c', normal, compile, ['-fdefer-type-errors -fno-warn-typed-holes']) test('T7643', normal, compile, ['']) test('T9834', normal, compile, ['']) test('T9892', normal, compile, ['']) - +test('T9971', normal, compile, ['']) From git at git.haskell.org Fri Jan 16 22:30:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 22:30:46 +0000 (UTC) Subject: [commit: packages/terminfo] master: Avoid redundant import of Data.Monoid w/ base-4.8 (e9d2262) Message-ID: <20150116223046.B91EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/terminfo On branch : master Link : http://git.haskell.org/packages/terminfo.git/commitdiff/e9d2262e6afd104663da48df1a610d3a51ac4bee >--------------------------------------------------------------- commit e9d2262e6afd104663da48df1a610d3a51ac4bee Author: Herbert Valerio Riedel Date: Sun Dec 28 09:01:50 2014 +0100 Avoid redundant import of Data.Monoid w/ base-4.8 This makes `terminfo` `-Wall` clean >--------------------------------------------------------------- e9d2262e6afd104663da48df1a610d3a51ac4bee System/Console/Terminfo/Base.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/System/Console/Terminfo/Base.hs b/System/Console/Terminfo/Base.hs index 24a4782..87ac774 100644 --- a/System/Console/Terminfo/Base.hs +++ b/System/Console/Terminfo/Base.hs @@ -45,7 +45,9 @@ module System.Console.Terminfo.Base( import Control.Applicative import Control.Monad +#if !MIN_VERSION_base(4,8,0) import Data.Monoid +#endif import Foreign.C import Foreign.ForeignPtr import Foreign.Ptr From git at git.haskell.org Fri Jan 16 22:30:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 22:30:48 +0000 (UTC) Subject: [commit: packages/terminfo] master: Merge pull request #4 from hvr/pr-base48 (1b5ab01) Message-ID: <20150116223048.BE20A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/terminfo On branch : master Link : http://git.haskell.org/packages/terminfo.git/commitdiff/1b5ab01452eaa6c21de7174ad4312a017a13d0ab >--------------------------------------------------------------- commit 1b5ab01452eaa6c21de7174ad4312a017a13d0ab Merge: 83cb515 e9d2262 Author: Judah Jacobson Date: Mon Dec 29 22:35:40 2014 -0800 Merge pull request #4 from hvr/pr-base48 Avoid redundant import of Data.Monoid w/ base-4.8 >--------------------------------------------------------------- 1b5ab01452eaa6c21de7174ad4312a017a13d0ab System/Console/Terminfo/Base.hs | 2 ++ 1 file changed, 2 insertions(+) From git at git.haskell.org Fri Jan 16 22:53:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Jan 2015 22:53:48 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Cabal/directory/process/terminfo submodules (194f1b5) Message-ID: <20150116225348.D2A3C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/194f1b5638e8fb27d8a107344fc14bfbd9ff0d43/ghc >--------------------------------------------------------------- commit 194f1b5638e8fb27d8a107344fc14bfbd9ff0d43 Author: Herbert Valerio Riedel Date: Fri Jan 16 23:37:50 2015 +0100 Update Cabal/directory/process/terminfo submodules >--------------------------------------------------------------- 194f1b5638e8fb27d8a107344fc14bfbd9ff0d43 libraries/Cabal | 2 +- libraries/directory | 2 +- libraries/process | 2 +- libraries/terminfo | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index e4ea51c..52e80d2 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit e4ea51c3156c27b7dec40cb2733b8bfe37bca6a1 +Subproject commit 52e80d21b3cf37bea2ead237fe9c97ccb816e779 diff --git a/libraries/directory b/libraries/directory index e22771f..c43340d 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit e22771f4e9fbd30b2ed4af75cf4b19b9e4e94c7c +Subproject commit c43340dc29874c80570a7295d5d4c93756b4bc03 diff --git a/libraries/process b/libraries/process index 1a62f86..93d8b62 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 1a62f86e77118520143985d9baf62d31a9d1c748 +Subproject commit 93d8b624252feea034683508eb3f112f9dc76662 diff --git a/libraries/terminfo b/libraries/terminfo index 83cb515..1b5ab01 160000 --- a/libraries/terminfo +++ b/libraries/terminfo @@ -1 +1 @@ -Subproject commit 83cb51568234910c66a1ec6fd69ba127f6177194 +Subproject commit 1b5ab01452eaa6c21de7174ad4312a017a13d0ab From git at git.haskell.org Sun Jan 18 12:17:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Jan 2015 12:17:31 +0000 (UTC) Subject: [commit: ghc] master: Trac #9384: fix increasing capabilites number for eventlog. (2edb4a7) Message-ID: <20150118121731.7FE2E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2edb4a7bd5b892ddfac75d0b549d6682a0be5c02/ghc >--------------------------------------------------------------- commit 2edb4a7bd5b892ddfac75d0b549d6682a0be5c02 Author: Alexander Vershilov Date: Sun Jan 18 10:58:57 2015 +0000 Trac #9384: fix increasing capabilites number for eventlog. Event log had inconcistent support for increacing capabilies number, as header were not inserted in capability buffer. It resulted in a ghc-events crash (see #9384). This commit fixes this issue by inserting required header when number of capabilies grows. Reviewers: simonmar, Mikolaj, trofi, austin Reviewed By: Mikolaj, trofi, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D592 GHC Trac Issues: #9384 >--------------------------------------------------------------- 2edb4a7bd5b892ddfac75d0b549d6682a0be5c02 rts/eventlog/EventLog.c | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/rts/eventlog/EventLog.c b/rts/eventlog/EventLog.c index ef96f3c..f830ec1 100644 --- a/rts/eventlog/EventLog.c +++ b/rts/eventlog/EventLog.c @@ -500,6 +500,15 @@ moreCapEventBufs (nat from, nat to) for (c = from; c < to; ++c) { initEventsBuf(&capEventBuf[c], EVENT_LOG_SIZE, c); } + + // The from == 0 already covered in initEventLogging, so we are interested + // only in case when we are increasing capabilities number + if (from > 0) { + for (c = from; c < to; ++c) { + postBlockMarker(&capEventBuf[c]); + } + } + } From git at git.haskell.org Mon Jan 19 09:10:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 09:10:35 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Comments (7d817a0) Message-ID: <20150119091035.27AC53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/7d817a0db4c2dc1b3397f001e2a35804e4243053/ghc >--------------------------------------------------------------- commit 7d817a0db4c2dc1b3397f001e2a35804e4243053 Author: Simon Peyton Jones Date: Mon Jan 19 09:10:08 2015 +0000 Comments >--------------------------------------------------------------- 7d817a0db4c2dc1b3397f001e2a35804e4243053 compiler/deSugar/Check.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 2a8dbfe..cdeacc2 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -87,6 +87,10 @@ instance Eq (PmLit id) where -- | The main pattern type for pattern match check. Only guards, variables, -- constructors, literals and negative literals. It it sufficient to represent -- all different patterns, apart maybe from bang and lazy patterns. + +-- SPJ... Say that this the term-level stuff only. +-- Drop all types, existential type variables +-- data PmPat id = PmGuardPat PmGuard -- Note [Translation to PmPat] | PmVarPat { pm_ty :: Type, pm_var :: id } | PmConPat { pm_ty :: Type, pm_pat_con :: DataCon, pm_pat_args :: [PmPat id] } @@ -324,6 +328,7 @@ mkConFull con = do return (con_pat, evvars) mkConSigSubst :: DataCon -> PmM TvSubst +-- SPJ: not convinced that we need to make fresh uniques mkConSigSubst con = do tvs <- replicateM notys (liftPmM freshTyVarPmM) return (mkTopTvSubst (tyvars `zip` tvs)) From git at git.haskell.org Mon Jan 19 09:15:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 09:15:26 +0000 (UTC) Subject: [commit: ghc] master: Fix the 'builder' code for pattern synonyms with type signatures (3ea40e3) Message-ID: <20150119091526.48AE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3ea40e38a7ae03c05cb79485fb04a3f00c632793/ghc >--------------------------------------------------------------- commit 3ea40e38a7ae03c05cb79485fb04a3f00c632793 Author: Simon Peyton Jones Date: Mon Jan 19 09:06:21 2015 +0000 Fix the 'builder' code for pattern synonyms with type signatures See Note [Type signatures and the builder expression] for the details >--------------------------------------------------------------- 3ea40e38a7ae03c05cb79485fb04a3f00c632793 compiler/typecheck/TcPatSyn.hs | 144 ++++++++++++++++++++++------------------- 1 file changed, 79 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3ea40e38a7ae03c05cb79485fb04a3f00c632793 From git at git.haskell.org Mon Jan 19 10:05:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 10:05:47 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Fixed a bug in to_tc_type (7e7c36f) Message-ID: <20150119100547.128003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/7e7c36f66a7d1e9032ca62f833cc955c1c466093/ghc >--------------------------------------------------------------- commit 7e7c36f66a7d1e9032ca62f833cc955c1c466093 Author: George Karachalias Date: Mon Jan 19 11:06:47 2015 +0100 Fixed a bug in to_tc_type >--------------------------------------------------------------- 7e7c36f66a7d1e9032ca62f833cc955c1c466093 compiler/deSugar/Check.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index cdeacc2..0a89e19 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -299,10 +299,10 @@ toTcType ty = to_tc_type emptyVarSet ty -- A bit tiresome; but one day I expect the two types to be entirely separate -- in which case we'll definitely need to do this to_tc_type forall_tvs (TyVarTy tv) - | tv `elemVarSet` forall_tvs = return (TyVarTy tv) + | tv `elemVarSet` forall_tvs = return (TyVarTy tv) -- Sure tv is well-formed ?? | otherwise = return (TyVarTy (mkTcTyVar (tyVarName tv) (tyVarKind tv) vanillaSkolemTv)) to_tc_type ftvs (FunTy t1 t2) = FunTy <$> to_tc_type ftvs t1 <*> to_tc_type ftvs t2 - to_tc_type ftvs (AppTy t1 t2) = FunTy <$> to_tc_type ftvs t1 <*> to_tc_type ftvs t2 + to_tc_type ftvs (AppTy t1 t2) = AppTy <$> to_tc_type ftvs t1 <*> to_tc_type ftvs t2 to_tc_type ftvs (TyConApp tc tys) = TyConApp tc <$> mapM (to_tc_type ftvs) tys to_tc_type ftvs (ForAllTy tv ty) = ForAllTy tv <$> to_tc_type (ftvs `extendVarSet` tv) ty to_tc_type ftvs (LitTy l) = return (LitTy l) @@ -316,6 +316,7 @@ toTcTypeBag evvars = do ty' <- toTcType (tyVarKind tyvar) return (setTyVarKind tyvar ty') +-- (mkConFull K) makes a fresh pattern for K, thus (K ex1 ex2 d1 d2 x1 x2 x3) mkConFull :: DataCon -> PmM (PmPat Id, [EvVar]) mkConFull con = do subst <- mkConSigSubst con @@ -329,7 +330,7 @@ mkConFull con = do mkConSigSubst :: DataCon -> PmM TvSubst -- SPJ: not convinced that we need to make fresh uniques -mkConSigSubst con = do +mkConSigSubst con = do -- INLINE THIS FUNCTION tvs <- replicateM notys (liftPmM freshTyVarPmM) return (mkTopTvSubst (tyvars `zip` tvs)) where @@ -586,7 +587,7 @@ checkpmPmM :: [Type] -> [EquationInfo] -> PmM PmResult checkpmPmM _ [] = return ([],[],[]) checkpmPmM tys' eq_infos = do tys <- mapM toTcType tys' -- Not sure if this is correct - init_pats <- mapM (freshPmVar . expandTypeSynonyms) tys + init_pats <- mapM (freshPmVar . expandTypeSynonyms) tys -- should we expand? init_delta <- addEnvEvVars empty_delta checkpm' [(init_delta, init_pats)] eq_infos From git at git.haskell.org Mon Jan 19 10:19:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 10:19:21 +0000 (UTC) Subject: [commit: ghc] master: Add missing argument in Match, a merge bug (apologies) (9a14582) Message-ID: <20150119101921.AB9F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a1458266b8fa349c9fb58889825d899a762fa27/ghc >--------------------------------------------------------------- commit 9a1458266b8fa349c9fb58889825d899a762fa27 Author: Simon Peyton Jones Date: Mon Jan 19 10:20:39 2015 +0000 Add missing argument in Match, a merge bug (apologies) >--------------------------------------------------------------- 9a1458266b8fa349c9fb58889825d899a762fa27 compiler/typecheck/TcPatSyn.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 16ff2e8..612eabe 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -388,8 +388,8 @@ tcPatSynBuilderBind PSB{ psb_id = L loc name, psb_def = lpat InfixPatSyn arg1 arg2 -> [arg1, arg2] add_dummy_arg :: MatchGroup Name (LHsExpr Name) -> MatchGroup Name (LHsExpr Name) - add_dummy_arg mg@(MG { mg_alts = [L loc (Match [] ty grhss)] }) - = mg { mg_alts = [L loc (Match [nlWildPatName] ty grhss)] } + add_dummy_arg mg@(MG { mg_alts = [L loc (Match Nothing [] ty grhss)] }) + = mg { mg_alts = [L loc (Match Nothing [nlWildPatName] ty grhss)] } add_dummy_arg other_mg = pprPanic "add_dummy_arg" $ pprMatches (PatSyn :: HsMatchContext Name) other_mg From git at git.haskell.org Mon Jan 19 11:09:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 11:09:02 +0000 (UTC) Subject: [commit: ghc] master: Update bytestring submodule (ff4733f) Message-ID: <20150119110902.4B9D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ff4733f4e0355085002a1f9053ba2276e92d2cb6/ghc >--------------------------------------------------------------- commit ff4733f4e0355085002a1f9053ba2276e92d2cb6 Author: Herbert Valerio Riedel Date: Mon Jan 19 12:08:58 2015 +0100 Update bytestring submodule This pulls in - https://github.com/haskell/bytestring/pull/40 (which is related to #9992) - https://github.com/haskell/bytestring/pull/38 >--------------------------------------------------------------- ff4733f4e0355085002a1f9053ba2276e92d2cb6 libraries/bytestring | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/bytestring b/libraries/bytestring index fa7e1cc..08d5c3a 160000 --- a/libraries/bytestring +++ b/libraries/bytestring @@ -1 +1 @@ -Subproject commit fa7e1cc94982c0da85a022a501eadb1b347ea60c +Subproject commit 08d5c3a80be94a9d7ef7731317dea79aaadbd2c4 From git at git.haskell.org Mon Jan 19 11:21:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 11:21:44 +0000 (UTC) Subject: [commit: ghc] master: Fix bad '... \\' escape in ghcversion.h generation (1289048) Message-ID: <20150119112144.009CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1289048eaf31915b9335c6f7e0b7b64625ab0ed5/ghc >--------------------------------------------------------------- commit 1289048eaf31915b9335c6f7e0b7b64625ab0ed5 Author: Herbert Valerio Riedel Date: Mon Jan 19 12:18:02 2015 +0100 Fix bad '... \\' escape in ghcversion.h generation Today I learned about the peculiarities of escaping within single-quotes: Turns out, echo 'foo \\' emits foo \\ rather than escaping the '\'. Curiously, if you need to escape a ' within single-quotes, here's how to do it echo 'foo '\'' bar' which will emit foo ' bar This fixes #10002 >--------------------------------------------------------------- 1289048eaf31915b9335c6f7e0b7b64625ab0ed5 includes/ghc.mk | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/includes/ghc.mk b/includes/ghc.mk index c7cec6c..7a255db 100644 --- a/includes/ghc.mk +++ b/includes/ghc.mk @@ -71,12 +71,12 @@ $(includes_H_VERSION) : mk/project.mk | $$(dir $$@)/. echo "#define __GLASGOW_HASKELL_PATCHLEVEL2__ $(ProjectPatchLevel2)" >> $@; \ fi @echo >> $@ - @echo '#define MIN_VERSION_GLASGOW_HASKELL(ma,mi,pl1,pl2) (\\' >> $@ - @echo ' ((ma)*100+(mi)) < __GLASGOW_HASKELL__ || \\' >> $@ - @echo ' ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \\' >> $@ - @echo ' && (pl1) < __GLASGOW_HASKELL_PATCHLEVEL1__ || \\'>> $@ - @echo ' ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \\' >> $@ - @echo ' && (pl1) == __GLASGOW_HASKELL_PATCHLEVEL1__ \\' >> $@ + @echo '#define MIN_VERSION_GLASGOW_HASKELL(ma,mi,pl1,pl2) (\' >> $@ + @echo ' ((ma)*100+(mi)) < __GLASGOW_HASKELL__ || \' >> $@ + @echo ' ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \' >> $@ + @echo ' && (pl1) < __GLASGOW_HASKELL_PATCHLEVEL1__ || \' >> $@ + @echo ' ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \' >> $@ + @echo ' && (pl1) == __GLASGOW_HASKELL_PATCHLEVEL1__ \' >> $@ @echo ' && (pl2) <= __GLASGOW_HASKELL_PATCHLEVEL2__ )' >> $@ @echo >> $@ @echo "#endif /* __GHCVERSION_H__ */" >> $@ From git at git.haskell.org Mon Jan 19 11:58:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 11:58:21 +0000 (UTC) Subject: [commit: ghc] master: Improve documentation of pattern synonyms, to reflect conclusion of Trac #9953 (8e774ba) Message-ID: <20150119115821.9398C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e774ba1c0fb38a1e01d156734c8a1acf0b1e59b/ghc >--------------------------------------------------------------- commit 8e774ba1c0fb38a1e01d156734c8a1acf0b1e59b Author: Simon Peyton Jones Date: Mon Jan 19 11:58:54 2015 +0000 Improve documentation of pattern synonyms, to reflect conclusion of Trac #9953 >--------------------------------------------------------------- 8e774ba1c0fb38a1e01d156734c8a1acf0b1e59b docs/users_guide/glasgow_exts.xml | 145 ++++++++++++++++++++++++-------------- 1 file changed, 92 insertions(+), 53 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index f352a32..684f8f0 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -1072,90 +1072,129 @@ would bring into scope the data constructor Just from the Given a pattern synonym definition of the form - pattern P var1 var2 ... varN <- pat - it is assigned a pattern type of the form - pattern P :: CProv => CReq => t1 -> t2 -> ... -> tN -> t - where CProv and CReq are type contexts, and t1, t2, ..., tN and t are - types. If CReq is empty - (()) it can be omitted. - - - -A pattern synonym of this type can be used in a pattern if the -instatiated (monomorphic) type satisfies the constraints of -CReq. In this case, it extends the context -available in the right-hand side of the match with -CProv, just like how an existentially-typed -data constructor can extend the context. - - - -For example, in the following program: - + types. +Notice the unusual form of the type, with two contexts CProv and CReq: + +CReq are the constraints required to match the pattern. +CProv are the constraints made available (provided) +by a successful pattern match. + +For example, consider -{-# LANGUAGE PatternSynonyms, GADTs #-} -module ShouldCompile where - data T a where - MkT :: (Show b) => a -> b -> T a - -pattern ExNumPat x = MkT 42 x - + MkT :: (Show b) => a -> b -> T a - -the inferred pattern type of ExNumPat is - +f1 :: (Eq a, Num a) => MkT a -> String +f1 (MkT 42 x) = show x - pattern ExNumPat :: (Show b) => (Num a, Eq a) => b -> T a - +pattern ExNumPat x = MkT 42 x +f2 :: (Eq a, Num a) => MkT a -> String +f2 (ExNumPat x) = show x + +Here f1 does not use pattern synonyms. To match against the +numeric pattern 42 requires the caller to +satisfy the constraints (Num a, Eq a), +so they appear in f1's type. The call to show generates a (Show b) +constraint, where b is an existentially type variable bound by the pattern match +on MkT. But the same pattern match also provides the constraint +(Show b) (see MkT's type), and so all is well. + - and so can be used in a function definition like the following: +Exactly the same reasoning applies to ExNumPat: +matching against ExNumPat requires +the constraints (Num a, Eq a), and provides +the constraint (Show b). + +Note also the following points + + +In the common case where CReq is empty, + (), it can be omitted altogether. + + +You may specify an explicit pattern signature, as +we did for ExNumPat above, to specify the type of a pattern, +just as you can for a function. As usual, the type signature can be less polymorphic +than the inferred type. For example - f :: (Num t, Eq t) => T t -> String - f (ExNumPat x) = show x + -- Inferred type would be 'a -> [a]' + pattern SinglePair :: (a, a) -> [(a, a)] + pattern SinglePair x = [x] + - - For bidirectional pattern synonyms, uses as expressions have the type - + +The GHCi :info command shows pattern types in this format. + + + +For a bidirectional pattern synonym, a use of the pattern synonym as an expression has the type (CProv, CReq) => t1 -> t2 -> ... -> tN -> t - - - So in the previous example, ExNumPat, - when used in an expression, has type - + So in the previous example, when used in an expression, ExNumPat has type ExNumPat :: (Show b, Num a, Eq a) => b -> T t - - - - Pattern synonyms can also be given a type signature in the source - program, e.g.: - +Notice that this is a tiny bit more restrictive than the expression MkT 42 x +which would not require (Eq a). + + +Consider these two pattern synonyms: - -- Inferred type would be 'a -> [a]' - pattern SinglePair :: (a, a) -> [(a, a)] - pattern SinglePair x = [x] +data S a where + S1 :: Bool -> S Bool + +pattern P1 b = Just b -- P1 :: Bool -> Maybe Bool +pattern P2 b = S1 b -- P2 :: (b~Bool) => Bool -> S b + +f :: Maybe a -> String +f (P1 x) = "no no no" -- Type-incorrect + +g :: S a -> String +g (P2 b) = "yes yes yes" -- Fine +Pattern P1 can only match against a value of type Maybe Bool, +so function f is rejected because the type signature is Maybe a. +(To see this, imagine expanding the pattern synonym.) + + +On the other hand, function g works fine, becuase matching against P2 +(which wraps the GADT S) provides the local equality (a~Bool). +If you were to give an explicit pattern signature P2 :: Bool -> S Bool, then P2 +would become less polymorphic, and would behave exactly like P1 so that g +would then be rejected. + + +In short, if you want GADT-like behaviour for pattern synonyms, +then (unlike unlike concrete data constructors like S1) +you must write its type with explicit provided equalities. +For a concrete data construoctr like S1 you can write +its type signature as eigher S1 :: Bool -> S Bool or +S1 :: (b~Bool) => Bool -> S b; the two are equivalent. +Not so for pattern synonyms: the two forms are different, in order to +distinguish the two cases above. (See Trac #9953 for +discussion of this choice.) + + + + Matching of pattern synonyms @@ -1173,7 +1212,7 @@ f (Pair True True) = True f _ = False f' [x, y] | True <- x, True <- y = True -f' _ = False +f' _ = False From git at git.haskell.org Mon Jan 19 11:58:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 11:58:24 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9867 (4cfd235) Message-ID: <20150119115824.A00BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4cfd235d4d52ce6e6c48013b2d5dcb347b978c24/ghc >--------------------------------------------------------------- commit 4cfd235d4d52ce6e6c48013b2d5dcb347b978c24 Author: Simon Peyton Jones Date: Mon Jan 19 11:59:28 2015 +0000 Test Trac #9867 >--------------------------------------------------------------- 4cfd235d4d52ce6e6c48013b2d5dcb347b978c24 testsuite/tests/patsyn/should_compile/T9867.hs | 5 +++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 2 files changed, 6 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T9867.hs b/testsuite/tests/patsyn/should_compile/T9867.hs new file mode 100644 index 0000000..f05c43c --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T9867.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE PatternSynonyms, ScopedTypeVariables #-} + +module T9867 where + +pattern Nil = [] :: [a] diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 086875f..0ef30f0 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -21,3 +21,4 @@ test('T8968-3', expect_broken(9953), compile, ['']) test('ImpExp_Imp', [extra_clean(['ImpExp_Exp.hi', 'ImpExp_Exp.o'])], multimod_compile, ['ImpExp_Imp', '-v0']) test('T9857', normal, compile, ['']) test('T9889', normal, compile, ['']) +test('T9867', normal, compile, ['']) From git at git.haskell.org Mon Jan 19 12:10:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 12:10:53 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update bytestring submodule (9db49ea) Message-ID: <20150119121053.2EE2F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/9db49eabab473d260a6390fce5bb14d71384576a/ghc >--------------------------------------------------------------- commit 9db49eabab473d260a6390fce5bb14d71384576a Author: Herbert Valerio Riedel Date: Mon Jan 19 12:08:58 2015 +0100 Update bytestring submodule This pulls in - https://github.com/haskell/bytestring/pull/40 (which is related to #9992) - https://github.com/haskell/bytestring/pull/38 (cherry picked from commit ff4733f4e0355085002a1f9053ba2276e92d2cb6) >--------------------------------------------------------------- 9db49eabab473d260a6390fce5bb14d71384576a libraries/bytestring | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/bytestring b/libraries/bytestring index fa7e1cc..08d5c3a 160000 --- a/libraries/bytestring +++ b/libraries/bytestring @@ -1 +1 @@ -Subproject commit fa7e1cc94982c0da85a022a501eadb1b347ea60c +Subproject commit 08d5c3a80be94a9d7ef7731317dea79aaadbd2c4 From git at git.haskell.org Mon Jan 19 12:10:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 12:10:55 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix bad '... \\' escape in ghcversion.h generation (42aad28) Message-ID: <20150119121055.BE8F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/42aad2834e634aee50254e0a67685ef129286d50/ghc >--------------------------------------------------------------- commit 42aad2834e634aee50254e0a67685ef129286d50 Author: Herbert Valerio Riedel Date: Mon Jan 19 12:18:02 2015 +0100 Fix bad '... \\' escape in ghcversion.h generation Today I learned about the peculiarities of escaping within single-quotes: Turns out, echo 'foo \\' emits foo \\ rather than escaping the '\'. Curiously, if you need to escape a ' within single-quotes, here's how to do it echo 'foo '\'' bar' which will emit foo ' bar This fixes #10002 (cherry picked from commit 1289048eaf31915b9335c6f7e0b7b64625ab0ed5) >--------------------------------------------------------------- 42aad2834e634aee50254e0a67685ef129286d50 includes/ghc.mk | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/includes/ghc.mk b/includes/ghc.mk index c7cec6c..7a255db 100644 --- a/includes/ghc.mk +++ b/includes/ghc.mk @@ -71,12 +71,12 @@ $(includes_H_VERSION) : mk/project.mk | $$(dir $$@)/. echo "#define __GLASGOW_HASKELL_PATCHLEVEL2__ $(ProjectPatchLevel2)" >> $@; \ fi @echo >> $@ - @echo '#define MIN_VERSION_GLASGOW_HASKELL(ma,mi,pl1,pl2) (\\' >> $@ - @echo ' ((ma)*100+(mi)) < __GLASGOW_HASKELL__ || \\' >> $@ - @echo ' ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \\' >> $@ - @echo ' && (pl1) < __GLASGOW_HASKELL_PATCHLEVEL1__ || \\'>> $@ - @echo ' ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \\' >> $@ - @echo ' && (pl1) == __GLASGOW_HASKELL_PATCHLEVEL1__ \\' >> $@ + @echo '#define MIN_VERSION_GLASGOW_HASKELL(ma,mi,pl1,pl2) (\' >> $@ + @echo ' ((ma)*100+(mi)) < __GLASGOW_HASKELL__ || \' >> $@ + @echo ' ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \' >> $@ + @echo ' && (pl1) < __GLASGOW_HASKELL_PATCHLEVEL1__ || \' >> $@ + @echo ' ((ma)*100+(mi)) == __GLASGOW_HASKELL__ \' >> $@ + @echo ' && (pl1) == __GLASGOW_HASKELL_PATCHLEVEL1__ \' >> $@ @echo ' && (pl2) <= __GLASGOW_HASKELL_PATCHLEVEL2__ )' >> $@ @echo >> $@ @echo "#endif /* __GHCVERSION_H__ */" >> $@ From git at git.haskell.org Mon Jan 19 12:55:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 12:55:09 +0000 (UTC) Subject: [commit: ghc] master: Revert "Fix undefined GHC.Real export with integer-simple" (e1a4581) Message-ID: <20150119125509.B41DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e1a458101a5233068f4d50fdfcfa473b5c8fdd11/ghc >--------------------------------------------------------------- commit e1a458101a5233068f4d50fdfcfa473b5c8fdd11 Author: Austin Seipp Date: Mon Jan 19 06:54:54 2015 -0600 Revert "Fix undefined GHC.Real export with integer-simple" This reverts commit 228902aa4a3350a9c99e421c0c989c7de794b7b6. This commit is dependent on d6e7f5dc9db7e382ce34d649f85505176a451a04, which broke the build on Windows (issue #9945). >--------------------------------------------------------------- e1a458101a5233068f4d50fdfcfa473b5c8fdd11 libraries/base/GHC/Real.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs index 1464709..1a18e6a 100644 --- a/libraries/base/GHC/Real.hs +++ b/libraries/base/GHC/Real.hs @@ -25,7 +25,7 @@ module GHC.Real Rational, (%), (^), (^%^), (^^), (^^%^^), denominator, divZeroError, even, - fromIntegral, gcd, infinity, integralEnumFrom, + fromIntegral, gcd, gcdInt', gcdWord', infinity, integralEnumFrom, integralEnumFromThen, integralEnumFromThenTo, integralEnumFromTo, lcm, notANumber, numerator, numericEnumFrom, numericEnumFromThen, numericEnumFromThenTo, numericEnumFromTo, odd, overflowError, ratioPrec, From git at git.haskell.org Mon Jan 19 12:55:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 12:55:12 +0000 (UTC) Subject: [commit: ghc] master: Revert "Add export lists to some modules." (f006ed7) Message-ID: <20150119125512.48AD93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f006ed7965a0fa918d720cc387b33cb8e7083854/ghc >--------------------------------------------------------------- commit f006ed7965a0fa918d720cc387b33cb8e7083854 Author: Austin Seipp Date: Mon Jan 19 06:55:57 2015 -0600 Revert "Add export lists to some modules." This reverts commit d6e7f5dc9db7e382ce34d649f85505176a451a04. This commit broke the build on Windows due to CPP weirdness (#9945). >--------------------------------------------------------------- f006ed7965a0fa918d720cc387b33cb8e7083854 libraries/base/Control/Category.hs | 2 +- libraries/base/Control/Monad/Zip.hs | 2 +- libraries/base/GHC/Base.hs | 33 +++++++++++--------------------- libraries/base/GHC/Num.hs | 7 +------ libraries/base/GHC/Real.hs | 14 +------------- libraries/base/System/Posix/Internals.hs | 27 ++------------------------ libraries/ghc-prim/GHC/Classes.hs | 19 +----------------- 7 files changed, 18 insertions(+), 86 deletions(-) diff --git a/libraries/base/Control/Category.hs b/libraries/base/Control/Category.hs index d21d4f9..ab7740b 100644 --- a/libraries/base/Control/Category.hs +++ b/libraries/base/Control/Category.hs @@ -15,7 +15,7 @@ -- http://ghc.haskell.org/trac/ghc/ticket/1773 -module Control.Category ((<<<), (>>>), Category(..)) where +module Control.Category where import qualified GHC.Base (id,(.)) import Data.Type.Coercion diff --git a/libraries/base/Control/Monad/Zip.hs b/libraries/base/Control/Monad/Zip.hs index b994c47..df096b1 100644 --- a/libraries/base/Control/Monad/Zip.hs +++ b/libraries/base/Control/Monad/Zip.hs @@ -15,7 +15,7 @@ -- ----------------------------------------------------------------------------- -module Control.Monad.Zip (MonadZip(..)) where +module Control.Monad.Zip where import Control.Monad (liftM) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index e3d247e..44085a2 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -93,28 +93,17 @@ Other Prelude modules are much easier with fewer complex dependencies. #include "MachDeps.h" module GHC.Base - ( - module GHC.Classes, - module GHC.CString, - module GHC.Magic, - module GHC.Types, - module GHC.Prim, -- Re-export GHC.Prim and [boot] GHC.Err, - -- to avoid lots of people having to - module GHC.Err, -- import it explicitly - - - Alternative(..), Applicative(..), Functor(..), Maybe(..), Monad(..), - MonadPlus(..), Monoid(..), Opaque(..), String, - - - ($), ($!), (++), (.), (<**>), (=<<), ap, asTypeOf, assert, augment, - bindIO, breakpoint, breakpointCond, build, const, divInt, divModInt, - divModInt#, eqString, flip, foldr, getTag, iShiftL#, iShiftRA#, - iShiftRL#, id, join, liftA, liftA2, liftA3, liftM, liftM2, liftM3, - liftM4, liftM5, map, mapFB, mapM, maxInt, minInt, modInt, ord, - otherwise, quotInt, quotRemInt, remInt, returnIO, sequence, shiftL#, - shiftRL#, thenIO, unIO, unsafeChr, until, when - ) where + ( + module GHC.Base, + module GHC.Classes, + module GHC.CString, + module GHC.Magic, + module GHC.Types, + module GHC.Prim, -- Re-export GHC.Prim and [boot] GHC.Err, + -- to avoid lots of people having to + module GHC.Err -- import it explicitly + ) + where import GHC.Types import GHC.Classes diff --git a/libraries/base/GHC/Num.hs b/libraries/base/GHC/Num.hs index 0b331fc..5d46dac 100644 --- a/libraries/base/GHC/Num.hs +++ b/libraries/base/GHC/Num.hs @@ -16,12 +16,7 @@ -- ----------------------------------------------------------------------------- -module GHC.Num - ( - module GHC.Integer - , Num(..) - , subtract - ) where +module GHC.Num (module GHC.Num, module GHC.Integer) where import GHC.Base import GHC.Integer diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs index 1a18e6a..71de0d2 100644 --- a/libraries/base/GHC/Real.hs +++ b/libraries/base/GHC/Real.hs @@ -18,19 +18,7 @@ -- ----------------------------------------------------------------------------- -module GHC.Real - ( - Fractional(..), Integral(..), Ratio(..), Real(..), RealFrac(..), - - Rational, - - (%), (^), (^%^), (^^), (^^%^^), denominator, divZeroError, even, - fromIntegral, gcd, gcdInt', gcdWord', infinity, integralEnumFrom, - integralEnumFromThen, integralEnumFromThenTo, integralEnumFromTo, lcm, - notANumber, numerator, numericEnumFrom, numericEnumFromThen, - numericEnumFromThenTo, numericEnumFromTo, odd, overflowError, ratioPrec, - ratioPrec1, ratioZeroDenominatorError, realToFrac, reduce, showSigned - ) where +module GHC.Real where import GHC.Base import GHC.Num diff --git a/libraries/base/System/Posix/Internals.hs b/libraries/base/System/Posix/Internals.hs index e2e32c3..c49e613 100644 --- a/libraries/base/System/Posix/Internals.hs +++ b/libraries/base/System/Posix/Internals.hs @@ -20,30 +20,7 @@ -- ----------------------------------------------------------------------------- -module System.Posix.Internals - ( - CFLock, CFilePath, CGroup, CLconv, CPasswd, CSigaction, CSigset, CStat, - CTermios, CTm, CTms, CUtimbuf, CUtsname, FD, - - c_access, c_chmod, c_close, c_creat, c_dup, c_dup2, c_fcntl_lock, - c_fcntl_read, c_fcntl_write, c_fork, c_fstat, c_ftruncate, c_getpid, - c_isatty, c_lflag, c_link, c_lseek, c_mkfifo, c_open, c_pipe, c_read, - c_s_isblk, c_s_ischr, c_s_isdir, c_s_isfifo, c_s_isreg, c_s_issock, - c_safe_open, c_safe_read, c_safe_write, c_sigaddset, c_sigemptyset, - c_sigprocmask, c_stat, c_tcgetattr, c_tcsetattr, c_umask, c_unlink, - c_utime, c_waitpid, c_write, const_echo, const_f_getfl, const_f_setfd, - const_f_setfl, const_fd_cloexec, const_icanon, const_sig_block, - const_sig_setmask, const_sigttou, const_tcsanow, const_vmin, const_vtime, - dEFAULT_BUFFER_SIZE, fdFileSize, fdGetMode, fdStat, fdType, fileType, - getEcho, get_saved_termios, ioe_unknownfiletype, lstat, newFilePath, - o_APPEND, o_BINARY, o_CREAT, o_EXCL, o_NOCTTY, o_NONBLOCK, o_RDONLY, - o_RDWR, o_TRUNC, o_WRONLY, peekFilePath, peekFilePathLen, poke_c_lflag, - ptr_c_cc, puts, sEEK_CUR, sEEK_END, sEEK_SET, s_isblk, s_ischr, s_isdir, - s_isfifo, s_isreg, s_issock, setCloseOnExec, setCooked, setEcho, - setNonBlockingFD, set_saved_termios, sizeof_sigset_t, sizeof_stat, - sizeof_termios, st_dev, st_ino, st_mode, st_mtime, st_size, statGetType, - tcSetAttr, withFilePath - ) where +module System.Posix.Internals where #include "HsBaseConfig.h" @@ -65,7 +42,7 @@ import GHC.Real import GHC.IO import GHC.IO.IOMode import GHC.IO.Exception -import GHC.IO.Device hiding (getEcho, setEcho) +import GHC.IO.Device #ifndef mingw32_HOST_OS import {-# SOURCE #-} GHC.IO.Encoding (getFileSystemEncoding) import qualified GHC.Foreign as GHC diff --git a/libraries/ghc-prim/GHC/Classes.hs b/libraries/ghc-prim/GHC/Classes.hs index 3f09ff7..9028f6e 100644 --- a/libraries/ghc-prim/GHC/Classes.hs +++ b/libraries/ghc-prim/GHC/Classes.hs @@ -17,24 +17,7 @@ -- ----------------------------------------------------------------------------- -module GHC.Classes - ( - (&&) - , (||) - , compareInt - , compareInt# - , divInt# - , eqInt - , geInt - , gtInt - , leInt - , ltInt - , modInt# - , neInt - , not - , Eq(..) - , Ord(..) - ) where +module GHC.Classes where -- GHC.Magic is used in some derived instances import GHC.Magic () From git at git.haskell.org Mon Jan 19 13:41:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 13:41:43 +0000 (UTC) Subject: [commit: ghc] master: Make AutoDeriveTypeable work for associated datatypes (fix #9999) (d839493) Message-ID: <20150119134143.809873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d839493991e508160d416311ba47b7a7e2d62aae/ghc >--------------------------------------------------------------- commit d839493991e508160d416311ba47b7a7e2d62aae Author: Jose Pedro Magalhaes Date: Mon Jan 19 13:36:03 2015 +0000 Make AutoDeriveTypeable work for associated datatypes (fix #9999) >--------------------------------------------------------------- d839493991e508160d416311ba47b7a7e2d62aae compiler/typecheck/TcDeriv.hs | 13 +++++++++---- testsuite/tests/typecheck/should_compile/T9999.hs | 13 +++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 23 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 10191ae..ae95f33 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -561,11 +561,16 @@ deriveAutoTypeable auto_typeable done_specs tycl_decls do_one cls (L _ decl) = do { tc <- tcLookupTyCon (tcdName decl) - ; if (isTypeSynonymTyCon tc || isTypeFamilyTyCon tc + -- Traverse into class declarations to check if they have ATs (#9999) + ; ats <- if isClassDecl decl + then concatMapM (do_one cls) (map (fmap FamDecl) (tcdATs decl)) + else return [] + ; rest <- if (isTypeSynonymTyCon tc || isTypeFamilyTyCon tc || tyConName tc `elemNameSet` done_tcs) - -- Do not derive Typeable for type synonyms or type families - then return [] - else mkPolyKindedTypeableEqn cls tc } + -- Do not derive Typeable for type synonyms or type families + then return [] + else mkPolyKindedTypeableEqn cls tc + ; return (ats ++ rest) } ------------------------------------------------------------------ deriveTyDecl :: LTyClDecl Name -> TcM [EarlyDerivSpec] diff --git a/testsuite/tests/typecheck/should_compile/T9999.hs b/testsuite/tests/typecheck/should_compile/T9999.hs new file mode 100644 index 0000000..656e913 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9999.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE AutoDeriveTypeable, PolyKinds, TypeFamilies, StandaloneDeriving #-} + +module T9999 where + +import Data.Typeable + +data family F a + +class C a where + data F1 a + type F2 a + +main = typeRep (Proxy :: Proxy F) == typeRep (Proxy :: Proxy F1) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 38c41f1..c292eaf 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -440,3 +440,4 @@ test('T9892', normal, compile, ['']) test('T9939', normal, compile, ['']) test('T9973', normal, compile, ['']) test('T9971', normal, compile, ['']) +test('T9999', normal, compile, ['']) From git at git.haskell.org Mon Jan 19 13:57:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 13:57:56 +0000 (UTC) Subject: [commit: ghc] master: Split stripTicks into expression editing and tick collection (55199a9) Message-ID: <20150119135756.91FA33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/55199a97c020761ff4bfdc06da0042e43bede697/ghc >--------------------------------------------------------------- commit 55199a97c020761ff4bfdc06da0042e43bede697 Author: Peter Wortmann Date: Mon Jan 19 07:57:19 2015 -0600 Split stripTicks into expression editing and tick collection As with stripTicksTop, this is because we often need the stripped expression but not the ticks (at least not right away). This makes a big difference for CSE, see #9961. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 55199a97c020761ff4bfdc06da0042e43bede697 compiler/coreSyn/CoreLint.hs | 2 +- compiler/coreSyn/CoreUtils.hs | 55 +++++++++++++++++++++---------------- compiler/simplCore/CSE.hs | 10 ++++--- compiler/simplCore/SimplUtils.hs | 4 +-- testsuite/tests/perf/compiler/all.T | 10 +++++++ 5 files changed, 51 insertions(+), 30 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 3dca78e..5ae7a59 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -1759,7 +1759,7 @@ withoutAnnots pass guts = do -- Nuke existing ticks in module. -- TODO: Ticks in unfoldings. Maybe change unfolding so it removes -- them in absence of @Opt_Debug@? - let nukeTicks = snd . stripTicks (not . tickishIsCode) + let nukeTicks = stripTicksE (not . tickishIsCode) nukeAnnotsBind :: CoreBind -> CoreBind nukeAnnotsBind bind = case bind of Rec bs -> Rec $ map (\(b,e) -> (b, nukeTicks e)) bs diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 135f81a..28981a3 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -44,7 +44,8 @@ module CoreUtils ( dataConRepInstPat, dataConRepFSInstPat, -- * Working with ticks - stripTicksTop, stripTicksTopE, stripTicksTopT, stripTicks, + stripTicksTop, stripTicksTopE, stripTicksTopT, + stripTicksE, stripTicksT ) where #include "HsVersions.h" @@ -77,10 +78,6 @@ import Pair import Data.Function ( on ) import Data.List import Data.Ord ( comparing ) -import Control.Applicative -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable ( traverse ) -#endif import OrdList {- @@ -358,25 +355,37 @@ stripTicksTopT p = go [] -- | Completely strip ticks satisfying a predicate from an -- expression. Note this is O(n) in the size of the expression! -stripTicks :: (Tickish Id -> Bool) -> Expr b -> ([Tickish Id], Expr b) -stripTicks p expr = (fromOL ticks, expr') - where (ticks, expr') = go expr - -- Note that OrdList (Tickish Id) is a Monoid, which makes - -- ((,) (OrdList (Tickish Id))) an Applicative. - go (App e a) = App <$> go e <*> go a - go (Lam b e) = Lam b <$> go e - go (Let b e) = Let <$> go_bs b <*> go e - go (Case e b t as) = Case <$> go e <*> pure b <*> pure t - <*> traverse go_a as - go (Cast e c) = Cast <$> go e <*> pure c +stripTicksE :: (Tickish Id -> Bool) -> Expr b -> Expr b +stripTicksE p expr = go expr + where go (App e a) = App (go e) (go a) + go (Lam b e) = Lam b (go e) + go (Let b e) = Let (go_bs b) (go e) + go (Case e b t as) = Case (go e) b t (map go_a as) + go (Cast e c) = Cast (go e) c go (Tick t e) - | p t = let (ts, e') = go e in (t `consOL` ts, e') - | otherwise = Tick t <$> go e - go other = pure other - go_bs (NonRec b e) = NonRec b <$> go e - go_bs (Rec bs) = Rec <$> traverse go_b bs - go_b (b, e) = (,) <$> pure b <*> go e - go_a (c,bs,e) = (,,) <$> pure c <*> pure bs <*> go e + | p t = go e + | otherwise = Tick t (go e) + go other = other + go_bs (NonRec b e) = NonRec b (go e) + go_bs (Rec bs) = Rec (map go_b bs) + go_b (b, e) = (b, go e) + go_a (c,bs,e) = (c,bs, go e) + +stripTicksT :: (Tickish Id -> Bool) -> Expr b -> [Tickish Id] +stripTicksT p expr = fromOL $ go expr + where go (App e a) = go e `appOL` go a + go (Lam _ e) = go e + go (Let b e) = go_bs b `appOL` go e + go (Case e _ _ as) = go e `appOL` concatOL (map go_a as) + go (Cast e _) = go e + go (Tick t e) + | p t = t `consOL` go e + | otherwise = go e + go _ = nilOL + go_bs (NonRec _ e) = go e + go_bs (Rec bs) = concatOL (map go_b bs) + go_b (_, e) = go e + go_a (_, _, e) = go e {- ************************************************************************ diff --git a/compiler/simplCore/CSE.hs b/compiler/simplCore/CSE.hs index a30c695..c43cbb7 100644 --- a/compiler/simplCore/CSE.hs +++ b/compiler/simplCore/CSE.hs @@ -15,7 +15,7 @@ import Var ( Var ) import Id ( Id, idType, idInlineActivation, zapIdOccInfo ) import CoreUtils ( mkAltExpr , exprIsTrivial - , stripTicks, stripTicksTopE, mkTick, mkTicks ) + , stripTicksE, stripTicksT, stripTicksTopE, mkTick, mkTicks ) import Type ( tyConAppArgs ) import CoreSyn import Outputable @@ -190,7 +190,8 @@ cseRhs env (id',rhs) where rhs' = cseExpr env rhs - (ticks, rhs'') = stripTicks tickishFloatable rhs' + ticks = stripTicksT tickishFloatable rhs' + rhs'' = stripTicksE tickishFloatable rhs' -- We don't want to lose the source notes when a common sub -- expression gets eliminated. Hence we push all (!) of them on -- top of the replaced sub-expression. This is probably not too @@ -206,7 +207,8 @@ tryForCSE env expr | otherwise = expr' where expr' = cseExpr env expr - (ticks, expr'') = stripTicks tickishFloatable expr' + expr'' = stripTicksE tickishFloatable expr' + ticks = stripTicksT tickishFloatable expr' cseExpr :: CSEnv -> InExpr -> OutExpr cseExpr env (Type t) = Type (substTy (csEnvSubst env) t) @@ -296,7 +298,7 @@ lookupCSEnv (CS { cs_map = csmap }) expr extendCSEnv :: CSEnv -> OutExpr -> Id -> CSEnv extendCSEnv cse expr id = cse { cs_map = extendCoreMap (cs_map cse) sexpr (sexpr,id) } - where (_, sexpr) = stripTicks tickishFloatable expr + where sexpr = stripTicksE tickishFloatable expr csEnvSubst :: CSEnv -> Subst csEnvSubst = cs_subst diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs index ccc8a56..6bb290e 100644 --- a/compiler/simplCore/SimplUtils.hs +++ b/compiler/simplCore/SimplUtils.hs @@ -1658,7 +1658,7 @@ combineIdenticalAlts case_bndr ((_con1,bndrs1,rhs1) : con_alts) cheapEqTicked e1 e2 = cheapEqExpr' tickishFloatable e1 e2 identical_to_alt1 (_con,bndrs,rhs) = all isDeadBinder bndrs && rhs `cheapEqTicked` rhs1 - tickss = map (fst . stripTicks tickishFloatable . thirdOf3) eliminated_alts + tickss = map (stripTicksT tickishFloatable . thirdOf3) eliminated_alts combineIdenticalAlts _ alts = return alts @@ -1755,7 +1755,7 @@ mkCase1 _dflags scrut case_bndr _ alts@((_,_,rhs1) : _) -- Identity case = do { tick (CaseIdentity case_bndr) ; return (mkTicks ticks $ re_cast scrut rhs1) } where - ticks = concatMap (fst . stripTicks tickishFloatable . thirdOf3) (tail alts) + ticks = concatMap (stripTicksT tickishFloatable . thirdOf3) (tail alts) identity_alt (con, args, rhs) = check_eq rhs con args check_eq (Cast rhs co) con args diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 62fe32a..ece1243 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -617,3 +617,13 @@ test('T9872d', ], compile, ['']) + +test('T9961', + [ only_ways(['normal']), + compiler_stats_num_field('bytes allocated', + [(wordsize(64), 772510192, 5) + # 2015-01-12 807117816 Initally created + ]), + ], + compile, + ['-O']) From git at git.haskell.org Mon Jan 19 13:58:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 13:58:14 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: add -th-file which generates a th.hs file (dfb2b5d) Message-ID: <20150119135814.328523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/dfb2b5d0f00e4bd5c0ed2af9a24eaf264c4166a9/ghc >--------------------------------------------------------------- commit dfb2b5d0f00e4bd5c0ed2af9a24eaf264c4166a9 Author: Greg Weber Date: Mon Jan 12 05:16:37 2015 -0600 add -th-file which generates a th.hs file Summary: see Trac #8624 similar functionality is now available with -ddump-to-file -ddump-splices However, users are already accustomed to -ddump-splices having a particular format, and this format is not completely valid code The goal of -th-file is to dump valid Haskell code Additionally, the convention of -ddump-to-file is to name the file after the flag, so the file is .dump-splices Given that the goal of the new flag is to generate valid Haskell, The extension should be .hs Additionally, -ddump-to-file effects all other dump flags Test Plan: look at the output of using the -th-file flag and compare it to the output of using -ddump-to-file and -ddump-splices I want to add test cases, but just need some pointers on getting started there Reviewers: thomie, goldfire, simonpj, austin Reviewed By: simonpj, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D518 GHC Trac Issues: #8624 (cherry picked from commit 07ace5c221adbb1675413a0fac300a9f7913c234) Conflicts: docs/users_guide/7.12.1-notes.xml >--------------------------------------------------------------- dfb2b5d0f00e4bd5c0ed2af9a24eaf264c4166a9 .gitignore | 8 +++ compiler/main/DynFlags.hs | 4 ++ compiler/main/ErrUtils.hs | 3 +- compiler/rename/RnSplice.hs | 63 +++++++++++++++++++--- compiler/typecheck/TcRnDriver.hs | 11 ++-- compiler/typecheck/TcRnMonad.hs | 11 ++-- compiler/typecheck/TcSplice.hs | 63 ++++++++++++++++++---- compiler/typecheck/TcSplice.hs-boot | 14 ++++- docs/users_guide/7.10.1-notes.xml | 17 ++++++ docs/users_guide/flags.xml | 6 +++ docs/users_guide/glasgow_exts.xml | 42 +++++++++++++-- .../tests/indexed-types/should_fail/T8129.stdout | 1 - testsuite/tests/th/Makefile | 6 +++ testsuite/tests/th/T3319.stderr | 3 +- testsuite/tests/th/T3600.stderr | 3 +- testsuite/tests/th/T5217.stderr | 3 +- testsuite/tests/th/T5290.stderr | 3 +- testsuite/tests/th/T5700.stderr | 3 +- testsuite/tests/th/T5883.stderr | 3 +- testsuite/tests/th/T5984.stderr | 6 +-- testsuite/tests/th/T7532.stderr | 3 +- testsuite/tests/th/T8624.hs | 7 +++ .../tests/th/T8624.stderr | 0 testsuite/tests/th/T8624.stdout | 2 + testsuite/tests/th/TH_TyInstWhere1.stderr | 3 +- .../tests/th/TH_foreignCallingConventions.stderr | 3 +- testsuite/tests/th/TH_foreignInterruptible.stderr | 3 +- testsuite/tests/th/TH_genEx.stderr | 3 +- testsuite/tests/th/TH_pragma.stderr | 6 +-- testsuite/tests/th/all.T | 1 + 30 files changed, 239 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dfb2b5d0f00e4bd5c0ed2af9a24eaf264c4166a9 From git at git.haskell.org Mon Jan 19 13:58:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 13:58:17 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Trac #9878: Make the static form illegal in interpreted mode. (ced7f4f) Message-ID: <20150119135817.627B23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/ced7f4fb582c570cee84b4b2cb665f7499b34ebc/ghc >--------------------------------------------------------------- commit ced7f4fb582c570cee84b4b2cb665f7499b34ebc Author: Alexander Vershilov Date: Wed Jan 14 17:58:30 2015 -0600 Trac #9878: Make the static form illegal in interpreted mode. Summary: The entries of the static pointers table are expected to exist as object code. Thus we have ghci complain with an intelligible error message if the static form is used in interpreted mode. It also includes a fix to keysHashTable in Hash.c which could cause a crash. The iteration of the hashtable internals was incorrect. This patch has the function keysHashTable imitate the iteration in freeHashTable. Finally, we submit here some minor edits to comments and GHC.StaticPtr.StaticPtrInfo field names. Authored-by: Alexander Vershilov Test Plan: ./validate Reviewers: simonpj, hvr, austin Reviewed By: austin Subscribers: carter, thomie, qnikst, mboes Differential Revision: https://phabricator.haskell.org/D586 GHC Trac Issues: #9878 (cherry picked from commit fffbf0627c2c2ee4bc49f9d26a226b39a066945e) >--------------------------------------------------------------- ced7f4fb582c570cee84b4b2cb665f7499b34ebc compiler/deSugar/DsExpr.hs | 4 ++-- compiler/rename/RnExpr.hs | 9 ++++++++ includes/rts/StaticPtrTable.h | 4 ++-- libraries/base/GHC/StaticPtr.hs | 4 ++-- rts/Hash.c | 24 ++++++++++++++-------- .../deSugar/should_run/DsStaticPointers.stdout | 10 ++++----- testsuite/tests/ghci/scripts/T9878.hs | 6 ++++++ testsuite/tests/ghci/scripts/T9878.script | 1 + testsuite/tests/ghci/scripts/T9878.stderr | 4 ++++ testsuite/tests/ghci/scripts/T9878b.script | 2 ++ .../tests/ghci/scripts/T9878b.stdout | 0 testsuite/tests/ghci/scripts/all.T | 7 +++++++ 12 files changed, 56 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ced7f4fb582c570cee84b4b2cb665f7499b34ebc From git at git.haskell.org Mon Jan 19 13:58:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 13:58:23 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Trac #9384: fix increasing capabilites number for eventlog. (87697aa) Message-ID: <20150119135823.49FEF3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/87697aadda4b5a11c23c48f7e5f011b6daf9e470/ghc >--------------------------------------------------------------- commit 87697aadda4b5a11c23c48f7e5f011b6daf9e470 Author: Alexander Vershilov Date: Sun Jan 18 10:58:57 2015 +0000 Trac #9384: fix increasing capabilites number for eventlog. Event log had inconcistent support for increacing capabilies number, as header were not inserted in capability buffer. It resulted in a ghc-events crash (see #9384). This commit fixes this issue by inserting required header when number of capabilies grows. Reviewers: simonmar, Mikolaj, trofi, austin Reviewed By: Mikolaj, trofi, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D592 GHC Trac Issues: #9384 (cherry picked from commit 2edb4a7bd5b892ddfac75d0b549d6682a0be5c02) >--------------------------------------------------------------- 87697aadda4b5a11c23c48f7e5f011b6daf9e470 rts/eventlog/EventLog.c | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/rts/eventlog/EventLog.c b/rts/eventlog/EventLog.c index ef96f3c..f830ec1 100644 --- a/rts/eventlog/EventLog.c +++ b/rts/eventlog/EventLog.c @@ -500,6 +500,15 @@ moreCapEventBufs (nat from, nat to) for (c = from; c < to; ++c) { initEventsBuf(&capEventBuf[c], EVENT_LOG_SIZE, c); } + + // The from == 0 already covered in initEventLogging, so we are interested + // only in case when we are increasing capabilities number + if (from > 0) { + for (c = from; c < to; ++c) { + postBlockMarker(&capEventBuf[c]); + } + } + } From git at git.haskell.org Mon Jan 19 13:58:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 13:58:20 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix panics of PartialTypeSignatures combined with extensions (95368a7) Message-ID: <20150119135820.882E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/95368a70b16ee384ccb6cd6cf62d4efb3d9b9c8f/ghc >--------------------------------------------------------------- commit 95368a70b16ee384ccb6cd6cf62d4efb3d9b9c8f Author: Thomas Winant Date: Mon Jan 12 05:29:50 2015 -0600 Fix panics of PartialTypeSignatures combined with extensions Summary: Disallow wildcards in stand-alone deriving instances (StandaloneDeriving), default signatures (DefaultSignatures) and instances signatures (InstanceSigs). Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: carter, thomie, monoidal Differential Revision: https://phabricator.haskell.org/D595 GHC Trac Issues: #9922 (cherry picked from commit c9532f810a82c6395bc08fb77f2a895a50da86b5) >--------------------------------------------------------------- 95368a70b16ee384ccb6cd6cf62d4efb3d9b9c8f compiler/parser/Parser.y | 15 +++++++++++++-- .../should_fail/WildcardInDefaultSignature.hs | 4 ++++ .../should_fail/WildcardInDefaultSignature.stderr | 4 ++++ .../partial-sigs/should_fail/WildcardInInstanceSig.hs | 4 ++++ .../partial-sigs/should_fail/WildcardInInstanceSig.stderr | 4 ++++ .../should_fail/WildcardInStandaloneDeriving.hs | 4 ++++ .../should_fail/WildcardInStandaloneDeriving.stderr | 4 ++++ testsuite/tests/partial-sigs/should_fail/all.T | 3 +++ 8 files changed, 40 insertions(+), 2 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 7739d97..817a96e 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -798,6 +798,10 @@ inst_decl :: { LInstDecl RdrName } , cid_datafam_insts = adts } ; let err = text "In instance head:" <+> ppr $3 ; checkNoPartialType err $3 + ; sequence_ [ checkNoPartialType err ty + | sig@(L _ (TypeSig _ ty _ )) <- sigs + , let err = text "in instance signature" <> colon + <+> quotes (ppr sig) ] ; ams (L (comb3 $1 $3 $4) (ClsInstD { cid_inst = cid })) (mj AnnInstance $1 : (fst $ unLoc $4)) } } @@ -972,8 +976,12 @@ capi_ctype : '{-# CTYPE' STRING STRING '#-}' -- Glasgow extension: stand-alone deriving declarations stand_alone_deriving :: { LDerivDecl RdrName } : 'deriving' 'instance' overlap_pragma inst_type - {% ams (sLL $1 $> (DerivDecl $4 $3)) - [mj AnnDeriving $1,mj AnnInstance $2] } + {% do { + let err = text "in the stand-alone deriving instance" + <> colon <+> quotes (ppr $4) + ; checkNoPartialType err $4 + ; ams (sLL $1 $> (DerivDecl $4 $3)) + [mj AnnDeriving $1,mj AnnInstance $2] }} ----------------------------------------------------------------------------- -- Role annotations @@ -1070,6 +1078,9 @@ decl_cls : at_decl_cls { sLL $1 $> (unitOL $1) } -- A 'default' signature used with the generic-programming extension | 'default' infixexp '::' sigtypedoc {% do { (TypeSig l ty _) <- checkValSig $2 $4 + ; let err = text "in default signature" <> colon <+> + quotes (ppr ty) + ; checkNoPartialType err ty ; ams (sLL $1 $> $ unitOL (sLL $1 $> $ SigD (GenericSig l ty))) [mj AnnDefault $1,mj AnnDcolon $3] } } diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.hs b/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.hs new file mode 100644 index 0000000..5e85e59 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE DefaultSignatures #-} +module WildcardInDefaultSignature where + +class C a where default f :: _ diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.stderr b/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.stderr new file mode 100644 index 0000000..38cb4ce --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInDefaultSignature.stderr @@ -0,0 +1,4 @@ + +WildcardInDefaultSignature.hs:4:30: + Wildcard not allowed + in default signature: ?_? diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.hs b/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.hs new file mode 100644 index 0000000..cd36449 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE InstanceSigs #-} +module WildcardInInstanceSig where + +instance Num Bool where negate :: _ diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.stderr b/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.stderr new file mode 100644 index 0000000..e8148f1 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceSig.stderr @@ -0,0 +1,4 @@ + +WildcardInInstanceSig.hs:4:35: + Wildcard not allowed + in instance signature: ?negate :: _? diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.hs b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.hs new file mode 100644 index 0000000..6348921 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE StandaloneDeriving #-} +module WildcardInStandaloneDeriving where + +deriving instance _ diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr new file mode 100644 index 0000000..921d7a0 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr @@ -0,0 +1,4 @@ + +WildcardInStandaloneDeriving.hs:4:19: + Wildcard not allowed + in the stand-alone deriving instance: ?_? diff --git a/testsuite/tests/partial-sigs/should_fail/all.T b/testsuite/tests/partial-sigs/should_fail/all.T index c275e93..7e56d15 100644 --- a/testsuite/tests/partial-sigs/should_fail/all.T +++ b/testsuite/tests/partial-sigs/should_fail/all.T @@ -26,15 +26,18 @@ test('WildcardInADT3', normal, compile_fail, ['']) test('WildcardInADTContext1', normal, compile_fail, ['']) test('WildcardInADTContext2', normal, compile_fail, ['']) test('WildcardInDefault', normal, compile_fail, ['']) +test('WildcardInDefaultSignature', normal, compile_fail, ['']) test('WildcardInDeriving', normal, compile_fail, ['']) test('WildcardInForeignExport', normal, compile_fail, ['']) test('WildcardInForeignImport', normal, compile_fail, ['']) test('WildcardInGADT1', normal, compile_fail, ['']) test('WildcardInGADT2', normal, compile_fail, ['']) test('WildcardInInstanceHead', normal, compile_fail, ['']) +test('WildcardInInstanceSig', normal, compile_fail, ['']) test('WildcardsInPatternAndExprSig', normal, compile_fail, ['']) test('WildcardInPatSynSig', normal, compile_fail, ['']) test('WildcardInNewtype', normal, compile_fail, ['']) +test('WildcardInStandaloneDeriving', normal, compile_fail, ['']) test('WildcardInstantiations', normal, compile_fail, ['']) test('WildcardInTypeBrackets', [req_interp, only_compiler_types(['ghc'])], compile_fail, ['']) test('WildcardInTypeFamilyInstanceLHS', normal, compile_fail, ['']) From git at git.haskell.org Mon Jan 19 13:58:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 13:58:26 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Pattern synonym names need to be in scope before renaming bindings (#9889) (f0754dc) Message-ID: <20150119135826.9DCF53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/f0754dcb4834ebc93a3908ef9c945ab6c3e19587/ghc >--------------------------------------------------------------- commit f0754dcb4834ebc93a3908ef9c945ab6c3e19587 Author: Dr. ERDI Gergo Date: Wed Dec 17 22:09:06 2014 +0800 Pattern synonym names need to be in scope before renaming bindings (#9889) I did a bit of refactoring at the same time, needless to say (cherry picked from commit 5830fc449af6b2c0ef5be409fd3457114ae938ca) >--------------------------------------------------------------- f0754dcb4834ebc93a3908ef9c945ab6c3e19587 compiler/hsSyn/HsBinds.hs | 10 ++ compiler/hsSyn/HsUtils.hs | 130 +++++++++++++-------- compiler/rename/RnBinds.hs | 28 +++-- compiler/rename/RnEnv.hs | 2 +- compiler/rename/RnNames.hs | 26 +++-- compiler/rename/RnPat.hs | 18 ++- compiler/rename/RnSource.hs | 26 +++-- compiler/typecheck/TcBinds.hs | 55 ++++----- testsuite/tests/ghci/scripts/T8776.stdout | 2 +- .../patsyn/should_compile/{num.hs => T9889.hs} | 6 +- testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/local.stderr | 4 +- testsuite/tests/patsyn/should_run/ghci.stdout | 2 +- 13 files changed, 185 insertions(+), 125 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f0754dcb4834ebc93a3908ef9c945ab6c3e19587 From git at git.haskell.org Mon Jan 19 13:58:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 13:58:29 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Package environments (d6ddfcc) Message-ID: <20150119135829.695F23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/d6ddfcc0d49415513a2394b02c3cff641c9dc865/ghc >--------------------------------------------------------------- commit d6ddfcc0d49415513a2394b02c3cff641c9dc865 Author: Edsko de Vries Date: Mon Jan 12 05:22:22 2015 -0600 Package environments Summary: Package environments are files with package IDs that indicate which packages should be visible; see entry in user guide for details. Reviewers: duncan, austin Reviewed By: duncan, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D558 (cherry picked from commit 099b76769f02432d8efcd7881348e5f5b6b50787) >--------------------------------------------------------------- d6ddfcc0d49415513a2394b02c3cff641c9dc865 compiler/main/CmdLineParser.hs | 8 +-- compiler/main/DynFlags.hs | 118 ++++++++++++++++++++++++++++++++++++++++- compiler/main/Packages.hs | 11 ++-- compiler/utils/Maybes.hs | 24 +++++++-- docs/users_guide/packages.xml | 86 ++++++++++++++++++++++++++++++ 5 files changed, 234 insertions(+), 13 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d6ddfcc0d49415513a2394b02c3cff641c9dc865 From git at git.haskell.org Mon Jan 19 13:58:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 13:58:32 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Don't hardcode the name "ghc" in versionedAppDir (d33e2ff) Message-ID: <20150119135832.0C7373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/d33e2ffbe33a99252708a9761995109ddac04a7f/ghc >--------------------------------------------------------------- commit d33e2ffbe33a99252708a9761995109ddac04a7f Author: Edsko de Vries Date: Wed Jan 14 17:58:13 2015 -0600 Don't hardcode the name "ghc" in versionedAppDir Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D618 (cherry picked from commit 6392df07e89304a4daeb1af379c051b03a39cda7) >--------------------------------------------------------------- d33e2ffbe33a99252708a9761995109ddac04a7f compiler/main/CmdLineParser.hs | 2 +- compiler/main/DynFlags.hs | 8 ++++---- compiler/main/Packages.hs | 5 ++--- 3 files changed, 7 insertions(+), 8 deletions(-) diff --git a/compiler/main/CmdLineParser.hs b/compiler/main/CmdLineParser.hs index 951db0e..dc2fd1c 100644 --- a/compiler/main/CmdLineParser.hs +++ b/compiler/main/CmdLineParser.hs @@ -18,7 +18,7 @@ module CmdLineParser Flag(..), defFlag, defGhcFlag, defGhciFlag, defHiddenFlag, errorsToGhcException, - EwM(..), runEwM, addErr, addWarn, getArg, getCurLoc, liftEwM, deprecate + EwM, runEwM, addErr, addWarn, getArg, getCurLoc, liftEwM, deprecate ) where #include "HsVersions.h" diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index a1b1400..c373fdf 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1021,9 +1021,9 @@ opt_lc dflags = sOpt_lc (settings dflags) -- | The directory for this version of ghc in the user's app directory -- (typically something like @~/.ghc/x86_64-linux-7.6.3@) -- -versionedAppDir :: IO FilePath -versionedAppDir = do - appdir <- getAppUserDataDirectory "ghc" +versionedAppDir :: DynFlags -> IO FilePath +versionedAppDir dflags = do + appdir <- getAppUserDataDirectory (programName dflags) return $ appdir (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion) -- | The target code type of the compilation (if any). @@ -3768,7 +3768,7 @@ interpretPackageEnv dflags = do namedEnvPath :: String -> MaybeT IO FilePath namedEnvPath name = do - appdir <- liftMaybeT $ versionedAppDir + appdir <- liftMaybeT $ versionedAppDir dflags return $ appdir "environments" name loadEnvName :: String -> MaybeT IO String diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index e081a31..dec7b5b 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -354,10 +354,9 @@ getPackageConfRefs dflags = do resolvePackageConfig :: DynFlags -> PkgConfRef -> IO (Maybe FilePath) resolvePackageConfig dflags GlobalPkgConf = return $ Just (systemPackageConfig dflags) -resolvePackageConfig _ UserPkgConf = handleIO (\_ -> return Nothing) $ do - dir <- versionedAppDir +resolvePackageConfig dflags UserPkgConf = handleIO (\_ -> return Nothing) $ do + dir <- versionedAppDir dflags let pkgconf = dir "package.conf.d" - exist <- doesDirectoryExist pkgconf return $ if exist then Just pkgconf else Nothing resolvePackageConfig _ (PkgConfFile name) = return $ Just name From git at git.haskell.org Mon Jan 19 13:58:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 13:58:34 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Dwarf generation fixed pt 2 (4ab5702) Message-ID: <20150119135834.9F6143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/4ab57024548c32a64baf069c8d78ffba073750e4/ghc >--------------------------------------------------------------- commit 4ab57024548c32a64baf069c8d78ffba073750e4 Author: Peter Wortmann Date: Thu Jan 8 22:19:56 2015 +0100 Dwarf generation fixed pt 2 - Don't bracket HsTick expression uneccessarily - Generate debug information in UTF8 - Reduce amount of information generated - we do not currently need block information, for example. Special thanks to slyfox for the reports! (cherry picked from commit 36df0988444bdf0555a842ce94f4d597b741923d) >--------------------------------------------------------------- 4ab57024548c32a64baf069c8d78ffba073750e4 compiler/hsSyn/HsExpr.hs | 2 +- compiler/nativeGen/Dwarf.hs | 5 ++++- compiler/nativeGen/Dwarf/Constants.hs | 3 ++- compiler/nativeGen/Dwarf/Types.hs | 35 ++++++++++++++++++++++------------- 4 files changed, 29 insertions(+), 16 deletions(-) diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs index 384222b..795837c 100644 --- a/compiler/hsSyn/HsExpr.hs +++ b/compiler/hsSyn/HsExpr.hs @@ -665,7 +665,7 @@ ppr_expr (HsStatic e) ppr_expr (HsTick tickish exp) = pprTicks (ppr exp) $ - ppr tickish <+> ppr exp + ppr tickish <+> ppr_lexpr exp ppr_expr (HsBinTick tickIdTrue tickIdFalse exp) = pprTicks (ppr exp) $ hcat [ptext (sLit "bintick<"), diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs index 70fca4f..d7c2f61 100644 --- a/compiler/nativeGen/Dwarf.hs +++ b/compiler/nativeGen/Dwarf.hs @@ -33,7 +33,10 @@ dwarfGen :: DynFlags -> ModLocation -> UniqSupply -> [DebugBlock] dwarfGen df modLoc us blocks = do -- Convert debug data structures to DWARF info records - let procs = debugSplitProcs blocks + -- We strip out block information, as it is not currently useful for + -- anything. In future we might want to only do this for -g1. + let procs = map stripBlocks $ debugSplitProcs blocks + stripBlocks dbg = dbg { dblBlocks = [] } compPath <- getCurrentDirectory let dwarfUnit = DwarfCompileUnit { dwChildren = map (procToDwarf df) procs diff --git a/compiler/nativeGen/Dwarf/Constants.hs b/compiler/nativeGen/Dwarf/Constants.hs index a5bbeac..2cd54a7 100644 --- a/compiler/nativeGen/Dwarf/Constants.hs +++ b/compiler/nativeGen/Dwarf/Constants.hs @@ -41,7 +41,7 @@ dW_TAG_arg_variable = 257 -- | Dwarf attributes dW_AT_name, dW_AT_stmt_list, dW_AT_low_pc, dW_AT_high_pc, dW_AT_language, dW_AT_comp_dir, dW_AT_producer, dW_AT_external, dW_AT_frame_base, - dW_AT_MIPS_linkage_name :: Word + dW_AT_use_UTF8, dW_AT_MIPS_linkage_name :: Word dW_AT_name = 0x03 dW_AT_stmt_list = 0x10 dW_AT_low_pc = 0x11 @@ -51,6 +51,7 @@ dW_AT_comp_dir = 0x1b dW_AT_producer = 0x25 dW_AT_external = 0x3f dW_AT_frame_base = 0x40 +dW_AT_use_UTF8 = 0x53 dW_AT_MIPS_linkage_name = 0x2007 -- | Abbrev declaration diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index 47e0bd1..520b5ae 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -21,6 +21,7 @@ module Dwarf.Types import Debug import CLabel import CmmExpr ( GlobalReg(..) ) +import Encoding import FastString import Outputable import Platform @@ -79,6 +80,7 @@ pprAbbrevDecls haveDebugLine = , (dW_AT_producer, dW_FORM_string) , (dW_AT_language, dW_FORM_data4) , (dW_AT_comp_dir, dW_FORM_string) + , (dW_AT_use_UTF8, dW_FORM_flag) ] ++ (if haveDebugLine then [ (dW_AT_stmt_list, dW_FORM_data4) ] @@ -115,6 +117,7 @@ pprDwarfInfoOpen haveSrc (DwarfCompileUnit _ name producer compDir lineLbl) = $$ pprString producer $$ pprData4 dW_LANG_Haskell $$ pprString compDir + $$ pprFlag True -- use UTF8 $$ if haveSrc then pprData4' (sectionOffset lineLbl dwarfLineLabel) else empty @@ -406,19 +409,25 @@ pprString' str = ptext (sLit "\t.asciz \"") <> str <> char '"' -- | Generate a string constant. We take care to escape the string. pprString :: String -> SDoc -pprString = pprString' . hcat . map escape - where escape '\\' = ptext (sLit "\\\\") - escape '\"' = ptext (sLit "\\\"") - escape '\n' = ptext (sLit "\\n") - escape c | isAscii c && isPrint c && c /= '?' - -- escaping '?' prevents trigraph warnings - = char c - | otherwise - = let ch = ord c - in char '\\' <> - char (intToDigit (ch `div` 64)) <> - char (intToDigit ((ch `div` 8) `mod` 8)) <> - char (intToDigit (ch `mod` 8)) +pprString str + = pprString' $ hcat $ map escapeChar $ + if utf8EncodedLength str == length str + then str + else map (chr . fromIntegral) $ bytesFS $ mkFastString str + +-- | Escape a single non-unicode character +escapeChar :: Char -> SDoc +escapeChar '\\' = ptext (sLit "\\\\") +escapeChar '\"' = ptext (sLit "\\\"") +escapeChar '\n' = ptext (sLit "\\n") +escapeChar c + | isAscii c && isPrint c && c /= '?' -- prevents trigraph warnings + = char c + | otherwise + = char '\\' <> char (intToDigit (ch `div` 64)) <> + char (intToDigit ((ch `div` 8) `mod` 8)) <> + char (intToDigit (ch `mod` 8)) + where ch = ord c -- | Generate an offset into another section. This is tricky because -- this is handled differently depending on platform: Mac Os expects From git at git.haskell.org Mon Jan 19 14:01:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 14:01:58 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Make AutoDeriveTypeable work for associated datatypes (fix #9999) (5541b6c) Message-ID: <20150119140158.024863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/5541b6c34161278180c45d378941d53ed20d9a5a/ghc >--------------------------------------------------------------- commit 5541b6c34161278180c45d378941d53ed20d9a5a Author: Jose Pedro Magalhaes Date: Mon Jan 19 13:36:03 2015 +0000 Make AutoDeriveTypeable work for associated datatypes (fix #9999) (cherry picked from commit d839493991e508160d416311ba47b7a7e2d62aae) >--------------------------------------------------------------- 5541b6c34161278180c45d378941d53ed20d9a5a compiler/typecheck/TcDeriv.hs | 13 +++++++++---- testsuite/tests/typecheck/should_compile/T9999.hs | 13 +++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 23 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 8b7af86..c5f3c25 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -561,11 +561,16 @@ deriveAutoTypeable auto_typeable done_specs tycl_decls do_one cls (L _ decl) = do { tc <- tcLookupTyCon (tcdName decl) - ; if (isTypeSynonymTyCon tc || isTypeFamilyTyCon tc + -- Traverse into class declarations to check if they have ATs (#9999) + ; ats <- if isClassDecl decl + then concatMapM (do_one cls) (map (fmap FamDecl) (tcdATs decl)) + else return [] + ; rest <- if (isTypeSynonymTyCon tc || isTypeFamilyTyCon tc || tyConName tc `elemNameSet` done_tcs) - -- Do not derive Typeable for type synonyms or type families - then return [] - else mkPolyKindedTypeableEqn cls tc } + -- Do not derive Typeable for type synonyms or type families + then return [] + else mkPolyKindedTypeableEqn cls tc + ; return (ats ++ rest) } ------------------------------------------------------------------ deriveTyDecl :: LTyClDecl Name -> TcM [EarlyDerivSpec] diff --git a/testsuite/tests/typecheck/should_compile/T9999.hs b/testsuite/tests/typecheck/should_compile/T9999.hs new file mode 100644 index 0000000..656e913 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9999.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE AutoDeriveTypeable, PolyKinds, TypeFamilies, StandaloneDeriving #-} + +module T9999 where + +import Data.Typeable + +data family F a + +class C a where + data F1 a + type F2 a + +main = typeRep (Proxy :: Proxy F) == typeRep (Proxy :: Proxy F1) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 9d915eb..df07a3e 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -438,3 +438,4 @@ test('T7643', normal, compile, ['']) test('T9834', normal, compile, ['']) test('T9892', normal, compile, ['']) test('T9971', normal, compile, ['']) +test('T9999', normal, compile, ['']) From git at git.haskell.org Mon Jan 19 14:02:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 14:02:00 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Trac #9878: Have StaticPointers support dynamic loading. (cd66ec3) Message-ID: <20150119140200.A1DBD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/cd66ec3620cbf56fb856712633b045991adf28f0/ghc >--------------------------------------------------------------- commit cd66ec3620cbf56fb856712633b045991adf28f0 Author: Alexander Vershilov Date: Mon Jan 12 05:29:18 2015 -0600 Trac #9878: Have StaticPointers support dynamic loading. Summary: A mutex is used to protect the SPT. unsafeLookupStaticPtr and staticPtrKeys in GHC.StaticPtr are made monadic. SPT entries are removed in a destructor function of modules. Authored-by: Facundo Dom?nguez Authored-by: Alexander Vershilov Test Plan: ./validate Reviewers: austin, simonpj, hvr Subscribers: carter, thomie, qnikst, mboes Differential Revision: https://phabricator.haskell.org/D587 GHC Trac Issues: #9878 (cherry picked from commit 7637810a93441d29bc84bbeeeced0615bbb9d9e4) >--------------------------------------------------------------- cd66ec3620cbf56fb856712633b045991adf28f0 compiler/deSugar/StaticPtrTable.hs | 23 ++++++++ includes/rts/StaticPtrTable.h | 8 +++ libraries/base/GHC/StaticPtr.hs | 33 +++++------- rts/Linker.c | 1 + rts/StaticPtrTable.c | 61 +++++++++++++++++++--- .../tests/codeGen/should_run/CgStaticPointers.hs | 11 ++-- testsuite/tests/rts/GcStaticPointers.hs | 2 +- testsuite/tests/rts/ListStaticPointers.hs | 10 ++-- 8 files changed, 113 insertions(+), 36 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cd66ec3620cbf56fb856712633b045991adf28f0 From git at git.haskell.org Mon Jan 19 14:03:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 14:03:01 +0000 (UTC) Subject: [commit: ghc] master: Update directory submodule to latest 1.2.2 snapshot (8ce3871) Message-ID: <20150119140301.97DF43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8ce3871304d1f49e4f6fb0f3d9221d42f537848f/ghc >--------------------------------------------------------------- commit 8ce3871304d1f49e4f6fb0f3d9221d42f537848f Author: Herbert Valerio Riedel Date: Mon Jan 19 14:39:57 2015 +0100 Update directory submodule to latest 1.2.2 snapshot >--------------------------------------------------------------- 8ce3871304d1f49e4f6fb0f3d9221d42f537848f libraries/directory | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/directory b/libraries/directory index e22771f..b78c422 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit e22771f4e9fbd30b2ed4af75cf4b19b9e4e94c7c +Subproject commit b78c422d9433141334d072a85f530dbacdadd1f7 From git at git.haskell.org Mon Jan 19 14:03:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 14:03:49 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update directory submodule to latest 1.2.2 snapshot (37c6934) Message-ID: <20150119140349.C052E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/37c6934f12bd6fa9721e3522be46952f52580dca/ghc >--------------------------------------------------------------- commit 37c6934f12bd6fa9721e3522be46952f52580dca Author: Herbert Valerio Riedel Date: Mon Jan 19 14:39:57 2015 +0100 Update directory submodule to latest 1.2.2 snapshot (cherry picked from commit 8ce3871304d1f49e4f6fb0f3d9221d42f537848f) >--------------------------------------------------------------- 37c6934f12bd6fa9721e3522be46952f52580dca libraries/directory | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/directory b/libraries/directory index c43340d..b78c422 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit c43340dc29874c80570a7295d5d4c93756b4bc03 +Subproject commit b78c422d9433141334d072a85f530dbacdadd1f7 From git at git.haskell.org Mon Jan 19 14:11:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 14:11:01 +0000 (UTC) Subject: [commit: ghc] master: Add missing test from previous commit (55199a97) (960e3c9) Message-ID: <20150119141101.191903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/960e3c92eace7f9b584cfc6f6eb69a37cd3d88f8/ghc >--------------------------------------------------------------- commit 960e3c92eace7f9b584cfc6f6eb69a37cd3d88f8 Author: Austin Seipp Date: Mon Jan 19 08:10:58 2015 -0600 Add missing test from previous commit (55199a97) Signed-off-by: Austin Seipp >--------------------------------------------------------------- 960e3c92eace7f9b584cfc6f6eb69a37cd3d88f8 testsuite/tests/perf/compiler/T9961.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/testsuite/tests/perf/compiler/T9961.hs b/testsuite/tests/perf/compiler/T9961.hs new file mode 100644 index 0000000..888ae90 --- /dev/null +++ b/testsuite/tests/perf/compiler/T9961.hs @@ -0,0 +1,7 @@ + +module Lexer (alex_table) where + +import Data.Array + +alex_table :: Array Int Int +alex_table = listArray (0,1109) [-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,18,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,20,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,- 1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,22,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,25,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,28,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1 ,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1, -1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1] From git at git.haskell.org Mon Jan 19 14:13:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 14:13:50 +0000 (UTC) Subject: [commit: ghc] master: API Annotations documentation update, parsing issue, add example test (851ed72) Message-ID: <20150119141350.8F5C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/851ed7211fb18fea938be84c99b6389f6762b30d/ghc >--------------------------------------------------------------- commit 851ed7211fb18fea938be84c99b6389f6762b30d Author: Alan Zimmerman Date: Mon Jan 19 08:15:18 2015 -0600 API Annotations documentation update, parsing issue, add example test Summary: Add a reference note to each AnnKeywordId haddock comment so GHC developers will have an idea why they are there. Add a new test to ghc-api/annotations to serve as a template for other GHC developers when they need to update the parser. It provides output which checks that each SrcSpan that an annotation is attached to actually appears in the `ParsedSource`, and lists the individual annotations. The idea is that a developer writes a version of this which parses a sample file using whatever syntax is changed in Parser.y, and can then check that all the annotations come through. Depends on D538 Test Plan: ./validate Reviewers: simonpj, hvr, austin Reviewed By: austin Subscribers: thomie, jstolarek Differential Revision: https://phabricator.haskell.org/D620 >--------------------------------------------------------------- 851ed7211fb18fea938be84c99b6389f6762b30d compiler/basicTypes/BasicTypes.hs | 30 ++++---- compiler/basicTypes/DataCon.hs | 2 + compiler/basicTypes/RdrName.hs | 2 + compiler/hsSyn/HsBinds.hs | 28 +++++++ compiler/hsSyn/HsDecls.hs | 51 +++++++++++- compiler/hsSyn/HsExpr.hs | 90 ++++++++++++++++++++++ compiler/hsSyn/HsImpExp.hs | 17 +++- compiler/hsSyn/HsLit.hs | 4 +- compiler/hsSyn/HsPat.hs | 24 ++++++ compiler/hsSyn/HsSyn.hs | 11 ++- compiler/hsSyn/HsTypes.hs | 60 ++++++++++++++- compiler/parser/ApiAnnotation.hs | 16 ++-- compiler/parser/Lexer.x | 14 ++-- compiler/parser/Parser.y | 5 +- compiler/prelude/ForeignCall.hs | 2 + compiler/types/Class.hs | 2 + testsuite/tests/ghc-api/annotations/.gitignore | 1 + testsuite/tests/ghc-api/annotations/Makefile | 6 +- testsuite/tests/ghc-api/annotations/all.T | 1 + .../annotations/{parseTree.hs => exampleTest.hs} | 24 ++++-- .../{parseTree.stdout => exampleTest.stdout} | 20 ++--- 21 files changed, 352 insertions(+), 58 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 851ed7211fb18fea938be84c99b6389f6762b30d From git at git.haskell.org Mon Jan 19 14:21:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 14:21:02 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: #9957: fix docs for unticked promoted constructor warning (4baf8d2) Message-ID: <20150119142102.6E6FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/4baf8d2aa09bb72ff8ba32335ddf235f5a644717/ghc >--------------------------------------------------------------- commit 4baf8d2aa09bb72ff8ba32335ddf235f5a644717 Author: Austin Seipp Date: Mon Jan 19 08:22:04 2015 -0600 #9957: fix docs for unticked promoted constructor warning Signed-off-by: Austin Seipp >--------------------------------------------------------------- 4baf8d2aa09bb72ff8ba32335ddf235f5a644717 docs/users_guide/7.10.1-notes.xml | 20 ++++++++++++++++++++ docs/users_guide/using.xml | 2 +- 2 files changed, 21 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 318e77e..9ef8d28 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -199,6 +199,26 @@ + A new warning flag, + has been added. This flag causes GHC to warn when you use a promoted constructor without using a "tick" preceding its name. + + For example: + + +data Nat = Succ Nat | Zero + +data Vec n s where + Nil :: Vec Zero a + Cons :: a -> Vec n a -> Vec (Succ n) a + + Will raise two warnings because Zero + and Succ are not written as 'Zero and + 'Succ. + + This warning is enabled by default in -Wall mode. + + + Added the option . This dumps out a .th.hs file of all Template Haskell diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 83c69ce..c1a5196 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -1815,7 +1815,7 @@ data Vec n s where and Succ are not written as 'Zero and 'Succ. - This warning is off by default. + This warning is enabled by default in -Wall mode. From git at git.haskell.org Mon Jan 19 14:22:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 14:22:26 +0000 (UTC) Subject: [commit: ghc] master: Doc fix (follow up to #9957) (cb65bdb) Message-ID: <20150119142226.985DD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb65bdbca83f43d72dd2fc6ecd1897e734454d33/ghc >--------------------------------------------------------------- commit cb65bdbca83f43d72dd2fc6ecd1897e734454d33 Author: Austin Seipp Date: Mon Jan 19 08:23:51 2015 -0600 Doc fix (follow up to #9957) Signed-off-by: Austin Seipp >--------------------------------------------------------------- cb65bdbca83f43d72dd2fc6ecd1897e734454d33 docs/users_guide/using.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 0504fb5..1940e7a 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -1862,7 +1862,7 @@ data Vec n s where and Succ are not written as 'Zero and 'Succ. - This warning is off by default. + This warning is is enabled by default in -Wall mode. From git at git.haskell.org Mon Jan 19 15:32:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 15:32:46 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: We track branch 1.22 for GHC 7.10.x (a01de8b) Message-ID: <20150119153246.8DC693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a01de8b0d9c3ec32f00e2b1d2fb67b1da6a6ad65/ghc >--------------------------------------------------------------- commit a01de8b0d9c3ec32f00e2b1d2fb67b1da6a6ad65 Author: Herbert Valerio Riedel Date: Mon Jan 19 16:33:35 2015 +0100 We track branch 1.22 for GHC 7.10.x >--------------------------------------------------------------- a01de8b0d9c3ec32f00e2b1d2fb67b1da6a6ad65 .gitmodules | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitmodules b/.gitmodules index 662f6d6..75c508d 100644 --- a/.gitmodules +++ b/.gitmodules @@ -10,6 +10,7 @@ path = libraries/Cabal url = ../packages/Cabal.git ignore = untracked + branch = 1.22 [submodule "libraries/containers"] path = libraries/containers url = ../packages/containers.git From git at git.haskell.org Mon Jan 19 15:56:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 15:56:05 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Cabal submodule to latest 1.22.1.0 snapshot (fffc60b) Message-ID: <20150119155605.62C383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/fffc60bafeb9ed04ed06529cc9cc3014d7edb836/ghc >--------------------------------------------------------------- commit fffc60bafeb9ed04ed06529cc9cc3014d7edb836 Author: Herbert Valerio Riedel Date: Mon Jan 19 16:57:23 2015 +0100 Update Cabal submodule to latest 1.22.1.0 snapshot >--------------------------------------------------------------- fffc60bafeb9ed04ed06529cc9cc3014d7edb836 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 52e80d2..66dade3 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 52e80d21b3cf37bea2ead237fe9c97ccb816e779 +Subproject commit 66dade371e720efd57b06424cfdf68454e6aba77 From git at git.haskell.org Mon Jan 19 16:44:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 16:44:26 +0000 (UTC) Subject: [commit: ghc] master: Tidy up fix to Trac #9999 (d3c08ca) Message-ID: <20150119164426.6A3153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d3c08ca0c4f83aaed6bd25785a03c0fb52438ba6/ghc >--------------------------------------------------------------- commit d3c08ca0c4f83aaed6bd25785a03c0fb52438ba6 Author: Simon Peyton Jones Date: Mon Jan 19 16:45:31 2015 +0000 Tidy up fix to Trac #9999 Minor refactoring only >--------------------------------------------------------------- d3c08ca0c4f83aaed6bd25785a03c0fb52438ba6 compiler/typecheck/TcDeriv.hs | 14 ++++++-------- 1 file changed, 6 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index ae95f33..3d980e2 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -560,17 +560,15 @@ deriveAutoTypeable auto_typeable done_specs tycl_decls -- omitted because the user had manually requested an instance do_one cls (L _ decl) + | isClassDecl decl -- Traverse into class declarations to check if they have ATs (#9999) + = concatMapM (do_one cls) (map (fmap FamDecl) (tcdATs decl)) + | otherwise = do { tc <- tcLookupTyCon (tcdName decl) - -- Traverse into class declarations to check if they have ATs (#9999) - ; ats <- if isClassDecl decl - then concatMapM (do_one cls) (map (fmap FamDecl) (tcdATs decl)) - else return [] - ; rest <- if (isTypeSynonymTyCon tc || isTypeFamilyTyCon tc + ; if (isTypeSynonymTyCon tc || isTypeFamilyTyCon tc || tyConName tc `elemNameSet` done_tcs) -- Do not derive Typeable for type synonyms or type families - then return [] - else mkPolyKindedTypeableEqn cls tc - ; return (ats ++ rest) } + then return [] + else mkPolyKindedTypeableEqn cls tc } ------------------------------------------------------------------ deriveTyDecl :: LTyClDecl Name -> TcM [EarlyDerivSpec] From git at git.haskell.org Mon Jan 19 18:48:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 18:48:29 +0000 (UTC) Subject: [commit: ghc] master: Respect package visibility when deciding wired in packages. (1f15951) Message-ID: <20150119184829.5DE2F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1f1595195443700b7c2708fa903969fa2f0a927b/ghc >--------------------------------------------------------------- commit 1f1595195443700b7c2708fa903969fa2f0a927b Author: Edward Z. Yang Date: Mon Jan 19 10:23:46 2015 -0800 Respect package visibility when deciding wired in packages. Summary: Previously, we would consider ALL versions of a wired-in package, no matter if they were exposed or not, and pick the latest version. This patch is a minor refinement on the behavior: now we try to pick the wired in package from just the list of exposed packages, and if there are no candidates fall back on the full list. This means that if you do: -hide-all-packages -package wired-in-OLD-VERSION it will actually work by default (whereas previously you needed to *explicitly* -ignore-package the newer version). This is especially useful for the 'ghc' package. Fixes #9955. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D603 GHC Trac Issues: #9955 >--------------------------------------------------------------- 1f1595195443700b7c2708fa903969fa2f0a927b compiler/main/Packages.hs | 84 ++++++++++++++++++++++++++--------------------- 1 file changed, 47 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1f1595195443700b7c2708fa903969fa2f0a927b From git at git.haskell.org Mon Jan 19 19:16:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 19:16:47 +0000 (UTC) Subject: [commit: ghc] master: Upgrade Cabal submodule to latest HEAD, change to package key calculation. (c77eecd) Message-ID: <20150119191647.586EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c77eecdc35e2fb4664765264a72ed3f29e50c047/ghc >--------------------------------------------------------------- commit c77eecdc35e2fb4664765264a72ed3f29e50c047 Author: Edward Z. Yang Date: Fri Jan 9 16:53:22 2015 -0800 Upgrade Cabal submodule to latest HEAD, change to package key calculation. Summary: One notable change is that the package key calculation algorithm in Cabal has changed (from an undocumented format based on Show instances to a fully specified format), so you will need to do a full rebuild. I'd greatly prefer if this could be merged to 7.10. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: GHC Trac Issues: >--------------------------------------------------------------- c77eecdc35e2fb4664765264a72ed3f29e50c047 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index e4ea51c..18c17cb 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit e4ea51c3156c27b7dec40cb2733b8bfe37bca6a1 +Subproject commit 18c17cbad1e36275ca878cce89539cf4ffa1a6ff From git at git.haskell.org Mon Jan 19 22:07:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 22:07:38 +0000 (UTC) Subject: [commit: ghc] master: Expose source locations via Implicit Parameters of type GHC.Location.Location (c024af1) Message-ID: <20150119220738.C57B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c024af131b9e2538486eb605ba8af6a8d10fe76d/ghc >--------------------------------------------------------------- commit c024af131b9e2538486eb605ba8af6a8d10fe76d Author: Eric Seidel Date: Mon Jan 19 16:08:32 2015 -0600 Expose source locations via Implicit Parameters of type GHC.Location.Location Summary: IPs with this type will always be solved for the current source location. If another IP of the same type is in scope, the two locations will be appended, creating a call-stack. The Location type is kept abstract so users cannot create them, but a Location can be turned into a list of SrcLocs, which correspond to individual locations in a program. Each SrcLoc contains a package/module/file name and start/end lines and columns. The only thing missing from the SrcLoc in my opinion is the name of the top-level definition it inhabits. I suspect that would also be useful, but it's not clear to me how to extract the current top-level binder from within the constraint solver. (Surely I'm just missing something here?) I made the (perhaps controversial) decision to have GHC completely ignore the names of Location IPs, meaning that in the following code: bar :: (?myloc :: Location) => String bar = foo foo :: (?loc :: Location) => String foo = show ?loc if I call `bar`, the resulting call-stack will include locations for 1. the use of `?loc` inside `foo`, 2. `foo`s call-site inside `bar`, and 3. `bar`s call-site, wherever that may be. This makes Location IPs very special indeed, and I'm happy to change it if the dissonance is too great. I've also left out any changes to base to make use of Location IPs, since there were some concerns about a snowball effect. I think it would be reasonable to mark this as an experimental feature for now (it is!), and defer using it in base until we have more experience with it. It is, after all, quite easy to define your own version of `error`, `undefined`, etc. that use Location IPs. Test Plan: validate, new test-case is testsuite/tests/typecheck/should_run/IPLocation.hs Reviewers: austin, hvr, simonpj Reviewed By: simonpj Subscribers: simonmar, rodlogic, carter, thomie Differential Revision: https://phabricator.haskell.org/D578 GHC Trac Issues: #9049 >--------------------------------------------------------------- c024af131b9e2538486eb605ba8af6a8d10fe76d compiler/deSugar/DsBinds.hs | 64 +++++++- compiler/prelude/PrelNames.hs | 26 +++ compiler/typecheck/Inst.hs | 2 - compiler/typecheck/TcBinds.hs | 7 +- compiler/typecheck/TcEvidence.hs | 174 ++++++++++++++++++++- compiler/typecheck/TcExpr.hs | 6 +- compiler/typecheck/TcHsSyn.hs | 7 + compiler/typecheck/TcInteract.hs | 46 +++++- docs/users_guide/7.12.1-notes.xml | 43 +++++ docs/users_guide/glasgow_exts.xml | 50 ++++++ libraries/base/GHC/SrcLoc.hs | 33 ++++ libraries/base/GHC/Stack.hsc | 57 ++++++- libraries/base/base.cabal | 1 + testsuite/tests/typecheck/should_run/IPLocation.hs | 44 ++++++ .../tests/typecheck/should_run/IPLocation.stdout | 28 ++++ testsuite/tests/typecheck/should_run/all.T | 1 + 16 files changed, 568 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c024af131b9e2538486eb605ba8af6a8d10fe76d From git at git.haskell.org Mon Jan 19 22:25:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 22:25:49 +0000 (UTC) Subject: [commit: ghc] master: CMM: add a mechanism to import C .data labels (d82f592) Message-ID: <20150119222549.72B353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d82f592522eb8e063276a8a8c87ab93e18353c6b/ghc >--------------------------------------------------------------- commit d82f592522eb8e063276a8a8c87ab93e18353c6b Author: Sergei Trofimovich Date: Mon Jan 19 16:27:06 2015 -0600 CMM: add a mechanism to import C .data labels Summary: This introduces new .cmm syntax for import: 'import' 'CLOSURE' ; Currently cmm syntax allows importing only function labels: import pthread_mutex_lock; but sometimes ghc needs to import global gariables or haskell closures: import ghczmprim_GHCziTypes_True_closure; import base_ControlziExceptionziBase_nestedAtomically_closure; import ghczmprim_GHCziTypes_False_closure; import sm_mutex; It breaks on ia64 where there is a difference in pointers to data and pointer to functions. Patch fixes threaded runtime on ia64 where dereference of 'sm_mutex' from CMM led to incurrect location. Exact breakage machanics are the same as in e18525fae273f4c1ad8d6cbe1dea4fc074cac721 Merge into the 7.10 branch Signed-off-by: Sergei Trofimovich Test Plan: passes ./validate, makes ghci work on ghc-7.8.4 Reviewers: simonmar, simonpj, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D622 >--------------------------------------------------------------- d82f592522eb8e063276a8a8c87ab93e18353c6b compiler/cmm/CmmParse.y | 4 ++++ rts/Exception.cmm | 2 +- rts/PrimOps.cmm | 6 +++--- 3 files changed, 8 insertions(+), 4 deletions(-) diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 6b51e51..fd9489b 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -575,6 +575,10 @@ importName : NAME { ($1, mkForeignLabel $1 Nothing ForeignLabelInExternalPackage IsFunction) } + -- as previous 'NAME', but 'IsData' + | 'CLOSURE' NAME + { ($2, mkForeignLabel $2 Nothing ForeignLabelInExternalPackage IsData) } + -- A label imported with an explicit packageId. | STRING NAME { ($2, mkCmmCodeLabel (fsToPackageKey (mkFastString $1)) $2) } diff --git a/rts/Exception.cmm b/rts/Exception.cmm index 5007ef3..8d19c14 100644 --- a/rts/Exception.cmm +++ b/rts/Exception.cmm @@ -13,7 +13,7 @@ #include "Cmm.h" #include "RaiseAsync.h" -import ghczmprim_GHCziTypes_True_closure; +import CLOSURE ghczmprim_GHCziTypes_True_closure; /* ----------------------------------------------------------------------------- Exception Primitives diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index 3e8612c..2e6ca46 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -28,12 +28,12 @@ import pthread_mutex_lock; import pthread_mutex_unlock; #endif -import base_ControlziExceptionziBase_nestedAtomically_closure; +import CLOSURE base_ControlziExceptionziBase_nestedAtomically_closure; import EnterCriticalSection; import LeaveCriticalSection; -import ghczmprim_GHCziTypes_False_closure; +import CLOSURE ghczmprim_GHCziTypes_False_closure; #if defined(USE_MINIINTERPRETER) || !defined(mingw32_HOST_OS) -import sm_mutex; +import CLOSURE sm_mutex; #endif /*----------------------------------------------------------------------------- From git at git.haskell.org Mon Jan 19 22:26:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 22:26:26 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: CMM: add a mechanism to import C .data labels (a993712) Message-ID: <20150119222626.1D1CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a993712d16691829c3bf6d1ea552112abb2d4f9f/ghc >--------------------------------------------------------------- commit a993712d16691829c3bf6d1ea552112abb2d4f9f Author: Sergei Trofimovich Date: Mon Jan 19 16:27:06 2015 -0600 CMM: add a mechanism to import C .data labels Summary: This introduces new .cmm syntax for import: 'import' 'CLOSURE' ; Currently cmm syntax allows importing only function labels: import pthread_mutex_lock; but sometimes ghc needs to import global gariables or haskell closures: import ghczmprim_GHCziTypes_True_closure; import base_ControlziExceptionziBase_nestedAtomically_closure; import ghczmprim_GHCziTypes_False_closure; import sm_mutex; It breaks on ia64 where there is a difference in pointers to data and pointer to functions. Patch fixes threaded runtime on ia64 where dereference of 'sm_mutex' from CMM led to incurrect location. Exact breakage machanics are the same as in e18525fae273f4c1ad8d6cbe1dea4fc074cac721 Merge into the 7.10 branch Signed-off-by: Sergei Trofimovich Test Plan: passes ./validate, makes ghci work on ghc-7.8.4 Reviewers: simonmar, simonpj, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D622 (cherry picked from commit d82f592522eb8e063276a8a8c87ab93e18353c6b) >--------------------------------------------------------------- a993712d16691829c3bf6d1ea552112abb2d4f9f compiler/cmm/CmmParse.y | 4 ++++ rts/Exception.cmm | 2 +- rts/PrimOps.cmm | 6 +++--- 3 files changed, 8 insertions(+), 4 deletions(-) diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 6b51e51..fd9489b 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -575,6 +575,10 @@ importName : NAME { ($1, mkForeignLabel $1 Nothing ForeignLabelInExternalPackage IsFunction) } + -- as previous 'NAME', but 'IsData' + | 'CLOSURE' NAME + { ($2, mkForeignLabel $2 Nothing ForeignLabelInExternalPackage IsData) } + -- A label imported with an explicit packageId. | STRING NAME { ($2, mkCmmCodeLabel (fsToPackageKey (mkFastString $1)) $2) } diff --git a/rts/Exception.cmm b/rts/Exception.cmm index 5007ef3..8d19c14 100644 --- a/rts/Exception.cmm +++ b/rts/Exception.cmm @@ -13,7 +13,7 @@ #include "Cmm.h" #include "RaiseAsync.h" -import ghczmprim_GHCziTypes_True_closure; +import CLOSURE ghczmprim_GHCziTypes_True_closure; /* ----------------------------------------------------------------------------- Exception Primitives diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index 3e8612c..2e6ca46 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -28,12 +28,12 @@ import pthread_mutex_lock; import pthread_mutex_unlock; #endif -import base_ControlziExceptionziBase_nestedAtomically_closure; +import CLOSURE base_ControlziExceptionziBase_nestedAtomically_closure; import EnterCriticalSection; import LeaveCriticalSection; -import ghczmprim_GHCziTypes_False_closure; +import CLOSURE ghczmprim_GHCziTypes_False_closure; #if defined(USE_MINIINTERPRETER) || !defined(mingw32_HOST_OS) -import sm_mutex; +import CLOSURE sm_mutex; #endif /*----------------------------------------------------------------------------- From git at git.haskell.org Mon Jan 19 23:16:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 23:16:30 +0000 (UTC) Subject: [commit: ghc] branch 'wip/llvm-3.6' created Message-ID: <20150119231630.405C23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/llvm-3.6 Referencing: bde6e36379ee8cf7238dcb6bd23d09152844ac34 From git at git.haskell.org Mon Jan 19 23:16:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 23:16:32 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: RFC: Move to LLVM 3.6 (6157817) Message-ID: <20150119231632.F11543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/6157817776a0cb493b250a358b8a636cf0f8283a/ghc >--------------------------------------------------------------- commit 6157817776a0cb493b250a358b8a636cf0f8283a Author: Ben Gamari Date: Fri Nov 28 11:14:17 2014 -0500 RFC: Move to LLVM 3.6 Summary: Here we rework the LLVM backend to support LLVM 3.6 exclusively and refactor TNTC to take advantage of LLVM's new and improved prefix data support.. Test Plan: Validate, look at emitted code Reviewers: dterei, austin, scpmw Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D530 >--------------------------------------------------------------- 6157817776a0cb493b250a358b8a636cf0f8283a compiler/llvmGen/Llvm/PpLlvm.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index 050d200..de76766 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -77,12 +77,12 @@ ppLlvmGlobal (LMGlobal var@(LMGlobalVar _ _ link x a c) dat) = Nothing -> ppr (pLower $ getVarType var) -- Position of linkage is different for aliases. - const_link = case c of - Global -> ppr link <+> text "global" - Constant -> ppr link <+> text "constant" - Alias -> ppr link <+> text "alias" + const = case c of + Global -> text "global" + Constant -> text "constant" + Alias -> text "alias" - in ppAssignment var $ const_link <+> rhs <> sect <> align + in ppAssignment var $ ppr link <+> const <+> rhs <> sect <> align $+$ newLine ppLlvmGlobal (LMGlobal var val) = sdocWithDynFlags $ \dflags -> From git at git.haskell.org Mon Jan 19 23:16:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 23:16:35 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: llvmGen: metadata no longer marked with `metadata` keyword (bde6e36) Message-ID: <20150119231635.9EF833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/bde6e36379ee8cf7238dcb6bd23d09152844ac34/ghc >--------------------------------------------------------------- commit bde6e36379ee8cf7238dcb6bd23d09152844ac34 Author: Ben Gamari Date: Sun Jan 4 18:25:24 2015 -0500 llvmGen: metadata no longer marked with `metadata` keyword As of LLVM 3.6 >--------------------------------------------------------------- bde6e36379ee8cf7238dcb6bd23d09152844ac34 compiler/llvmGen/Llvm/MetaData.hs | 14 +++++++------- compiler/llvmGen/Llvm/PpLlvm.hs | 12 ++++++++---- 2 files changed, 15 insertions(+), 11 deletions(-) diff --git a/compiler/llvmGen/Llvm/MetaData.hs b/compiler/llvmGen/Llvm/MetaData.hs index 36efcd7..e1e63c9 100644 --- a/compiler/llvmGen/Llvm/MetaData.hs +++ b/compiler/llvmGen/Llvm/MetaData.hs @@ -20,12 +20,12 @@ import Outputable -- information. They consist of metadata strings, metadata nodes, regular -- LLVM values (both literals and references to global variables) and -- metadata expressions (i.e., recursive data type). Some examples: --- !{ metadata !"hello", metadata !0, i32 0 } --- !{ metadata !1, metadata !{ i32 0 } } +-- !{ !"hello", !0, i32 0 } +-- !{ !1, !{ i32 0 } } -- -- * Metadata nodes -- global metadata variables that attach a metadata -- expression to a number. For example: --- !0 = metadata !{ [] !} +-- !0 = !{ [] !} -- -- * Named metadata -- global metadata variables that attach a metadata nodes -- to a name. Used ONLY to communicated module level information to LLVM @@ -39,7 +39,7 @@ import Outputable -- * Attach to instructions -- metadata can be attached to LLVM instructions -- using a specific reference as follows: -- %l = load i32* @glob, !nontemporal !10 --- %m = load i32* @glob, !nontemporal !{ i32 0, metadata !{ i32 0 } } +-- %m = load i32* @glob, !nontemporal !{ i32 0, !{ i32 0 } } -- Only metadata nodes or expressions can be attached, named metadata cannot. -- Refer to LLVM documentation for which instructions take metadata and its -- meaning. @@ -63,10 +63,10 @@ data MetaExpr = MetaStr LMString deriving (Eq) instance Outputable MetaExpr where - ppr (MetaStr s ) = text "metadata !\"" <> ftext s <> char '"' - ppr (MetaNode n ) = text "metadata !" <> int n + ppr (MetaStr s ) = text "!\"" <> ftext s <> char '"' + ppr (MetaNode n ) = text "!" <> int n ppr (MetaVar v ) = ppr v - ppr (MetaStruct es) = text "metadata !{ " <> ppCommaJoin es <> char '}' + ppr (MetaStruct es) = text "!{ " <> ppCommaJoin es <> char '}' -- | Associates some metadata with a specific label for attaching to an -- instruction. diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index de76766..0b3deac 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -117,11 +117,11 @@ ppLlvmMeta (MetaNamed n m) -- | Print out an LLVM metadata value. ppLlvmMetaExpr :: MetaExpr -> SDoc -ppLlvmMetaExpr (MetaStr s ) = text "metadata !" <> doubleQuotes (ftext s) -ppLlvmMetaExpr (MetaNode n ) = text "metadata !" <> int n +ppLlvmMetaExpr (MetaStr s ) = text "!" <> doubleQuotes (ftext s) +ppLlvmMetaExpr (MetaNode n ) = text "!" <> int n ppLlvmMetaExpr (MetaVar v ) = ppr v ppLlvmMetaExpr (MetaStruct es) = - text "metadata !{" <> hsep (punctuate comma (map ppLlvmMetaExpr es)) <> char '}' + text "!{" <> hsep (punctuate comma (map ppLlvmMetaExpr es)) <> char '}' -- | Print out a list of function definitions. @@ -272,7 +272,7 @@ ppCall ct fptr args attrs = case fptr of where ppCall' (LlvmFunctionDecl _ _ cc ret argTy params _) = let tc = if ct == TailCall then text "tail " else empty - ppValues = ppCommaJoin args + ppValues = hsep $ punctuate comma $ map ppCallMetaExpr args ppArgTy = (ppCommaJoin $ map fst params) <> (case argTy of VarArgs -> text ", ..." @@ -283,6 +283,10 @@ ppCall ct fptr args attrs = case fptr of <> fnty <+> ppName fptr <> lparen <+> ppValues <+> rparen <+> attrDoc + -- Metadata needs to be marked as having the `metadata` type when used + -- in a call argument + ppCallMetaExpr (MetaVar v) = ppr v + ppCallMetaExpr v = text "metadata" <+> ppr v ppMachOp :: LlvmMachOp -> LlvmVar -> LlvmVar -> SDoc ppMachOp op left right = From git at git.haskell.org Mon Jan 19 23:16:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 23:16:38 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: Kill unused binding (2893517) Message-ID: <20150119231638.5EBCA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/289351774db47a0094afc7c57081c9dd06bbb062/ghc >--------------------------------------------------------------- commit 289351774db47a0094afc7c57081c9dd06bbb062 Author: Ben Gamari Date: Fri Nov 28 12:00:47 2014 -0500 Kill unused binding >--------------------------------------------------------------- 289351774db47a0094afc7c57081c9dd06bbb062 compiler/llvmGen/LlvmCodeGen/Ppr.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index ecd1d3c..fdc1c3a 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -117,7 +117,7 @@ pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) -- generate the info table prefix <- case mb_info of Nothing -> return Nothing - Just (Statics info_lbl statics) -> do + Just (Statics _ statics) -> do infoStatics <- mapM genData statics let infoTy = LMStruct $ map getStatType infoStatics return $ Just $ LMStaticStruc infoStatics infoTy From git at git.haskell.org Mon Jan 19 23:16:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 23:16:41 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: llvmGen: Only support LLVM 3.6 (e69cc4c) Message-ID: <20150119231641.0983E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/e69cc4c7f90e81d193122a02481de3be55decf7a/ghc >--------------------------------------------------------------- commit e69cc4c7f90e81d193122a02481de3be55decf7a Author: Ben Gamari Date: Fri Nov 28 10:17:19 2014 -0500 llvmGen: Only support LLVM 3.6 >--------------------------------------------------------------- e69cc4c7f90e81d193122a02481de3be55decf7a compiler/llvmGen/LlvmCodeGen/Base.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index a23b5ef..15918a3 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -176,13 +176,13 @@ type LlvmVersion = Int -- | The LLVM Version we assume if we don't know defaultLlvmVersion :: LlvmVersion -defaultLlvmVersion = 30 +defaultLlvmVersion = 36 minSupportLlvmVersion :: LlvmVersion -minSupportLlvmVersion = 28 +minSupportLlvmVersion = 36 maxSupportLlvmVersion :: LlvmVersion -maxSupportLlvmVersion = 35 +maxSupportLlvmVersion = 36 -- ---------------------------------------------------------------------------- -- * Environment Handling From git at git.haskell.org Mon Jan 19 23:16:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 23:16:43 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: Fix lints (39cdce5) Message-ID: <20150119231643.9E9B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/39cdce5ca11a231516f32df7ce5b76f9d420e43f/ghc >--------------------------------------------------------------- commit 39cdce5ca11a231516f32df7ce5b76f9d420e43f Author: Ben Gamari Date: Fri Nov 28 12:03:24 2014 -0500 Fix lints >--------------------------------------------------------------- 39cdce5ca11a231516f32df7ce5b76f9d420e43f compiler/llvmGen/LlvmCodeGen/Ppr.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index fdc1c3a..1a9373b 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -112,7 +112,8 @@ pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) funDec <- llvmFunSig live lbl link dflags <- getDynFlags - let funArgs = map (fsLit . showSDoc dflags . ppPlainName) (llvmFunArgs dflags live) + let buildArg = fsLit . showSDoc dflags . ppPlainName + funArgs = map buildArg (llvmFunArgs dflags live) -- generate the info table prefix <- case mb_info of @@ -122,7 +123,8 @@ pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) let infoTy = LMStruct $ map getStatType infoStatics return $ Just $ LMStaticStruc infoStatics infoTy - let fun = LlvmFunction funDec funArgs llvmStdFunAttrs Nothing prefix lmblocks + let fun = LlvmFunction funDec funArgs llvmStdFunAttrs Nothing + prefix lmblocks name = decName $ funcDecl fun defName = name `appendFS` fsLit "$def" funcDecl' = (funcDecl fun) { decName = defName } From git at git.haskell.org Mon Jan 19 23:16:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 23:16:46 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: More TNTC cleanup (077940b) Message-ID: <20150119231646.3F3C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/077940b9a4f5659722e48df505c2fa30e39a855f/ghc >--------------------------------------------------------------- commit 077940b9a4f5659722e48df505c2fa30e39a855f Author: Ben Gamari Date: Fri Nov 28 09:30:29 2014 -0500 More TNTC cleanup >--------------------------------------------------------------- 077940b9a4f5659722e48df505c2fa30e39a855f compiler/llvmGen/LlvmCodeGen.hs | 7 +------ compiler/llvmGen/LlvmCodeGen/Base.hs | 7 ------- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 6 +++--- 3 files changed, 4 insertions(+), 16 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs index 6120a72..f0c184a 100644 --- a/compiler/llvmGen/LlvmCodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen.hs @@ -138,13 +138,8 @@ cmmLlvmGen cmm at CmmProc{} = do -- generate llvm code from cmm llvmBC <- withClearVars $ genLlvmProc fixed_cmm - -- allocate IDs for info table and code, so the mangler can later - -- make sure they end up next to each other. - itableSection <- freshSectionId - _codeSection <- freshSectionId - -- pretty print - (docs, ivars) <- fmap unzip $ mapM (pprLlvmCmmDecl itableSection) llvmBC + (docs, ivars) <- fmap unzip $ mapM pprLlvmCmmDecl llvmBC -- Output, note down used variables renderLlvm (vcat docs) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index c1111cf..a23b5ef 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -24,7 +24,6 @@ module LlvmCodeGen.Base ( getMetaUniqueId, setUniqMeta, getUniqMeta, - freshSectionId, cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy, llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign, @@ -194,7 +193,6 @@ data LlvmEnv = LlvmEnv , envDynFlags :: DynFlags -- ^ Dynamic flags , envOutput :: BufHandle -- ^ Output buffer , envUniq :: UniqSupply -- ^ Supply of unique values - , envNextSection :: Int -- ^ Supply of fresh section IDs , envFreshMeta :: Int -- ^ Supply of fresh metadata IDs , envUniqMeta :: UniqFM Int -- ^ Global metadata nodes , envFunMap :: LlvmEnvMap -- ^ Global functions so far, with type @@ -248,7 +246,6 @@ runLlvm dflags ver out us m = do , envUniq = us , envFreshMeta = 0 , envUniqMeta = emptyUFM - , envNextSection = 1 } -- | Get environment (internal) @@ -353,10 +350,6 @@ setUniqMeta f m = modifyEnv $ \env -> env { envUniqMeta = addToUFM (envUniqMeta getUniqMeta :: Unique -> LlvmM (Maybe Int) getUniqMeta s = getEnv (flip lookupUFM s . envUniqMeta) --- | Returns a fresh section ID -freshSectionId :: LlvmM Int -freshSectionId = LlvmM $ \env -> return (envNextSection env, env { envNextSection = envNextSection env + 1}) - -- ---------------------------------------------------------------------------- -- * Internal functions -- diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index 321064c..ecd1d3c 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -96,11 +96,11 @@ pprLlvmData (globals, types) = -- | Pretty print LLVM code -pprLlvmCmmDecl :: Int -> LlvmCmmDecl -> LlvmM (SDoc, [LlvmVar]) -pprLlvmCmmDecl _ (CmmData _ lmdata) +pprLlvmCmmDecl :: LlvmCmmDecl -> LlvmM (SDoc, [LlvmVar]) +pprLlvmCmmDecl (CmmData _ lmdata) = return (vcat $ map pprLlvmData lmdata, []) -pprLlvmCmmDecl count (CmmProc mb_info entry_lbl live (ListGraph blks)) +pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) = do let lbl = case mb_info of Nothing -> entry_lbl Just (Statics info_lbl _) -> info_lbl From git at git.haskell.org Mon Jan 19 23:16:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 23:16:48 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: llvmGen: LLVM 3.6 makes alias grammar consistent (8a3790b) Message-ID: <20150119231648.DFC143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/8a3790ba01e5229dbc4c65ba3f3dfda2782c83a6/ghc >--------------------------------------------------------------- commit 8a3790ba01e5229dbc4c65ba3f3dfda2782c83a6 Author: Ben Gamari Date: Thu Nov 27 22:39:55 2014 +0100 llvmGen: LLVM 3.6 makes alias grammar consistent It used to be that the alias grammar was, @ = [Visibility] [DLLStorageClass] [ThreadLocal] [unnamed_addr] alias [Linkage] @ As of LLVM 3.6 it is now, @ = [Linkage] [Visibility] [DLLStorageClass] [ThreadLocal] [unnamed_addr] alias @ Namely the linkage has been moved to be consistent with the other global variable types. >--------------------------------------------------------------- 8a3790ba01e5229dbc4c65ba3f3dfda2782c83a6 compiler/llvmGen/Llvm/PpLlvm.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index 7307725..cdc407c 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -80,7 +80,7 @@ ppLlvmGlobal (LMGlobal var@(LMGlobalVar _ _ link x a c) dat) = const_link = case c of Global -> ppr link <+> text "global" Constant -> ppr link <+> text "constant" - Alias -> text "alias" <+> ppr link + Alias -> ppr link <+> text "alias" in ppAssignment var $ const_link <+> rhs <> sect <> align $+$ newLine From git at git.haskell.org Mon Jan 19 23:16:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Jan 2015 23:16:51 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: llvmGen: Begin reimplementing tntc (6910de9) Message-ID: <20150119231651.980E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/6910de9de9f284b2987215e0b07829815191be32/ghc >--------------------------------------------------------------- commit 6910de9de9f284b2987215e0b07829815191be32 Author: Ben Gamari Date: Thu Nov 27 22:04:31 2014 -0500 llvmGen: Begin reimplementing tntc >--------------------------------------------------------------- 6910de9de9f284b2987215e0b07829815191be32 compiler/llvmGen/Llvm/AbsSyn.hs | 13 +++--- compiler/llvmGen/Llvm/PpLlvm.hs | 15 ++++--- compiler/llvmGen/LlvmCodeGen/Base.hs | 13 +----- compiler/llvmGen/LlvmCodeGen/Data.hs | 2 +- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 82 +++++++++--------------------------- compiler/llvmGen/LlvmMangler.hs | 49 ++------------------- 6 files changed, 43 insertions(+), 131 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6910de9de9f284b2987215e0b07829815191be32 From git at git.haskell.org Tue Jan 20 12:37:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 12:37:01 +0000 (UTC) Subject: [commit: ghc] master: comments only (9894f6a) Message-ID: <20150120123701.A53F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9894f6a5b4883ea87fd5f280a2eb4a8abfbd2a6b/ghc >--------------------------------------------------------------- commit 9894f6a5b4883ea87fd5f280a2eb4a8abfbd2a6b Author: Simon Marlow Date: Wed Jan 14 08:45:07 2015 +0000 comments only >--------------------------------------------------------------- 9894f6a5b4883ea87fd5f280a2eb4a8abfbd2a6b rts/sm/Scav.c | 2 ++ 1 file changed, 2 insertions(+) diff --git a/rts/sm/Scav.c b/rts/sm/Scav.c index 2ecb23b..781840c 100644 --- a/rts/sm/Scav.c +++ b/rts/sm/Scav.c @@ -285,6 +285,8 @@ scavenge_large_srt_bitmap( StgLargeSRT *large_srt ) for (i = 0; i < size / BITS_IN(W_); i++) { bitmap = large_srt->l.bitmap[i]; + // skip zero words: bitmaps can be very sparse, and this helps + // performance a lot in some cases. if (bitmap != 0) { for (j = 0; j < BITS_IN(W_); j++) { if ((bitmap & 1) != 0) { From git at git.haskell.org Tue Jan 20 12:38:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 12:38:12 +0000 (UTC) Subject: [commit: ghc] master: Make the linker_unload test less fragile (6108d95) Message-ID: <20150120123812.B16AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6108d95a73f93d486223064ad72bf6bedc116cbd/ghc >--------------------------------------------------------------- commit 6108d95a73f93d486223064ad72bf6bedc116cbd Author: Simon Marlow Date: Tue Jan 20 03:59:25 2015 -0800 Make the linker_unload test less fragile Summary: Now it invokes the GHC API to load packages, rather than trying to do it manually. This should fix most of the issues we've had with this test, and might make it work on Windows too. >--------------------------------------------------------------- 6108d95a73f93d486223064ad72bf6bedc116cbd testsuite/tests/rts/LinkerUnload.hs | 20 ++++++++++++++++++ testsuite/tests/rts/Makefile | 21 ++----------------- testsuite/tests/rts/linker_unload.c | 35 ++++---------------------------- testsuite/tests/rts/linker_unload.stdout | 4 +++- 4 files changed, 29 insertions(+), 51 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6108d95a73f93d486223064ad72bf6bedc116cbd From git at git.haskell.org Tue Jan 20 14:13:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 14:13:40 +0000 (UTC) Subject: [commit: ghc] master: Cosmetic: Fix all uses of the word 'worker' when referring to pattern synonym builders (cf0e100) Message-ID: <20150120141340.4F9B23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cf0e10077c67018669633e14e7e574d38a9fb174/ghc >--------------------------------------------------------------- commit cf0e10077c67018669633e14e7e574d38a9fb174 Author: Dr. ERDI Gergo Date: Tue Jan 20 19:30:42 2015 +0800 Cosmetic: Fix all uses of the word 'worker' when referring to pattern synonym builders >--------------------------------------------------------------- cf0e10077c67018669633e14e7e574d38a9fb174 compiler/rename/RnBinds.hs | 12 ++++++------ compiler/typecheck/TcBinds.hs | 6 +++--- compiler/typecheck/TcPatSyn.hs | 26 ++++++++++++++++---------- 3 files changed, 25 insertions(+), 19 deletions(-) diff --git a/compiler/rename/RnBinds.hs b/compiler/rename/RnBinds.hs index 7a9dcae..97eb457 100644 --- a/compiler/rename/RnBinds.hs +++ b/compiler/rename/RnBinds.hs @@ -595,7 +595,7 @@ rnPatSynBind _sig_fn bind@(PSB { psb_id = L _ name ; fvs' `seq` -- See Note [Free-variable space leak] return (bind', [name], fvs1) - -- See Note [Pattern synonym wrappers don't yield dependencies] + -- See Note [Pattern synonym builders don't yield dependencies] } where lookupVar = wrapLocM lookupOccRn @@ -606,10 +606,10 @@ rnPatSynBind _sig_fn bind@(PSB { psb_id = L _ name 2 (ptext (sLit "Use -XPatternSynonyms to enable this extension")) {- -Note [Pattern synonym wrappers don't yield dependencies] +Note [Pattern synonym builders don't yield dependencies] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -When renaming a pattern synonym that has an explicit wrapper, -references in the wrapper definition should not be used when +When renaming a pattern synonym that has an explicit builder, +references in the builder definition should not be used when calculating dependencies. For example, consider the following pattern synonym definition: @@ -622,9 +622,9 @@ In this case, 'P' needs to be typechecked in two passes: 1. Typecheck the pattern definition of 'P', which fully determines the type of 'P'. This step doesn't require knowing anything about 'f', -since the wrapper definition is not looked at. +since the builder definition is not looked at. -2. Typecheck the wrapper definition, which needs the typechecked +2. Typecheck the builder definition, which needs the typechecked definition of 'f' to be in scope. This behaviour is implemented in 'tcValBinds', but it crucially diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index f421c74..fc84c59 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -313,9 +313,9 @@ tcValBinds top_lvl binds sigs thing_inside ; tcExtendIdEnv3 [(idName id, id) | id <- poly_ids] (mkVarSet nwc_tvs) $ do { (binds', (extra_binds', thing)) <- tcBindGroups top_lvl sig_fn prag_fn binds $ do { thing <- thing_inside - -- See Note [Pattern synonym wrappers don't yield dependencies] - ; patsyn_workers <- mapM tcPatSynBuilderBind patsyns - ; let extra_binds = [ (NonRecursive, worker) | worker <- patsyn_workers ] + -- See Note [Pattern synonym builders don't yield dependencies] + ; patsyn_builders <- mapM tcPatSynBuilderBind patsyns + ; let extra_binds = [ (NonRecursive, builder) | builder <- patsyn_builders ] ; return (extra_binds, thing) } ; return (binds' ++ extra_binds', thing) }} where diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 612eabe..9cc8222 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -191,7 +191,13 @@ tc_patsyn_finish lname dir is_infix lpat' (ex_tvs, subst, prov_theta, prov_ev_binds, prov_dicts) wrapped_args pat_ty - = do { (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' + = do { traceTc "tc_patsyn_finish {" $ + ppr (unLoc lname) $$ ppr (unLoc lpat') $$ + ppr (univ_tvs, req_theta, req_ev_binds, req_dicts) $$ + ppr (ex_tvs, subst, prov_theta, prov_ev_binds, prov_dicts) $$ + ppr wrapped_args $$ + ppr pat_ty + ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' (univ_tvs, req_theta, req_ev_binds, req_dicts) (ex_tvs, subst, prov_theta, prov_ev_binds, prov_dicts) wrapped_args @@ -350,25 +356,25 @@ tcPatSynBuilderBind PSB{ psb_id = L loc name, psb_def = lpat | otherwise -- Bidirectional = do { patsyn <- tcLookupPatSyn name - ; let Just (worker_id, need_dummy_arg) = patSynBuilder patsyn + ; let Just (builder_id, need_dummy_arg) = patSynBuilder patsyn -- Bidirectional, so patSynBuilder returns Just match_group' | need_dummy_arg = add_dummy_arg match_group | otherwise = match_group - bind = FunBind { fun_id = L loc (idName worker_id) + bind = FunBind { fun_id = L loc (idName builder_id) , fun_infix = False , fun_matches = match_group' , fun_co_fn = idHsWrapper , bind_fvs = placeHolderNamesTc , fun_tick = [] } - ; sig <- instTcTySigFromId worker_id + ; sig <- instTcTySigFromId builder_id -- See Note [Redundant constraints for builder] - ; (worker_binds, _, _) <- tcPolyCheck NonRecursive (const []) sig (noLoc bind) - ; traceTc "tcPatSynDecl worker" $ ppr worker_binds - ; return worker_binds } + ; (builder_binds, _, _) <- tcPolyCheck NonRecursive (const []) sig (noLoc bind) + ; traceTc "tcPatSynBuilderBind }" $ ppr builder_binds + ; return builder_binds } where Just match_group = mb_match_group mb_match_group @@ -378,10 +384,10 @@ tcPatSynBuilderBind PSB{ psb_id = L loc name, psb_def = lpat ImplicitBidirectional -> fmap mk_mg (tcPatToExpr args lpat) mk_mg :: LHsExpr Name -> MatchGroup Name (LHsExpr Name) - mk_mg body = mkMatchGroupName Generated [wrapper_match] + mk_mg body = mkMatchGroupName Generated [builder_match] where - wrapper_args = [L loc (VarPat n) | L loc n <- args] - wrapper_match = mkMatch wrapper_args body EmptyLocalBinds + builder_args = [L loc (VarPat n) | L loc n <- args] + builder_match = mkMatch builder_args body EmptyLocalBinds args = case details of PrefixPatSyn args -> args From git at git.haskell.org Tue Jan 20 16:54:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 16:54:35 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: llvmGen: LLVM 3.6 makes alias grammar consistent (da569bf) Message-ID: <20150120165436.010CD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/da569bfd34333a536843c8bac9409ee5173df7d1/ghc >--------------------------------------------------------------- commit da569bfd34333a536843c8bac9409ee5173df7d1 Author: Ben Gamari Date: Thu Nov 27 22:39:55 2014 +0100 llvmGen: LLVM 3.6 makes alias grammar consistent It used to be that the alias grammar was, @ = [Visibility] [DLLStorageClass] [ThreadLocal] [unnamed_addr] alias [Linkage] @ As of LLVM 3.6 it is now, @ = [Linkage] [Visibility] [DLLStorageClass] [ThreadLocal] [unnamed_addr] alias @ Namely the linkage has been moved to be consistent with the other global variable types. >--------------------------------------------------------------- da569bfd34333a536843c8bac9409ee5173df7d1 compiler/llvmGen/Llvm/PpLlvm.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index 7307725..cdc407c 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -80,7 +80,7 @@ ppLlvmGlobal (LMGlobal var@(LMGlobalVar _ _ link x a c) dat) = const_link = case c of Global -> ppr link <+> text "global" Constant -> ppr link <+> text "constant" - Alias -> text "alias" <+> ppr link + Alias -> ppr link <+> text "alias" in ppAssignment var $ const_link <+> rhs <> sect <> align $+$ newLine From git at git.haskell.org Tue Jan 20 16:54:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 16:54:38 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: Fix lints (116720c) Message-ID: <20150120165438.C08783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/116720c2d069fd666b647ef75f26beafeefdf6f3/ghc >--------------------------------------------------------------- commit 116720c2d069fd666b647ef75f26beafeefdf6f3 Author: Ben Gamari Date: Fri Nov 28 12:03:24 2014 -0500 Fix lints >--------------------------------------------------------------- 116720c2d069fd666b647ef75f26beafeefdf6f3 compiler/llvmGen/LlvmCodeGen/Ppr.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index fdc1c3a..1a9373b 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -112,7 +112,8 @@ pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) funDec <- llvmFunSig live lbl link dflags <- getDynFlags - let funArgs = map (fsLit . showSDoc dflags . ppPlainName) (llvmFunArgs dflags live) + let buildArg = fsLit . showSDoc dflags . ppPlainName + funArgs = map buildArg (llvmFunArgs dflags live) -- generate the info table prefix <- case mb_info of @@ -122,7 +123,8 @@ pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) let infoTy = LMStruct $ map getStatType infoStatics return $ Just $ LMStaticStruc infoStatics infoTy - let fun = LlvmFunction funDec funArgs llvmStdFunAttrs Nothing prefix lmblocks + let fun = LlvmFunction funDec funArgs llvmStdFunAttrs Nothing + prefix lmblocks name = decName $ funcDecl fun defName = name `appendFS` fsLit "$def" funcDecl' = (funcDecl fun) { decName = defName } From git at git.haskell.org Tue Jan 20 16:54:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 16:54:41 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: More TNTC cleanup (ef980b0) Message-ID: <20150120165441.65CA83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/ef980b019f705822d8f90bbab106f004dcd634eb/ghc >--------------------------------------------------------------- commit ef980b019f705822d8f90bbab106f004dcd634eb Author: Ben Gamari Date: Fri Nov 28 09:30:29 2014 -0500 More TNTC cleanup >--------------------------------------------------------------- ef980b019f705822d8f90bbab106f004dcd634eb compiler/llvmGen/LlvmCodeGen.hs | 7 +------ compiler/llvmGen/LlvmCodeGen/Base.hs | 7 ------- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 6 +++--- 3 files changed, 4 insertions(+), 16 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs index 6120a72..f0c184a 100644 --- a/compiler/llvmGen/LlvmCodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen.hs @@ -138,13 +138,8 @@ cmmLlvmGen cmm at CmmProc{} = do -- generate llvm code from cmm llvmBC <- withClearVars $ genLlvmProc fixed_cmm - -- allocate IDs for info table and code, so the mangler can later - -- make sure they end up next to each other. - itableSection <- freshSectionId - _codeSection <- freshSectionId - -- pretty print - (docs, ivars) <- fmap unzip $ mapM (pprLlvmCmmDecl itableSection) llvmBC + (docs, ivars) <- fmap unzip $ mapM pprLlvmCmmDecl llvmBC -- Output, note down used variables renderLlvm (vcat docs) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index c1111cf..a23b5ef 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -24,7 +24,6 @@ module LlvmCodeGen.Base ( getMetaUniqueId, setUniqMeta, getUniqMeta, - freshSectionId, cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy, llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign, @@ -194,7 +193,6 @@ data LlvmEnv = LlvmEnv , envDynFlags :: DynFlags -- ^ Dynamic flags , envOutput :: BufHandle -- ^ Output buffer , envUniq :: UniqSupply -- ^ Supply of unique values - , envNextSection :: Int -- ^ Supply of fresh section IDs , envFreshMeta :: Int -- ^ Supply of fresh metadata IDs , envUniqMeta :: UniqFM Int -- ^ Global metadata nodes , envFunMap :: LlvmEnvMap -- ^ Global functions so far, with type @@ -248,7 +246,6 @@ runLlvm dflags ver out us m = do , envUniq = us , envFreshMeta = 0 , envUniqMeta = emptyUFM - , envNextSection = 1 } -- | Get environment (internal) @@ -353,10 +350,6 @@ setUniqMeta f m = modifyEnv $ \env -> env { envUniqMeta = addToUFM (envUniqMeta getUniqMeta :: Unique -> LlvmM (Maybe Int) getUniqMeta s = getEnv (flip lookupUFM s . envUniqMeta) --- | Returns a fresh section ID -freshSectionId :: LlvmM Int -freshSectionId = LlvmM $ \env -> return (envNextSection env, env { envNextSection = envNextSection env + 1}) - -- ---------------------------------------------------------------------------- -- * Internal functions -- diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index 321064c..ecd1d3c 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -96,11 +96,11 @@ pprLlvmData (globals, types) = -- | Pretty print LLVM code -pprLlvmCmmDecl :: Int -> LlvmCmmDecl -> LlvmM (SDoc, [LlvmVar]) -pprLlvmCmmDecl _ (CmmData _ lmdata) +pprLlvmCmmDecl :: LlvmCmmDecl -> LlvmM (SDoc, [LlvmVar]) +pprLlvmCmmDecl (CmmData _ lmdata) = return (vcat $ map pprLlvmData lmdata, []) -pprLlvmCmmDecl count (CmmProc mb_info entry_lbl live (ListGraph blks)) +pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) = do let lbl = case mb_info of Nothing -> entry_lbl Just (Statics info_lbl _) -> info_lbl From git at git.haskell.org Tue Jan 20 16:54:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 16:54:44 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: llvmGen: Begin reimplementing tntc (37f82e9) Message-ID: <20150120165444.12EF73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/37f82e997d622015f267cd77d68d7c09306b8577/ghc >--------------------------------------------------------------- commit 37f82e997d622015f267cd77d68d7c09306b8577 Author: Ben Gamari Date: Thu Nov 27 22:04:31 2014 -0500 llvmGen: Begin reimplementing tntc >--------------------------------------------------------------- 37f82e997d622015f267cd77d68d7c09306b8577 compiler/llvmGen/Llvm/AbsSyn.hs | 13 +++--- compiler/llvmGen/Llvm/PpLlvm.hs | 15 ++++--- compiler/llvmGen/LlvmCodeGen/Base.hs | 13 +----- compiler/llvmGen/LlvmCodeGen/Data.hs | 2 +- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 82 +++++++++--------------------------- compiler/llvmGen/LlvmMangler.hs | 49 ++------------------- 6 files changed, 43 insertions(+), 131 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 37f82e997d622015f267cd77d68d7c09306b8577 From git at git.haskell.org Tue Jan 20 16:54:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 16:54:46 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: RFC: Move to LLVM 3.6 (fdb27cd) Message-ID: <20150120165446.A96C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/fdb27cd428ac1af8e250dc8c559d80461dc23873/ghc >--------------------------------------------------------------- commit fdb27cd428ac1af8e250dc8c559d80461dc23873 Author: Ben Gamari Date: Fri Nov 28 11:14:17 2014 -0500 RFC: Move to LLVM 3.6 Summary: Here we rework the LLVM backend to support LLVM 3.6 exclusively and refactor TNTC to take advantage of LLVM's new and improved prefix data support.. Test Plan: Validate, look at emitted code Reviewers: dterei, austin, scpmw Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D530 >--------------------------------------------------------------- fdb27cd428ac1af8e250dc8c559d80461dc23873 compiler/llvmGen/Llvm/PpLlvm.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index 050d200..de76766 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -77,12 +77,12 @@ ppLlvmGlobal (LMGlobal var@(LMGlobalVar _ _ link x a c) dat) = Nothing -> ppr (pLower $ getVarType var) -- Position of linkage is different for aliases. - const_link = case c of - Global -> ppr link <+> text "global" - Constant -> ppr link <+> text "constant" - Alias -> ppr link <+> text "alias" + const = case c of + Global -> text "global" + Constant -> text "constant" + Alias -> text "alias" - in ppAssignment var $ const_link <+> rhs <> sect <> align + in ppAssignment var $ ppr link <+> const <+> rhs <> sect <> align $+$ newLine ppLlvmGlobal (LMGlobal var val) = sdocWithDynFlags $ \dflags -> From git at git.haskell.org Tue Jan 20 16:54:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 16:54:49 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: llvmGen: metadata no longer marked with `metadata` keyword (884a826) Message-ID: <20150120165449.5632E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/884a826a64a82a1e8478b6d723c589a5d66267f5/ghc >--------------------------------------------------------------- commit 884a826a64a82a1e8478b6d723c589a5d66267f5 Author: Ben Gamari Date: Sun Jan 4 18:25:24 2015 -0500 llvmGen: metadata no longer marked with `metadata` keyword As of LLVM 3.6 >--------------------------------------------------------------- 884a826a64a82a1e8478b6d723c589a5d66267f5 compiler/llvmGen/Llvm/MetaData.hs | 14 +++++++------- compiler/llvmGen/Llvm/PpLlvm.hs | 12 ++++++++---- 2 files changed, 15 insertions(+), 11 deletions(-) diff --git a/compiler/llvmGen/Llvm/MetaData.hs b/compiler/llvmGen/Llvm/MetaData.hs index 36efcd7..e1e63c9 100644 --- a/compiler/llvmGen/Llvm/MetaData.hs +++ b/compiler/llvmGen/Llvm/MetaData.hs @@ -20,12 +20,12 @@ import Outputable -- information. They consist of metadata strings, metadata nodes, regular -- LLVM values (both literals and references to global variables) and -- metadata expressions (i.e., recursive data type). Some examples: --- !{ metadata !"hello", metadata !0, i32 0 } --- !{ metadata !1, metadata !{ i32 0 } } +-- !{ !"hello", !0, i32 0 } +-- !{ !1, !{ i32 0 } } -- -- * Metadata nodes -- global metadata variables that attach a metadata -- expression to a number. For example: --- !0 = metadata !{ [] !} +-- !0 = !{ [] !} -- -- * Named metadata -- global metadata variables that attach a metadata nodes -- to a name. Used ONLY to communicated module level information to LLVM @@ -39,7 +39,7 @@ import Outputable -- * Attach to instructions -- metadata can be attached to LLVM instructions -- using a specific reference as follows: -- %l = load i32* @glob, !nontemporal !10 --- %m = load i32* @glob, !nontemporal !{ i32 0, metadata !{ i32 0 } } +-- %m = load i32* @glob, !nontemporal !{ i32 0, !{ i32 0 } } -- Only metadata nodes or expressions can be attached, named metadata cannot. -- Refer to LLVM documentation for which instructions take metadata and its -- meaning. @@ -63,10 +63,10 @@ data MetaExpr = MetaStr LMString deriving (Eq) instance Outputable MetaExpr where - ppr (MetaStr s ) = text "metadata !\"" <> ftext s <> char '"' - ppr (MetaNode n ) = text "metadata !" <> int n + ppr (MetaStr s ) = text "!\"" <> ftext s <> char '"' + ppr (MetaNode n ) = text "!" <> int n ppr (MetaVar v ) = ppr v - ppr (MetaStruct es) = text "metadata !{ " <> ppCommaJoin es <> char '}' + ppr (MetaStruct es) = text "!{ " <> ppCommaJoin es <> char '}' -- | Associates some metadata with a specific label for attaching to an -- instruction. diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index de76766..0b3deac 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -117,11 +117,11 @@ ppLlvmMeta (MetaNamed n m) -- | Print out an LLVM metadata value. ppLlvmMetaExpr :: MetaExpr -> SDoc -ppLlvmMetaExpr (MetaStr s ) = text "metadata !" <> doubleQuotes (ftext s) -ppLlvmMetaExpr (MetaNode n ) = text "metadata !" <> int n +ppLlvmMetaExpr (MetaStr s ) = text "!" <> doubleQuotes (ftext s) +ppLlvmMetaExpr (MetaNode n ) = text "!" <> int n ppLlvmMetaExpr (MetaVar v ) = ppr v ppLlvmMetaExpr (MetaStruct es) = - text "metadata !{" <> hsep (punctuate comma (map ppLlvmMetaExpr es)) <> char '}' + text "!{" <> hsep (punctuate comma (map ppLlvmMetaExpr es)) <> char '}' -- | Print out a list of function definitions. @@ -272,7 +272,7 @@ ppCall ct fptr args attrs = case fptr of where ppCall' (LlvmFunctionDecl _ _ cc ret argTy params _) = let tc = if ct == TailCall then text "tail " else empty - ppValues = ppCommaJoin args + ppValues = hsep $ punctuate comma $ map ppCallMetaExpr args ppArgTy = (ppCommaJoin $ map fst params) <> (case argTy of VarArgs -> text ", ..." @@ -283,6 +283,10 @@ ppCall ct fptr args attrs = case fptr of <> fnty <+> ppName fptr <> lparen <+> ppValues <+> rparen <+> attrDoc + -- Metadata needs to be marked as having the `metadata` type when used + -- in a call argument + ppCallMetaExpr (MetaVar v) = ppr v + ppCallMetaExpr v = text "metadata" <+> ppr v ppMachOp :: LlvmMachOp -> LlvmVar -> LlvmVar -> SDoc ppMachOp op left right = From git at git.haskell.org Tue Jan 20 16:54:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 16:54:52 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: Kill unused binding (3ffd3ac) Message-ID: <20150120165452.0ADAB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/3ffd3ac4c068dfc9cf8491b3c6e87c510adcf753/ghc >--------------------------------------------------------------- commit 3ffd3ac4c068dfc9cf8491b3c6e87c510adcf753 Author: Ben Gamari Date: Fri Nov 28 12:00:47 2014 -0500 Kill unused binding >--------------------------------------------------------------- 3ffd3ac4c068dfc9cf8491b3c6e87c510adcf753 compiler/llvmGen/LlvmCodeGen/Ppr.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index ecd1d3c..fdc1c3a 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -117,7 +117,7 @@ pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) -- generate the info table prefix <- case mb_info of Nothing -> return Nothing - Just (Statics info_lbl statics) -> do + Just (Statics _ statics) -> do infoStatics <- mapM genData statics let infoTy = LMStruct $ map getStatType infoStatics return $ Just $ LMStaticStruc infoStatics infoTy From git at git.haskell.org Tue Jan 20 16:54:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 16:54:54 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6: llvmGen: Only support LLVM 3.6 (81615f0) Message-ID: <20150120165454.A96653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.6 Link : http://ghc.haskell.org/trac/ghc/changeset/81615f09d4eb2ad1a7267741f63df7d495effe9f/ghc >--------------------------------------------------------------- commit 81615f09d4eb2ad1a7267741f63df7d495effe9f Author: Ben Gamari Date: Fri Nov 28 10:17:19 2014 -0500 llvmGen: Only support LLVM 3.6 >--------------------------------------------------------------- 81615f09d4eb2ad1a7267741f63df7d495effe9f compiler/llvmGen/LlvmCodeGen/Base.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index a23b5ef..15918a3 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -176,13 +176,13 @@ type LlvmVersion = Int -- | The LLVM Version we assume if we don't know defaultLlvmVersion :: LlvmVersion -defaultLlvmVersion = 30 +defaultLlvmVersion = 36 minSupportLlvmVersion :: LlvmVersion -minSupportLlvmVersion = 28 +minSupportLlvmVersion = 36 maxSupportLlvmVersion :: LlvmVersion -maxSupportLlvmVersion = 35 +maxSupportLlvmVersion = 36 -- ---------------------------------------------------------------------------- -- * Environment Handling From git at git.haskell.org Tue Jan 20 16:54:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 16:54:57 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.6's head updated: llvmGen: metadata no longer marked with `metadata` keyword (884a826) Message-ID: <20150120165457.202DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/llvm-3.6' now includes: fb7c311 Repsect the package name when checking for self-import 854e7b8 Fix a terrible bug in the canonicaliser which led to an infinite loop 6392df0 Don't hardcode the name "ghc" in versionedAppDir fffbf06 Trac #9878: Make the static form illegal in interpreted mode. 11881ec API Annotations tweaks. 2edb4a7 Trac #9384: fix increasing capabilites number for eventlog. 3ea40e3 Fix the 'builder' code for pattern synonyms with type signatures 9a14582 Add missing argument in Match, a merge bug (apologies) ff4733f Update bytestring submodule 1289048 Fix bad '... \\' escape in ghcversion.h generation 8e774ba Improve documentation of pattern synonyms, to reflect conclusion of Trac #9953 4cfd235 Test Trac #9867 e1a4581 Revert "Fix undefined GHC.Real export with integer-simple" f006ed7 Revert "Add export lists to some modules." d839493 Make AutoDeriveTypeable work for associated datatypes (fix #9999) 55199a9 Split stripTicks into expression editing and tick collection 8ce3871 Update directory submodule to latest 1.2.2 snapshot 960e3c9 Add missing test from previous commit (55199a97) 851ed72 API Annotations documentation update, parsing issue, add example test cb65bdb Doc fix (follow up to #9957) d3c08ca Tidy up fix to Trac #9999 1f15951 Respect package visibility when deciding wired in packages. c77eecd Upgrade Cabal submodule to latest HEAD, change to package key calculation. c024af1 Expose source locations via Implicit Parameters of type GHC.Location.Location d82f592 CMM: add a mechanism to import C .data labels da569bf llvmGen: LLVM 3.6 makes alias grammar consistent 37f82e9 llvmGen: Begin reimplementing tntc ef980b0 More TNTC cleanup 81615f0 llvmGen: Only support LLVM 3.6 fdb27cd RFC: Move to LLVM 3.6 3ffd3ac Kill unused binding 116720c Fix lints 884a826 llvmGen: metadata no longer marked with `metadata` keyword From git at git.haskell.org Tue Jan 20 23:12:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 23:12:37 +0000 (UTC) Subject: [commit: ghc] master: cmm lex: drop unused 'align' token (f3e6271) Message-ID: <20150120231237.355DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f3e62714e356521efe49a011f874d3a66e543d76/ghc >--------------------------------------------------------------- commit f3e62714e356521efe49a011f874d3a66e543d76 Author: Sergei Trofimovich Date: Tue Jan 20 23:04:31 2015 +0000 cmm lex: drop unused 'align' token Max removed 'align' token from parser productions long ago: > commit ec39750268da134c906b8bb4b7d61763d4ea5c2e > Author: Max Bolingbroke > Date: Tue Jul 5 09:31:08 2011 +0100 > > Remove the unused CmmAlign and CmmDataLabel from CmmStatic This patch drops 'align' from lexer as well. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- f3e62714e356521efe49a011f874d3a66e543d76 compiler/cmm/CmmLex.x | 2 -- compiler/cmm/CmmParse.y | 1 - 2 files changed, 3 deletions(-) diff --git a/compiler/cmm/CmmLex.x b/compiler/cmm/CmmLex.x index d5a8067..9e688dd 100644 --- a/compiler/cmm/CmmLex.x +++ b/compiler/cmm/CmmLex.x @@ -144,7 +144,6 @@ data CmmToken | CmmT_else | CmmT_export | CmmT_section - | CmmT_align | CmmT_goto | CmmT_if | CmmT_call @@ -228,7 +227,6 @@ reservedWordsFM = listToUFM $ ( "else", CmmT_else ), ( "export", CmmT_export ), ( "section", CmmT_section ), - ( "align", CmmT_align ), ( "goto", CmmT_goto ), ( "if", CmmT_if ), ( "call", CmmT_call ), diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index fd9489b..916c161 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -309,7 +309,6 @@ import Data.Maybe 'else' { L _ (CmmT_else) } 'export' { L _ (CmmT_export) } 'section' { L _ (CmmT_section) } - 'align' { L _ (CmmT_align) } 'goto' { L _ (CmmT_goto) } 'if' { L _ (CmmT_if) } 'call' { L _ (CmmT_call) } From git at git.haskell.org Tue Jan 20 23:38:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Jan 2015 23:38:55 +0000 (UTC) Subject: [commit: ghc] master: compiler/parser/cutils: drop unused 'ghc_memcmp_off' helper (bef8b79) Message-ID: <20150120233855.3AD673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bef8b7976bd9ea0ee384d77cc8111cceae8d0d42/ghc >--------------------------------------------------------------- commit bef8b7976bd9ea0ee384d77cc8111cceae8d0d42 Author: Sergei Trofimovich Date: Tue Jan 20 23:27:08 2015 +0000 compiler/parser/cutils: drop unused 'ghc_memcmp_off' helper Function came out of use in 2006: > commit 9d7da331989abcd1844e9d03b8d1e4163796fa85 > Author: simonmar > Date: Fri Jan 6 16:30:19 2006 +0000 > > [project @ 2006-01-06 16:30:17 by simonmar] > Add support for UTF-8 source files Found by uselex.rb: ghc_memcmp_off: [R]: exported from: ./compiler/stage1/build/parser/cutils.o ./compiler/stage2/build/parser/cutils.o Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- bef8b7976bd9ea0ee384d77cc8111cceae8d0d42 compiler/parser/cutils.c | 6 ------ compiler/parser/cutils.h | 1 - 2 files changed, 7 deletions(-) diff --git a/compiler/parser/cutils.c b/compiler/parser/cutils.c index d714a0c..e458c08 100644 --- a/compiler/parser/cutils.c +++ b/compiler/parser/cutils.c @@ -30,12 +30,6 @@ ghc_memcmp( HsPtr a1, HsPtr a2, HsInt len ) return (memcmp((char *)a1, a2, len)); } -HsInt -ghc_memcmp_off( HsPtr a1, HsInt i, HsPtr a2, HsInt len ) -{ - return (memcmp((char *)a1 + i, a2, len)); -} - void enableTimingStats( void ) /* called from the driver */ { diff --git a/compiler/parser/cutils.h b/compiler/parser/cutils.h index c7c1867..95a10c5 100644 --- a/compiler/parser/cutils.h +++ b/compiler/parser/cutils.h @@ -9,7 +9,6 @@ // Out-of-line string functions, see PrimPacked.lhs HsInt ghc_strlen( HsAddr a ); HsInt ghc_memcmp( HsAddr a1, HsAddr a2, HsInt len ); -HsInt ghc_memcmp_off( HsAddr a1, HsInt i, HsAddr a2, HsInt len ); void enableTimingStats( void ); From git at git.haskell.org Wed Jan 21 16:11:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jan 2015 16:11:41 +0000 (UTC) Subject: [commit: ghc] master: Update Backpack document with examples [skip ci] (ca15376) Message-ID: <20150121161141.3BE4D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ca15376d9371f336be6102df6894e79710ccddbc/ghc >--------------------------------------------------------------- commit ca15376d9371f336be6102df6894e79710ccddbc Author: Edward Z. Yang Date: Wed Jan 21 08:13:09 2015 -0800 Update Backpack document with examples [skip ci] Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- ca15376d9371f336be6102df6894e79710ccddbc docs/backpack/backpack-manual.pdf | Bin 199748 -> 202608 bytes docs/backpack/backpack-manual.tex | 96 +++++++++++++++++++++++++++++++------- 2 files changed, 78 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ca15376d9371f336be6102df6894e79710ccddbc From git at git.haskell.org Wed Jan 21 18:30:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jan 2015 18:30:03 +0000 (UTC) Subject: [commit: ghc] master: Restore invariant in `Data (Ratio a)` instance (79b0d0e) Message-ID: <20150121183003.637363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/79b0d0e633af8302d2dd907663a4a231cd889b67/ghc >--------------------------------------------------------------- commit 79b0d0e633af8302d2dd907663a4a231cd889b67 Author: Herbert Valerio Riedel Date: Wed Jan 21 08:21:36 2015 +0100 Restore invariant in `Data (Ratio a)` instance The Data instance for `Ratio` just uses the raw `:%` constructor and doesn't check that the result is reduced to normal form. The fix is to add back the `Integral` constraint on the Data instance (which was dropped in c409b6f30373535) and to use `%` rather than `:%` in the `gfoldl` and `gunfold` implementation. This restores the invariant and matches the behavior of "virtual constructors" we've used to patch up such problems elsewhere. This addresses #10011 Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D625 >--------------------------------------------------------------- 79b0d0e633af8302d2dd907663a4a231cd889b67 libraries/base/Data/Data.hs | 8 ++++---- libraries/base/changelog.md | 2 ++ 2 files changed, 6 insertions(+), 4 deletions(-) diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index dce610b..4a6c8be 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -1059,15 +1059,15 @@ instance Data Word64 where ------------------------------------------------------------------------------ ratioConstr :: Constr -ratioConstr = mkConstr ratioDataType ":%" [] Infix +ratioConstr = mkConstr ratioDataType "%" [] Infix ratioDataType :: DataType ratioDataType = mkDataType "GHC.Real.Ratio" [ratioConstr] -instance Data a => Data (Ratio a) where - gfoldl k z (a :% b) = z (:%) `k` a `k` b +instance (Data a, Integral a) => Data (Ratio a) where + gfoldl k z (a :% b) = z (%) `k` a `k` b toConstr _ = ratioConstr - gunfold k z c | constrIndex c == 1 = k (k (z (:%))) + gunfold k z c | constrIndex c == 1 = k (k (z (%))) gunfold _ _ _ = error "Data.Data.gunfold(Ratio)" dataTypeOf _ = ratioDataType diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 83ae5e4..0d7ebcf 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -140,6 +140,8 @@ * Add `callocArray` and `callocArray0` to `Foreign.Marshal.Array`. (#9859) + * Restore invariant in `Data (Ratio a)` instance (#10011) + ## 4.7.0.2 *Dec 2014* * Bundled with GHC 7.8.4 From git at git.haskell.org Wed Jan 21 18:32:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jan 2015 18:32:07 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Restore invariant in `Data (Ratio a)` instance (dde5561) Message-ID: <20150121183207.22A9C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/dde5561b77b5b5703ddcd43fd8917a12f9d207e5/ghc >--------------------------------------------------------------- commit dde5561b77b5b5703ddcd43fd8917a12f9d207e5 Author: Herbert Valerio Riedel Date: Wed Jan 21 08:21:36 2015 +0100 Restore invariant in `Data (Ratio a)` instance The Data instance for `Ratio` just uses the raw `:%` constructor and doesn't check that the result is reduced to normal form. The fix is to add back the `Integral` constraint on the Data instance (which was dropped in c409b6f30373535) and to use `%` rather than `:%` in the `gfoldl` and `gunfold` implementation. This restores the invariant and matches the behavior of "virtual constructors" we've used to patch up such problems elsewhere. This addresses #10011 (cherry picked from commit 79b0d0e633af8302d2dd907663a4a231cd889b67) >--------------------------------------------------------------- dde5561b77b5b5703ddcd43fd8917a12f9d207e5 libraries/base/Data/Data.hs | 6 +++--- libraries/base/changelog.md | 2 ++ 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index 8f1e5f4..2ca3a0c 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -1059,15 +1059,15 @@ instance Data Word64 where ------------------------------------------------------------------------------ ratioConstr :: Constr -ratioConstr = mkConstr ratioDataType ":%" [] Infix +ratioConstr = mkConstr ratioDataType "%" [] Infix ratioDataType :: DataType ratioDataType = mkDataType "GHC.Real.Ratio" [ratioConstr] instance (Data a, Integral a) => Data (Ratio a) where - gfoldl k z (a :% b) = z (:%) `k` a `k` b + gfoldl k z (a :% b) = z (%) `k` a `k` b toConstr _ = ratioConstr - gunfold k z c | constrIndex c == 1 = k (k (z (:%))) + gunfold k z c | constrIndex c == 1 = k (k (z (%))) gunfold _ _ _ = error "Data.Data.gunfold(Ratio)" dataTypeOf _ = ratioDataType diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 83ae5e4..0d7ebcf 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -140,6 +140,8 @@ * Add `callocArray` and `callocArray0` to `Foreign.Marshal.Array`. (#9859) + * Restore invariant in `Data (Ratio a)` instance (#10011) + ## 4.7.0.2 *Dec 2014* * Bundled with GHC 7.8.4 From git at git.haskell.org Wed Jan 21 21:13:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Jan 2015 21:13:03 +0000 (UTC) Subject: [commit: ghc] master: Revert "Restore invariant in `Data (Ratio a)` instance" (22c4d60) Message-ID: <20150121211303.68E343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/22c4d60b0665a15535c0ec9fe0b8e65d2c948e7d/ghc >--------------------------------------------------------------- commit 22c4d60b0665a15535c0ec9fe0b8e65d2c948e7d Author: Herbert Valerio Riedel Date: Wed Jan 21 22:13:07 2015 +0100 Revert "Restore invariant in `Data (Ratio a)` instance" This reverts commit 79b0d0e633af8302d2dd907663a4a231cd889b67 due to Compile failed (status 256) errors were: [1 of 2] Compiling A ( A.hs, A.o ) [2 of 2] Compiling Main ( T4491.hs, T4491.o ) T4491.hs:19:11: Illegal data constructor name: ???%??? When splicing a TH expression: (GHC.Real.%) 11 2 In the splice: $(dataToExpQ (const Nothing) (5.5 :: Rational)) *** unexpected failure for T4491(normal) Therefore re-opening #10011 >--------------------------------------------------------------- 22c4d60b0665a15535c0ec9fe0b8e65d2c948e7d libraries/base/Data/Data.hs | 8 ++++---- libraries/base/changelog.md | 2 -- 2 files changed, 4 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index 4a6c8be..dce610b 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -1059,15 +1059,15 @@ instance Data Word64 where ------------------------------------------------------------------------------ ratioConstr :: Constr -ratioConstr = mkConstr ratioDataType "%" [] Infix +ratioConstr = mkConstr ratioDataType ":%" [] Infix ratioDataType :: DataType ratioDataType = mkDataType "GHC.Real.Ratio" [ratioConstr] -instance (Data a, Integral a) => Data (Ratio a) where - gfoldl k z (a :% b) = z (%) `k` a `k` b +instance Data a => Data (Ratio a) where + gfoldl k z (a :% b) = z (:%) `k` a `k` b toConstr _ = ratioConstr - gunfold k z c | constrIndex c == 1 = k (k (z (%))) + gunfold k z c | constrIndex c == 1 = k (k (z (:%))) gunfold _ _ _ = error "Data.Data.gunfold(Ratio)" dataTypeOf _ = ratioDataType diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 0d7ebcf..83ae5e4 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -140,8 +140,6 @@ * Add `callocArray` and `callocArray0` to `Foreign.Marshal.Array`. (#9859) - * Restore invariant in `Data (Ratio a)` instance (#10011) - ## 4.7.0.2 *Dec 2014* * Bundled with GHC 7.8.4 From git at git.haskell.org Thu Jan 22 09:41:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 09:41:24 +0000 (UTC) Subject: [commit: ghc] master: 32-bit performance wibbles (387f1d1) Message-ID: <20150122094124.AA5E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/387f1d1ec334788c3e891e9304d427bc804998f4/ghc >--------------------------------------------------------------- commit 387f1d1ec334788c3e891e9304d427bc804998f4 Author: Simon Peyton Jones Date: Tue Jan 20 17:31:13 2015 +0000 32-bit performance wibbles Less for GHC, more for Haddock >--------------------------------------------------------------- 387f1d1ec334788c3e891e9304d427bc804998f4 libraries/{integer-simple => haskell98}/.gitignore | 0 libraries/haskell98/Array.hs | 15 + libraries/haskell98/Bits.hs | 8 + libraries/haskell98/CError.hs | 8 + libraries/haskell98/CForeign.hs | 7 + libraries/haskell98/CPUTime.hs | 9 + libraries/haskell98/CString.hs | 7 + libraries/haskell98/CTypes.hs | 7 + libraries/haskell98/Char.hs | 18 + libraries/haskell98/Complex.hs | 11 + libraries/haskell98/Directory.hs | 46 +++ libraries/haskell98/ForeignPtr.hs | 7 + libraries/haskell98/IO.hs | 74 ++++ libraries/haskell98/Int.hs | 7 + libraries/haskell98/Ix.hs | 10 + libraries/haskell98/LICENSE | 28 ++ libraries/haskell98/List.hs | 34 ++ libraries/haskell98/Locale.hs | 17 + libraries/haskell98/MarshalAlloc.hs | 7 + libraries/haskell98/MarshalArray.hs | 7 + libraries/haskell98/MarshalError.hs | 22 ++ libraries/haskell98/MarshalUtils.hs | 7 + libraries/haskell98/Maybe.hs | 16 + libraries/haskell98/Monad.hs | 19 + libraries/haskell98/Numeric.hs | 48 +++ libraries/haskell98/Prelude.hs | 196 ++++++++++ libraries/haskell98/Ptr.hs | 7 + libraries/haskell98/Random.hs | 407 +++++++++++++++++++++ libraries/haskell98/Ratio.hs | 10 + libraries/{integer-gmp => haskell98}/Setup.hs | 0 libraries/haskell98/StablePtr.hs | 7 + libraries/haskell98/Storable.hs | 7 + libraries/haskell98/System.hs | 15 + libraries/haskell98/Time.hs | 22 ++ libraries/haskell98/Word.hs | 7 + libraries/haskell98/changelog.md | 15 + libraries/haskell98/haskell98.cabal | 86 +++++ libraries/haskell98/prologue.txt | 9 + testsuite/tests/perf/compiler/all.T | 7 +- testsuite/tests/perf/haddock/all.T | 13 +- 40 files changed, 1240 insertions(+), 7 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 387f1d1ec334788c3e891e9304d427bc804998f4 From git at git.haskell.org Thu Jan 22 09:41:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 09:41:27 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9975 (3992a6e) Message-ID: <20150122094127.BC0C13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3992a6e2d0fa2f046baaf14c264d21acf9540c83/ghc >--------------------------------------------------------------- commit 3992a6e2d0fa2f046baaf14c264d21acf9540c83 Author: Simon Peyton Jones Date: Tue Jan 20 17:31:54 2015 +0000 Test Trac #9975 >--------------------------------------------------------------- 3992a6e2d0fa2f046baaf14c264d21acf9540c83 testsuite/tests/patsyn/should_compile/T9975a.hs | 7 +++++++ testsuite/tests/patsyn/should_compile/T9975a.stderr | 5 +++++ testsuite/tests/patsyn/should_compile/T9975b.hs | 7 +++++++ testsuite/tests/patsyn/should_compile/all.T | 2 ++ 4 files changed, 21 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T9975a.hs b/testsuite/tests/patsyn/should_compile/T9975a.hs new file mode 100644 index 0000000..ed5a2c2 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T9975a.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE PatternSynonyms #-} +module T9975a where + +data Test = Test { x :: Int } +pattern Test wat = Test { x = wat } + diff --git a/testsuite/tests/patsyn/should_compile/T9975a.stderr b/testsuite/tests/patsyn/should_compile/T9975a.stderr new file mode 100644 index 0000000..faddb2a --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T9975a.stderr @@ -0,0 +1,5 @@ + +T9975a.hs:6:1: + Multiple declarations of ?Test? + Declared at: T9975a.hs:5:13 + T9975a.hs:6:1 diff --git a/testsuite/tests/patsyn/should_compile/T9975b.hs b/testsuite/tests/patsyn/should_compile/T9975b.hs new file mode 100644 index 0000000..d36f54d --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T9975b.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE PatternSynonyms #-} +module T9975b where + +data Test = Test { x :: Int } +pattern PTest wat = Test { x = wat } + diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 0ef30f0..a046e79 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -22,3 +22,5 @@ test('ImpExp_Imp', [extra_clean(['ImpExp_Exp.hi', 'ImpExp_Exp.o'])], multimod_co test('T9857', normal, compile, ['']) test('T9889', normal, compile, ['']) test('T9867', normal, compile, ['']) +test('T9975a', normal, compile_fail, ['']) +test('T9975b', normal, compile, ['']) From git at git.haskell.org Thu Jan 22 09:41:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 09:41:30 +0000 (UTC) Subject: [commit: ghc] master: Some simplification and refactoring of FunDeps (bec932e) Message-ID: <20150122094130.6A99D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bec932efeb8308e8d56f2559b824a4a2598723e3/ghc >--------------------------------------------------------------- commit bec932efeb8308e8d56f2559b824a4a2598723e3 Author: Simon Peyton Jones Date: Tue Jan 20 17:56:09 2015 +0000 Some simplification and refactoring of FunDeps Nothing magical here, but the data types had grown more complicated than we really needed, so there were some worthwhile simplifications to be had. No change in functionality. >--------------------------------------------------------------- bec932efeb8308e8d56f2559b824a4a2598723e3 compiler/typecheck/FunDeps.hs | 121 +++++++++++++++++---------------------- compiler/typecheck/TcInteract.hs | 70 +++++++++++----------- 2 files changed, 92 insertions(+), 99 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bec932efeb8308e8d56f2559b824a4a2598723e3 From git at git.haskell.org Thu Jan 22 09:41:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 09:41:33 +0000 (UTC) Subject: [commit: ghc] master: Merge branch 'master' of ssh://git.haskell.org/ghc (027acf6) Message-ID: <20150122094133.8C1A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/027acf6314e323dc25a0c1b66cb55bb9b19d9f89/ghc >--------------------------------------------------------------- commit 027acf6314e323dc25a0c1b66cb55bb9b19d9f89 Merge: bec932e 22c4d60 Author: Simon Peyton Jones Date: Thu Jan 22 09:42:30 2015 +0000 Merge branch 'master' of ssh://git.haskell.org/ghc >--------------------------------------------------------------- 027acf6314e323dc25a0c1b66cb55bb9b19d9f89 compiler/cmm/CmmLex.x | 2 - compiler/cmm/CmmParse.y | 1 - compiler/parser/cutils.c | 6 -- compiler/parser/cutils.h | 1 - compiler/rename/RnBinds.hs | 12 ++-- compiler/typecheck/TcBinds.hs | 6 +- compiler/typecheck/TcPatSyn.hs | 26 +++++---- docs/backpack/backpack-manual.pdf | Bin 199748 -> 202608 bytes docs/backpack/backpack-manual.tex | 96 +++++++++++++++++++++++++------ rts/sm/Scav.c | 2 + testsuite/tests/rts/LinkerUnload.hs | 20 +++++++ testsuite/tests/rts/Makefile | 21 +------ testsuite/tests/rts/linker_unload.c | 35 ++--------- testsuite/tests/rts/linker_unload.stdout | 4 +- 14 files changed, 134 insertions(+), 98 deletions(-) From git at git.haskell.org Thu Jan 22 10:26:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 10:26:44 +0000 (UTC) Subject: [commit: ghc] master: Update a few performance numbers (8a29493) Message-ID: <20150122102644.A5BB83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a29493dc35d28b42105501ad19ba7e82448772a/ghc >--------------------------------------------------------------- commit 8a29493dc35d28b42105501ad19ba7e82448772a Author: Joachim Breitner Date: Thu Jan 22 11:27:35 2015 +0100 Update a few performance numbers to have less annoying false negatives on http://perf.ghc.haskell.org/#graph/testsuite/unexpected%20stats >--------------------------------------------------------------- 8a29493dc35d28b42105501ad19ba7e82448772a testsuite/tests/perf/compiler/all.T | 7 +++++-- testsuite/tests/perf/haddock/all.T | 3 ++- 2 files changed, 7 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 4e0fa2c..a874866 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -129,7 +129,7 @@ test('T3294', # 2014-04-24 19882188 (x86/Windows, 64bit machine) # 2014-12-22 26525384 (x86/Windows) Increase due to silent superclasses? - (wordsize(64), 40000000, 15)]), + (wordsize(64), 45000000, 20)]), # prev: 25753192 (amd64/Linux) # 29/08/2012: 37724352 (amd64/Linux) # (increase due to new codegen, see #7198) @@ -141,6 +141,8 @@ test('T3294', # (reason for increase back to earlier value unknown) # 2014-07-14: 36670800 (amd64/Linux) # (reason unknown, setting expected value somewhere in between) + # 2015-01-22: 45000000 (amd64/Linux) + # varies between 40959592 and 52914488... increasing to +-20% compiler_stats_num_field('bytes allocated', [(wordsize(32), 1377050640, 5), @@ -242,7 +244,7 @@ test('T3064', # 2013-11-13: 18 (x86/Windows, 64bit machine) # 2014-01-22: 23 (x86/Linux) # 2014-12-22: 23 (x86/Linux) death to silent superclasses - (wordsize(64), 27, 20)]), + (wordsize(64), 32, 20)]), # (amd64/Linux): 18 # (amd64/Linux) 2012-02-07: 26 # (amd64/Linux) 2013-02-12: 23; increased range to 10% @@ -254,6 +256,7 @@ test('T3064', # (amd64/Linux) (09/09/2014): 42, AMP changes (larger interfaces, more loading) # (amd64/Linux) 2014-10-13: 38: Stricter seqDmdType # (amd64/Linux) 2014-12-22: 27: death to silent superclasses + # (amd64/Linux) 2015-01-22: 32: Varies from 30 to 34, at least here. compiler_stats_num_field('bytes allocated', [(wordsize(32), 122836340, 10), diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 4e74798..e9ffbb6 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -45,7 +45,7 @@ test('haddock.base', test('haddock.Cabal', [unless(in_tree_compiler(), skip) ,stats_num_field('bytes allocated', - [(wordsize(64), 6387320816, 5) + [(wordsize(64), 6710234312, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -64,6 +64,7 @@ test('haddock.Cabal', # 2014-09-24: 5840893376 (x86_64/Linux - Cabal update) # 2014-10-04: 6019839624 (x86_64/Linux - Burning Bridges, Cabal update) # 2014-12-14: 6387320816 (x86_64/Linux) - Update to Haddock 2.16 + # 2015-01-22: 6710234312 (x86_64/Linux) - Cabal updated ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) From git at git.haskell.org Thu Jan 22 11:14:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 11:14:00 +0000 (UTC) Subject: [commit: ghc] master: Revert "32-bit performance wibbles" (ccbe2b8) Message-ID: <20150122111400.C0E043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ccbe2b8b8a564598dfbb72e2cd617c8f0c891b9a/ghc >--------------------------------------------------------------- commit ccbe2b8b8a564598dfbb72e2cd617c8f0c891b9a Author: Simon Peyton Jones Date: Thu Jan 22 10:52:02 2015 +0000 Revert "32-bit performance wibbles" This reverts commit 387f1d1ec334788c3e891e9304d427bc804998f4. Bizarrely, this commit accidentally added libraries/haskell98. So I'll revert it entirely and start again. >--------------------------------------------------------------- ccbe2b8b8a564598dfbb72e2cd617c8f0c891b9a libraries/haskell98/.gitignore | 3 - libraries/haskell98/Array.hs | 15 -- libraries/haskell98/Bits.hs | 8 - libraries/haskell98/CError.hs | 8 - libraries/haskell98/CForeign.hs | 7 - libraries/haskell98/CPUTime.hs | 9 - libraries/haskell98/CString.hs | 7 - libraries/haskell98/CTypes.hs | 7 - libraries/haskell98/Char.hs | 18 -- libraries/haskell98/Complex.hs | 11 - libraries/haskell98/Directory.hs | 46 ---- libraries/haskell98/ForeignPtr.hs | 7 - libraries/haskell98/IO.hs | 74 ------- libraries/haskell98/Int.hs | 7 - libraries/haskell98/Ix.hs | 10 - libraries/haskell98/LICENSE | 28 --- libraries/haskell98/List.hs | 34 --- libraries/haskell98/Locale.hs | 17 -- libraries/haskell98/MarshalAlloc.hs | 7 - libraries/haskell98/MarshalArray.hs | 7 - libraries/haskell98/MarshalError.hs | 22 -- libraries/haskell98/MarshalUtils.hs | 7 - libraries/haskell98/Maybe.hs | 16 -- libraries/haskell98/Monad.hs | 19 -- libraries/haskell98/Numeric.hs | 48 ----- libraries/haskell98/Prelude.hs | 196 ----------------- libraries/haskell98/Ptr.hs | 7 - libraries/haskell98/Random.hs | 407 ------------------------------------ libraries/haskell98/Ratio.hs | 10 - libraries/haskell98/Setup.hs | 6 - libraries/haskell98/StablePtr.hs | 7 - libraries/haskell98/Storable.hs | 7 - libraries/haskell98/System.hs | 15 -- libraries/haskell98/Time.hs | 22 -- libraries/haskell98/Word.hs | 7 - libraries/haskell98/changelog.md | 15 -- libraries/haskell98/haskell98.cabal | 86 -------- libraries/haskell98/prologue.txt | 9 - testsuite/tests/perf/compiler/all.T | 7 +- testsuite/tests/perf/haddock/all.T | 13 +- 40 files changed, 7 insertions(+), 1249 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ccbe2b8b8a564598dfbb72e2cd617c8f0c891b9a From git at git.haskell.org Thu Jan 22 11:14:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 11:14:03 +0000 (UTC) Subject: [commit: ghc] master: 32-bit performance wibbles (second attempt) (e675664) Message-ID: <20150122111403.60FFB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e6756640bb410258837d186e8c2e339d6746dc11/ghc >--------------------------------------------------------------- commit e6756640bb410258837d186e8c2e339d6746dc11 Author: Simon Peyton Jones Date: Thu Jan 22 10:55:48 2015 +0000 32-bit performance wibbles (second attempt) Updates the performance numbers for 32-bit windows. I tried to do this before with 387f1d1ec, but accidentally included some unrelated changes. >--------------------------------------------------------------- e6756640bb410258837d186e8c2e339d6746dc11 testsuite/tests/perf/compiler/all.T | 7 ++++--- testsuite/tests/perf/haddock/all.T | 13 +++++++++---- 2 files changed, 13 insertions(+), 7 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index e65ce83..a874866 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -578,7 +578,7 @@ test('T9872a', # 2014-12-10 5521332656 Initally created # 2014-12-16 5848657456 Flattener parameterized over roles # 2014-12-18 2680733672 Reduce type families even more eagerly - (wordsize(32), 1400000000, 5) + (wordsize(32), 1325592896, 5) ]), ], compile_fail, @@ -615,7 +615,7 @@ test('T9872d', # 2014-12-18 796071864 Initally created # 2014-12-18 739189056 Reduce type families even more eagerly # 2015-01-07 687562440 TrieMap leaf compression - (wordsize(32), 353644844, 5) + (wordsize(32), 328810212, 5) ]), ], compile, @@ -624,8 +624,9 @@ test('T9872d', test('T9961', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 772510192, 5) + [(wordsize(64), 772510192, 5), # 2015-01-12 807117816 Initally created + (wordsize(32), 375647160, 5) ]), ], compile, diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 21b4af7..e9ffbb6 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -23,11 +23,13 @@ test('haddock.base', # 2014-10-07: 8322584616 (x86_64/Linux) # 2014-12-14: 9502647104 (x86_64/Linux) - Update to Haddock 2.16 # 2014-01-08: 9014511528 (x86_64/Linux) - Eliminate so-called "silent superclass parameters" (and others) - ,(platform('i386-unknown-mingw32'), 4202377432, 5) + + ,(platform('i386-unknown-mingw32'), 4434804940, 5) # 2013-02-10: 3358693084 (x86/Windows) # 2013-11-13: 3097751052 (x86/Windows, 64bit machine) # 2014-04-04: 3548581572 (x86/Windows, 64bit machine) # 2014-12-01: 4202377432 (x86/Windows, 64bit machine) + # 2015-01-20: 4434804940 (x86/Windows, 64bit machine) ,(wordsize(32), 3799130400, 1)]) # 2012-08-14: 3046487920 (x86/OSX) @@ -64,12 +66,13 @@ test('haddock.Cabal', # 2014-12-14: 6387320816 (x86_64/Linux) - Update to Haddock 2.16 # 2015-01-22: 6710234312 (x86_64/Linux) - Cabal updated - ,(platform('i386-unknown-mingw32'), 3088635556, 5) + ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) # 2013-02-10: 1906532680 (x86/Windows) # 2014-01-28: 1966911336 (x86/Windows) # 2014-04-24: 2052220292 (x86/Windows) # 2014-12-01: 3088635556 (x86/Windows) + # 2015-01-20: 3293415576 ,(wordsize(32), 2127198484, 1)]) # 2012-08-14: 1648610180 (x86/OSX) @@ -84,7 +87,7 @@ test('haddock.compiler', [unless(in_tree_compiler(), skip) ,stats_num_field('bytes allocated', [(wordsize(64), 33562468736, 10) - # 2012-08-14: 26070600504 (amd64/Linux) + # 2012P-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) # 2012-11-12: 25990254632 (amd64/Linux) @@ -92,12 +95,14 @@ test('haddock.compiler', # 2012-11-27: 28708374824 (amd64/Linux) # 2014-09-10: 30353349160 (amd64/Linux) post-AMP cleanup # 2014-11-22: 33562468736 (amd64/Linux) - ,(platform('i386-unknown-mingw32'), 217933548, 10) + + ,(platform('i386-unknown-mingw32'), 902576468, 10) # 2012-10-30: 13773051312 (x86/Windows) # 2013-02-10: 14925262356 (x86/Windows) # 2013-11-13: 14328363592 (x86/Windows, 64bit machine) # 2014-12-01: 104140852 (x86/Windows, sudden shrinkage!) # 2014-12-10: 217933548 increased again + ,(wordsize(32), 15110426000, 1)]) # 2012-08-14: 13471797488 (x86/OSX) # 2014-01-22: 14581475024 (x86/Linux - new haddock) From git at git.haskell.org Thu Jan 22 15:24:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 15:24:01 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update submodule git branch for haddock (4c49f08) Message-ID: <20150122152401.4E8713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/4c49f08c8e62d9c3b854ec4137ba4d159b6c06f5/ghc >--------------------------------------------------------------- commit 4c49f08c8e62d9c3b854ec4137ba4d159b6c06f5 Author: Herbert Valerio Riedel Date: Thu Jan 22 16:24:46 2015 +0100 Update submodule git branch for haddock This is meta-information is used by commands such as e.g. git submodule update --remote util/haddock [skip ci] >--------------------------------------------------------------- 4c49f08c8e62d9c3b854ec4137ba4d159b6c06f5 .gitmodules | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitmodules b/.gitmodules index 75c508d..7039156 100644 --- a/.gitmodules +++ b/.gitmodules @@ -103,7 +103,7 @@ path = utils/haddock url = ../haddock.git ignore = none - branch = ghc-head + branch = master [submodule "nofib"] path = nofib url = ../nofib.git From git at git.haskell.org Thu Jan 22 21:35:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 21:35:45 +0000 (UTC) Subject: [commit: ghc] master: Restore invariant in `Data (Ratio a)` instance (3df429e) Message-ID: <20150122213545.BE22D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3df429e29b6fabda12af71091ba4ad1360f49b44/ghc >--------------------------------------------------------------- commit 3df429e29b6fabda12af71091ba4ad1360f49b44 Author: Herbert Valerio Riedel Date: Wed Jan 21 08:21:36 2015 +0100 Restore invariant in `Data (Ratio a)` instance (2nd attempt, this time leaving the `Constr` using `":%"`) The Data instance for `Ratio` just uses the raw `:%` constructor and doesn't check that the result is reduced to normal form. The fix is to add back the `Integral` constraint on the Data instance (which was dropped in c409b6f30373535) and to use `%` rather than `:%` in the `gfoldl` and `gunfold` implementation. This restores the invariant and matches the behavior of "virtual constructors" we've used to patch up such problems elsewhere. This addresses #10011 Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D625 >--------------------------------------------------------------- 3df429e29b6fabda12af71091ba4ad1360f49b44 libraries/base/Data/Data.hs | 6 +++--- libraries/base/changelog.md | 2 ++ 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index dce610b..6961b25 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -1064,10 +1064,10 @@ ratioConstr = mkConstr ratioDataType ":%" [] Infix ratioDataType :: DataType ratioDataType = mkDataType "GHC.Real.Ratio" [ratioConstr] -instance Data a => Data (Ratio a) where - gfoldl k z (a :% b) = z (:%) `k` a `k` b +instance (Data a, Integral a) => Data (Ratio a) where + gfoldl k z (a :% b) = z (%) `k` a `k` b toConstr _ = ratioConstr - gunfold k z c | constrIndex c == 1 = k (k (z (:%))) + gunfold k z c | constrIndex c == 1 = k (k (z (%))) gunfold _ _ _ = error "Data.Data.gunfold(Ratio)" dataTypeOf _ = ratioDataType diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 83ae5e4..0d7ebcf 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -140,6 +140,8 @@ * Add `callocArray` and `callocArray0` to `Foreign.Marshal.Array`. (#9859) + * Restore invariant in `Data (Ratio a)` instance (#10011) + ## 4.7.0.2 *Dec 2014* * Bundled with GHC 7.8.4 From git at git.haskell.org Thu Jan 22 21:59:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 21:59:49 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Restore invariant in `Data (Ratio a)` instance (bcfe534) Message-ID: <20150122215949.E34C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/bcfe5344a279377d75cdd31a35a1d47c5d4eb1a5/ghc >--------------------------------------------------------------- commit bcfe5344a279377d75cdd31a35a1d47c5d4eb1a5 Author: Herbert Valerio Riedel Date: Wed Jan 21 08:21:36 2015 +0100 Restore invariant in `Data (Ratio a)` instance (2nd attempt, this time leaving the `Constr` using `":%"`) The Data instance for `Ratio` just uses the raw `:%` constructor and doesn't check that the result is reduced to normal form. The fix is to add back the `Integral` constraint on the Data instance (which was dropped in c409b6f30373535) and to use `%` rather than `:%` in the `gfoldl` and `gunfold` implementation. This restores the invariant and matches the behavior of "virtual constructors" we've used to patch up such problems elsewhere. This addresses #10011 (cherry picked from commit 3df429e29b6fabda12af71091ba4ad1360f49b44) >--------------------------------------------------------------- bcfe5344a279377d75cdd31a35a1d47c5d4eb1a5 libraries/base/Data/Data.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index 2ca3a0c..fbad1d1 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -1059,7 +1059,7 @@ instance Data Word64 where ------------------------------------------------------------------------------ ratioConstr :: Constr -ratioConstr = mkConstr ratioDataType "%" [] Infix +ratioConstr = mkConstr ratioDataType ":%" [] Infix ratioDataType :: DataType ratioDataType = mkDataType "GHC.Real.Ratio" [ratioConstr] From git at git.haskell.org Thu Jan 22 22:36:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:36:05 +0000 (UTC) Subject: [commit: packages/binary] master: Add GHC 7.10 to test matrix (ea64195) Message-ID: <20150122223605.09C713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/ea641955e6465824789eb8e0452c5bad9a2b1fe8 >--------------------------------------------------------------- commit ea641955e6465824789eb8e0452c5bad9a2b1fe8 Author: Lennart Kolmodin Date: Fri Dec 26 20:42:14 2014 +0300 Add GHC 7.10 to test matrix >--------------------------------------------------------------- ea641955e6465824789eb8e0452c5bad9a2b1fe8 .travis.yml | 33 +++++++++++++++++---------------- 1 file changed, 17 insertions(+), 16 deletions(-) diff --git a/.travis.yml b/.travis.yml index 2c4c95a..5127742 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,35 +2,36 @@ # See https://github.com/hvr/multi-ghc-travis for more information env: - - GHCVER=7.4.2 - - GHCVER=7.6.3 - - GHCVER=7.8.3 + - CABALVER=1.16 GHCVER=7.4.2 + - CABALVER=1.18 GHCVER=7.6.3 + - CABALVER=1.18 GHCVER=7.8.3 + - CABALVER=1.22 GHCVER=7.10.1 before_install: - sudo add-apt-repository -y ppa:hvr/ghc - sudo apt-get update - - sudo apt-get install cabal-install-1.20 ghc-$GHCVER - - export PATH=/opt/ghc/$GHCVER/bin:$PATH + - sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH install: - - cabal-1.20 update - - cabal-1.20 sandbox init + - cabal update + - cabal sandbox init # can't use "cabal install --only-dependencies --enable-tests --enable-benchmarks" due to dep-cycle - - cabal-1.20 install criterion deepseq mtl "QuickCheck >= 2.7.3" HUnit "test-framework-quickcheck2 >= 0.3" "random >= 1.0.1.0" attoparsec cereal -j + - cabal install criterion deepseq mtl "QuickCheck >= 2.7.3" HUnit "test-framework-quickcheck2 >= 0.3" "random >= 1.0.1.0" attoparsec cereal -j script: - - cabal-1.20 configure --enable-tests --enable-benchmarks -v2 --ghc-options=-fno-spec-constr - - cabal-1.20 build - - cabal-1.20 test + - cabal configure --enable-tests --enable-benchmarks -v2 --ghc-options=-fno-spec-constr + - cabal build + - cabal test # "cabal check" disabled due to -O2 warning -# - cabal-1.20 check - - cabal-1.20 sdist +# - cabal check + - cabal sdist # check that the generated source-distribution can be built & installed - - export SRC_TGZ=$(cabal-1.20 info . | awk '{print $2 ".tar.gz";exit}') ; + - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; - cabal-1.20 sandbox init; + cabal sandbox init; if [ -f "$SRC_TGZ" ]; then - cabal-1.20 install "$SRC_TGZ"; + cabal install --force-reinstalls "$SRC_TGZ"; else echo "expected '$SRC_TGZ' not found"; exit 1; From git at git.haskell.org Thu Jan 22 22:36:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:36:07 +0000 (UTC) Subject: [commit: packages/binary] master: Travis: Use cabal-1.18 for older ghc versions. (4853c7b) Message-ID: <20150122223607.0F6D13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/4853c7b467409468ac9029558c8ed3caa4a4be6c >--------------------------------------------------------------- commit 4853c7b467409468ac9029558c8ed3caa4a4be6c Author: Lennart Kolmodin Date: Sat Dec 27 15:34:38 2014 +0300 Travis: Use cabal-1.18 for older ghc versions. We use the sandbox feature. >--------------------------------------------------------------- 4853c7b467409468ac9029558c8ed3caa4a4be6c .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 5127742..832819a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,7 +2,7 @@ # See https://github.com/hvr/multi-ghc-travis for more information env: - - CABALVER=1.16 GHCVER=7.4.2 + - CABALVER=1.18 GHCVER=7.4.2 - CABALVER=1.18 GHCVER=7.6.3 - CABALVER=1.18 GHCVER=7.8.3 - CABALVER=1.22 GHCVER=7.10.1 From git at git.haskell.org Thu Jan 22 22:36:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:36:09 +0000 (UTC) Subject: [commit: packages/binary] master: Add instance for Natural. (74b2c01) Message-ID: <20150122223609.171183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/74b2c01c64709ccdb4df2103cf931f1390f6b632 >--------------------------------------------------------------- commit 74b2c01c64709ccdb4df2103cf931f1390f6b632 Author: Lennart Kolmodin Date: Thu Jan 1 21:26:18 2015 +0300 Add instance for Natural. Natural is a new data type that comes with base-4.8 (GHC 7.10). We serialize it in the same way as we do with Integer. Since this is a new data type there are some ugly CPPs to handle whether Natural is there or not. Serialization tests have been added as well. Since QuickCheck doesn't yet implement instance Arbitrary Natural we do a workaround here. This fixes #63. >--------------------------------------------------------------- 74b2c01c64709ccdb4df2103cf931f1390f6b632 src/Data/Binary/Class.hs | 37 +++++++++++++++++++++++++++++++++++-- tests/Arbitrary.hs | 23 +++++++++++++++++++++++ tests/QC.hs | 20 ++++++++++++++++++-- 3 files changed, 76 insertions(+), 4 deletions(-) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index e5e59e8..8a4bc25 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -5,6 +5,11 @@ #ifdef GENERICS {-# LANGUAGE DefaultSignatures #-} #endif + +#if MIN_VERSION_base(4,8,0) +#define HAS_NATURAL +#endif + ----------------------------------------------------------------------------- -- | -- Module : Data.Binary.Class @@ -61,6 +66,9 @@ import Data.Array.Unboxed import GHC.Generics #endif +#ifdef HAS_NATURAL +import Numeric.Natural +#endif -- -- This isn't available in older Hugs or older GHC -- @@ -225,17 +233,42 @@ instance Binary Integer where -- -- Fold and unfold an Integer to and from a list of its bytes -- -unroll :: Integer -> [Word8] +unroll :: (Integral a, Num a, Bits a) => a -> [Word8] unroll = unfoldr step where step 0 = Nothing step i = Just (fromIntegral i, i `shiftR` 8) -roll :: [Word8] -> Integer +roll :: (Integral a, Num a, Bits a) => [Word8] -> a roll = foldr unstep 0 where unstep b a = a `shiftL` 8 .|. fromIntegral b +#ifdef HAS_NATURAL +-- Fixed-size type for a subset of Natural +type NaturalWord = Word64 + +instance Binary Natural where + {-# INLINE put #-} + put n | n <= hi = do + putWord8 0 + put (fromIntegral n :: NaturalWord) -- fast path + where + hi = fromIntegral (maxBound :: NaturalWord) :: Natural + + put n = do + putWord8 1 + put (unroll (abs n)) -- unroll the bytes + + {-# INLINE get #-} + get = do + tag <- get :: Get Word8 + case tag of + 0 -> liftM fromIntegral (get :: Get NaturalWord) + _ -> do bytes <- get + return $! roll bytes +#endif + {- -- diff --git a/tests/Arbitrary.hs b/tests/Arbitrary.hs index 99725af..c19a192 100644 --- a/tests/Arbitrary.hs +++ b/tests/Arbitrary.hs @@ -1,5 +1,10 @@ +{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-orphans #-} +#if MIN_VERSION_base(4,8,0) +#define HAS_NATURAL +#endif + module Arbitrary where import Test.QuickCheck @@ -7,6 +12,10 @@ import Test.QuickCheck import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as L +#ifdef HAS_NATURAL +import Numeric.Natural +#endif + instance Arbitrary L.ByteString where arbitrary = fmap L.fromChunks arbitrary @@ -52,3 +61,17 @@ instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, (a,b,c,d,e) <- arbitrary (f,g,h,i,j) <- arbitrary return (a,b,c,d,e,f,g,h,i,j) + + +#ifdef HAS_NATURAL +-- | Generates a natural number. The number must be positive +-- and its maximum value depends on the size parameter. +arbitrarySizedNatural :: Gen Natural +arbitrarySizedNatural = + sized $ \n0 -> + let n = toInteger n0 in + inBounds fromInteger (choose (0, n*n)) + +inBounds :: Integral a => (Integer -> a) -> Gen Integer -> Gen a +inBounds fi g = fmap fi (g `suchThat` (\x -> toInteger (fi x) == x)) +#endif \ No newline at end of file diff --git a/tests/QC.hs b/tests/QC.hs index fbaded1..2a08b3b 100644 --- a/tests/QC.hs +++ b/tests/QC.hs @@ -1,6 +1,10 @@ -{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE CPP, ScopedTypeVariables #-} module Main ( main ) where +#if MIN_VERSION_base(4,8,0) +#define HAS_NATURAL +#endif + import Control.Applicative import Control.Exception as C (SomeException, catch, evaluate) @@ -17,7 +21,7 @@ import Test.Framework.Providers.QuickCheck2 import Test.QuickCheck import qualified Action (tests) -import Arbitrary () +import Arbitrary (arbitrarySizedNatural) import Data.Binary import Data.Binary.Get import Data.Binary.Put @@ -349,6 +353,15 @@ main = defaultMain tests ------------------------------------------------------------------------ +#ifdef HAS_NATURAL +-- | Until the QuickCheck library implements instance Arbitrary Natural, +-- we need this test. +prop_test_Natural :: Property +prop_test_Natural = forAll arbitrarySizedNatural test +#endif + +------------------------------------------------------------------------ + type T a = a -> Property type B a = a -> Bool @@ -426,6 +439,9 @@ tests = , ("Word", p (test :: T Word )) , ("Int", p (test :: T Int )) , ("Integer", p (test :: T Integer )) +#ifdef HAS_NATURAL + , ("Natural", (prop_test_Natural :: Property )) +#endif , ("Float", p (test :: T Float )) , ("Double", p (test :: T Double )) From git at git.haskell.org Thu Jan 22 22:36:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:36:11 +0000 (UTC) Subject: [commit: packages/binary] master: Fix compilation error. (067a192) Message-ID: <20150122223611.1DE633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/067a19299eb068ee3228388a44bad4e5adae09b0 >--------------------------------------------------------------- commit 067a19299eb068ee3228388a44bad4e5adae09b0 Author: Lennart Kolmodin Date: Fri Jan 2 01:33:47 2015 +0300 Fix compilation error. arbitrarySizedNatural is only defined when base >= 4.8. >--------------------------------------------------------------- 067a19299eb068ee3228388a44bad4e5adae09b0 tests/QC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/QC.hs b/tests/QC.hs index 2a08b3b..653cb85 100644 --- a/tests/QC.hs +++ b/tests/QC.hs @@ -21,7 +21,7 @@ import Test.Framework.Providers.QuickCheck2 import Test.QuickCheck import qualified Action (tests) -import Arbitrary (arbitrarySizedNatural) +import Arbitrary import Data.Binary import Data.Binary.Get import Data.Binary.Put From git at git.haskell.org Thu Jan 22 22:36:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:36:13 +0000 (UTC) Subject: [commit: packages/binary] master: Silence warning. (8893118) Message-ID: <20150122223613.24F763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/8893118f94ea3bec5182c3a8b2285956982996e5 >--------------------------------------------------------------- commit 8893118f94ea3bec5182c3a8b2285956982996e5 Author: Lennart Kolmodin Date: Sat Jan 10 12:51:38 2015 +0300 Silence warning. >--------------------------------------------------------------- 8893118f94ea3bec5182c3a8b2285956982996e5 tests/QC.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/tests/QC.hs b/tests/QC.hs index 653cb85..9e00616 100644 --- a/tests/QC.hs +++ b/tests/QC.hs @@ -21,7 +21,11 @@ import Test.Framework.Providers.QuickCheck2 import Test.QuickCheck import qualified Action (tests) -import Arbitrary +import Arbitrary ( +#ifdef HAS_NATURAL + arbitrarySizedNatural +#endif + ) import Data.Binary import Data.Binary.Get import Data.Binary.Put From git at git.haskell.org Thu Jan 22 22:36:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:36:15 +0000 (UTC) Subject: [commit: packages/binary] master: Fix doc: Int64 are written as 8 bytes, not 4 (039918f) Message-ID: <20150122223615.2B1DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/039918f447ac0840577a8887d32a09e447baa192 >--------------------------------------------------------------- commit 039918f447ac0840577a8887d32a09e447baa192 Author: JP Moresmau Date: Sat Jan 17 17:55:51 2015 +0100 Fix doc: Int64 are written as 8 bytes, not 4 >--------------------------------------------------------------- 039918f447ac0840577a8887d32a09e447baa192 src/Data/Binary/Class.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 8a4bc25..8b7bc13 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -173,7 +173,7 @@ instance Binary Int32 where put i = put (fromIntegral i :: Word32) get = liftM fromIntegral (get :: Get Word32) --- Int64s are written as a 4 bytes in big endian format +-- Int64s are written as a 8 bytes in big endian format instance Binary Int64 where put i = put (fromIntegral i :: Word64) get = liftM fromIntegral (get :: Get Word64) From git at git.haskell.org Thu Jan 22 22:36:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:36:17 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #66 from JPMoresmau/master (91a86a7) Message-ID: <20150122223617.30E7E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/91a86a7148b81c5c8a42ba614bd78184a9375988 >--------------------------------------------------------------- commit 91a86a7148b81c5c8a42ba614bd78184a9375988 Merge: 8893118 039918f Author: Lennart Kolmodin Date: Sat Jan 17 19:59:35 2015 +0300 Merge pull request #66 from JPMoresmau/master Fix doc: Int64 are written as 8 bytes, not 4 >--------------------------------------------------------------- 91a86a7148b81c5c8a42ba614bd78184a9375988 src/Data/Binary/Class.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Jan 22 22:36:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:36:19 +0000 (UTC) Subject: [commit: packages/binary] master: Update changelog.md with changes for 0.7.3.0 (77c7d5f) Message-ID: <20150122223619.372343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/77c7d5f5ada4f74fdcde2d1046accc9ae7ff742b >--------------------------------------------------------------- commit 77c7d5f5ada4f74fdcde2d1046accc9ae7ff742b Author: Lennart Kolmodin Date: Thu Jan 22 18:13:42 2015 +0100 Update changelog.md with changes for 0.7.3.0 >--------------------------------------------------------------- 77c7d5f5ada4f74fdcde2d1046accc9ae7ff742b changelog.md | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/changelog.md b/changelog.md index 5d54fec..3d0f2f7 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,12 @@ binary ====== + +binary-0.7.3.0 +-------------- + +- Add Binary instance for Natural (only with base > 4.8). + binary-0.7.2.3 -------------- From git at git.haskell.org Thu Jan 22 22:36:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:36:21 +0000 (UTC) Subject: [commit: packages/binary] master: Bump version to 0.7.3.0 (ff9a48f) Message-ID: <20150122223621.3DAF93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/ff9a48fb213c2d1fd2e58b19c92264a3efadff7a >--------------------------------------------------------------- commit ff9a48fb213c2d1fd2e58b19c92264a3efadff7a Author: Lennart Kolmodin Date: Thu Jan 22 18:14:21 2015 +0100 Bump version to 0.7.3.0 >--------------------------------------------------------------- ff9a48fb213c2d1fd2e58b19c92264a3efadff7a binary.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/binary.cabal b/binary.cabal index cf3ed2e..3303025 100644 --- a/binary.cabal +++ b/binary.cabal @@ -1,5 +1,5 @@ name: binary -version: 0.7.2.3 +version: 0.7.3.0 license: BSD3 license-file: LICENSE author: Lennart Kolmodin From git at git.haskell.org Thu Jan 22 22:36:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:36:39 +0000 (UTC) Subject: [commit: ghc] master: Update binary submodule to 0.7.3.0 release (f2867dc) Message-ID: <20150122223639.879813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f2867dc52be69accec841dc8c4bbeb5e84edec51/ghc >--------------------------------------------------------------- commit f2867dc52be69accec841dc8c4bbeb5e84edec51 Author: Herbert Valerio Riedel Date: Thu Jan 22 23:06:14 2015 +0100 Update binary submodule to 0.7.3.0 release One highlight of 0.7.3.0 is the new instance for `Natural` >--------------------------------------------------------------- f2867dc52be69accec841dc8c4bbeb5e84edec51 libraries/binary | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/binary b/libraries/binary index a3edce4..ff9a48f 160000 --- a/libraries/binary +++ b/libraries/binary @@ -1 +1 @@ -Subproject commit a3edce4b95b82388997929424ce98b1d7a75350d +Subproject commit ff9a48fb213c2d1fd2e58b19c92264a3efadff7a From git at git.haskell.org Thu Jan 22 22:37:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Jan 2015 22:37:22 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update binary submodule to 0.7.3.0 release (a2858b8) Message-ID: <20150122223722.C17B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a2858b820586e9c3ba8c53269f8c9a4410ba523c/ghc >--------------------------------------------------------------- commit a2858b820586e9c3ba8c53269f8c9a4410ba523c Author: Herbert Valerio Riedel Date: Thu Jan 22 23:06:14 2015 +0100 Update binary submodule to 0.7.3.0 release One highlight of 0.7.3.0 is the new instance for `Natural` (cherry picked from commit f2867dc52be69accec841dc8c4bbeb5e84edec51) >--------------------------------------------------------------- a2858b820586e9c3ba8c53269f8c9a4410ba523c libraries/binary | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/binary b/libraries/binary index a3edce4..ff9a48f 160000 --- a/libraries/binary +++ b/libraries/binary @@ -1 +1 @@ -Subproject commit a3edce4b95b82388997929424ce98b1d7a75350d +Subproject commit ff9a48fb213c2d1fd2e58b19c92264a3efadff7a From git at git.haskell.org Fri Jan 23 00:12:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 00:12:36 +0000 (UTC) Subject: [commit: ghc] master: Update Haddock submodule (34d68d8) Message-ID: <20150123001236.46BA83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/34d68d8e83676c5010e9bc5d4619f24879f222af/ghc >--------------------------------------------------------------- commit 34d68d8e83676c5010e9bc5d4619f24879f222af Author: Mateusz Kowalczyk Date: Fri Jan 23 00:14:00 2015 +0000 Update Haddock submodule >--------------------------------------------------------------- 34d68d8e83676c5010e9bc5d4619f24879f222af utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index d61bbc7..bf77580 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6 +Subproject commit bf77580eb40fa960b701296ac828372d127a43dd From git at git.haskell.org Fri Jan 23 07:28:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 07:28:52 +0000 (UTC) Subject: [commit: ghc] master: Revert "Update Haddock submodule" (febee92) Message-ID: <20150123072852.9FC5A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/febee92ca8661b392fb09de91e2d317196658fdb/ghc >--------------------------------------------------------------- commit febee92ca8661b392fb09de91e2d317196658fdb Author: Herbert Valerio Riedel Date: Fri Jan 23 08:27:38 2015 +0100 Revert "Update Haddock submodule" This reverts commit 34d68d8e83676c5010e9bc5d4619f24879f222af as it breaks the build: Configuring hsc2hs-0.67... Configuring ghc-cabal-0.1... Configuring parallel-3.2.0.6... Configuring hpc-bin-0.67... Configuring haddock-2.16.0... ghc-cabal: At least the following dependencies are missing: ghc >=7.9 && <7.11 make[1]: *** [utils/haddock/dist/package-data.mk] Error 1 make[1]: *** Waiting for unfinished jobs.... GHC PKG libraries/parallel/dist-install/package-data.mk Reading package info from "libraries/parallel/dist-install/inplace-pkg-config" ... done. parallel-3.2.0.6: Warning: haddock-interfaces: /srv/builds/commits/rGHC/B3035-34d68d8e83676c5010e9bc5d4619f24879f222af/libraries/parallel/dist-install/doc/html/parallel/parallel.haddock doesn't exist or isn't a file parallel-3.2.0.6: cannot find any of ["Control/Seq.hi","Control/Seq.p_hi","Control/Seq.dyn_hi"] (ignoring) parallel-3.2.0.6: cannot find any of ["Control/Parallel.hi","Control/Parallel.p_hi","Control/Parallel.dyn_hi"] (ignoring) parallel-3.2.0.6: cannot find any of ["Control/Parallel/Strategies.hi","Control/Parallel/Strategies.p_hi","Control/Parallel/Strategies.dyn_hi"] (ignoring) parallel-3.2.0.6: cannot find any of ["libHSparal_791B1zx5CJ25cUOFECtmw0.a","libHSparal_791B1zx5CJ25cUOFECtmw0.p_a","libHSparal_791B1zx5CJ25cUOFECtmw0-ghc7.11.20150123.so","libHSparal_791B1zx5CJ25cUOFECtmw0-ghc7.11.20150123.dylib","HSparal_791B1zx5CJ25cUOFECtmw0-ghc7.11.20150123.dll"] on library path (ignoring) make: *** [all] Error 2 Moreover, utils/haddock is supposed to track the `ghc-head` branch (which is what `git submodule update --remote utils/haddock` helps with) >--------------------------------------------------------------- febee92ca8661b392fb09de91e2d317196658fdb utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index bf77580..d61bbc7 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit bf77580eb40fa960b701296ac828372d127a43dd +Subproject commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6 From git at git.haskell.org Fri Jan 23 07:52:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 07:52:37 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Haddock submodule to `master` branch tip (d2f34c9) Message-ID: <20150123075237.A27FA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/d2f34c9311f7a6b588a1efa26584e94fdad7d58c/ghc >--------------------------------------------------------------- commit d2f34c9311f7a6b588a1efa26584e94fdad7d58c Author: Herbert Valerio Riedel Date: Fri Jan 23 08:32:39 2015 +0100 Update Haddock submodule to `master` branch tip >--------------------------------------------------------------- d2f34c9311f7a6b588a1efa26584e94fdad7d58c utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 7f23bd5..bf77580 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 7f23bd526a6dd6ed0a2ddeeb30724606ea058ef5 +Subproject commit bf77580eb40fa960b701296ac828372d127a43dd From git at git.haskell.org Fri Jan 23 10:10:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 10:10:22 +0000 (UTC) Subject: [commit: ghc] master: Revert zipWith strictification (re #9949) (f44bbc8) Message-ID: <20150123101022.ED52A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f44bbc83bab62f9a2d25e69d87c2b4af25318d52/ghc >--------------------------------------------------------------- commit f44bbc83bab62f9a2d25e69d87c2b4af25318d52 Author: David Feuer Date: Fri Jan 23 10:04:49 2015 +0100 Revert zipWith strictification (re #9949) Also remove foldr2/right rule to avoid possibly introducing bottoms with rules. This effectively reverts most of 488e95b433d4f7568aa89622c729e64aa3b6520d Reviewed By: nomeata Differential Revision: https://phabricator.haskell.org/D602 >--------------------------------------------------------------- f44bbc83bab62f9a2d25e69d87c2b4af25318d52 docs/users_guide/bugs.xml | 8 ------- libraries/base/GHC/List.hs | 57 +++++++++++++++++++-------------------------- libraries/base/changelog.md | 4 ---- 3 files changed, 24 insertions(+), 45 deletions(-) diff --git a/docs/users_guide/bugs.xml b/docs/users_guide/bugs.xml index 30770f0..a23c75c 100644 --- a/docs/users_guide/bugs.xml +++ b/docs/users_guide/bugs.xml @@ -302,14 +302,6 @@ checking for duplicates. The reason for this is efficiency, pure and simple. splitAt undefined [] = undefined - - zip and zipWith semantics - zip and zipWith can give - less defined results than the Report specifies in certain cases. This deviation - is needed to allow more opportunities for list fusion. In particular, - termination of the left list cannot be used to avoid hitting bottom in the - right list. See the documentation for details. - Reading integers diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs index 34ba445..a712f9e 100644 --- a/libraries/base/GHC/List.hs +++ b/libraries/base/GHC/List.hs @@ -875,7 +875,7 @@ xs !! n foldr2 :: (a -> b -> c -> c) -> c -> [a] -> [b] -> c foldr2 k z = go where - go [] !_ys = z -- see #9495 for the ! + go [] _ys = z go _xs [] = z go (x:xs) (y:ys) = k x y (go xs ys) {-# INLINE [0] foldr2 #-} @@ -884,20 +884,26 @@ foldr2_left :: (a -> b -> c -> d) -> d -> a -> ([b] -> c) -> [b] -> d foldr2_left _k z _x _r [] = z foldr2_left k _z x r (y:ys) = k x y (r ys) -foldr2_right :: (a -> b -> c -> d) -> d -> b -> ([a] -> c) -> [a] -> d -foldr2_right _k z _y _r [] = z -foldr2_right k _z y r (x:xs) = k x y (r xs) - -- foldr2 k z xs ys = foldr (foldr2_left k z) (\_ -> z) xs ys --- foldr2 k z xs ys = foldr (foldr2_right k z) (\_ -> z) ys xs {-# RULES "foldr2/left" forall k z ys (g::forall b.(a->b->b)->b->b) . foldr2 k z (build g) ys = g (foldr2_left k z) (\_ -> z) ys - -"foldr2/right" forall k z xs (g::forall b.(a->b->b)->b->b) . - foldr2 k z xs (build g) = g (foldr2_right k z) (\_ -> z) xs #-} - +-- There used to be a foldr2/right rule, allowing foldr2 to fuse with a build +-- form on the right. However, this causes trouble if the right list ends in +-- a bottom that is only avoided by the left list ending at that spot. That is, +-- foldr2 f z [a,b,c] (d:e:f:_|_), where the right list is produced by a build +-- form, would cause the foldr2/right rule to introduce bottom. Example: +-- +-- zip [1,2,3,4] (unfoldr (\s -> if s > 4 then undefined else Just (s,s+1)) 1) +-- +-- should produce +-- +-- [(1,1),(2,2),(3,3),(4,4)] +-- +-- but with the foldr2/right rule it would instead produce +-- +-- (1,1):(2,2):(3,3):(4,4):_|_ -- Zips for larger tuples are in the List module. @@ -906,19 +912,12 @@ foldr2_right k _z y r (x:xs) = k x y (r xs) -- If one input list is short, excess elements of the longer list are -- discarded. -- --- NOTE: GHC's implementation of @zip@ deviates slightly from the --- standard. In particular, Haskell 98 and Haskell 2010 require that --- @zip [x1,x2,...,xn] (y1:y2:...:yn:_|_) = [(x1,y1),(x2,y2),...,(xn,yn)]@ --- In GHC, however, --- @zip [x1,x2,...,xn] (y1:y2:...:yn:_|_) = (x1,y1):(x2,y2):...:(xn,yn):_|_@ --- That is, you cannot use termination of the left list to avoid hitting --- bottom in the right list. - --- This deviation is necessary to make fusion with 'build' in the right --- list preserve semantics. +-- 'zip' is right-lazy: +-- +-- > zip [] _|_ = [] {-# NOINLINE [1] zip #-} zip :: [a] -> [b] -> [(a,b)] -zip [] !_bs = [] -- see #9495 for the ! +zip [] _bs = [] zip _as [] = [] zip (a:as) (b:bs) = (a,b) : zip as bs @@ -950,20 +949,12 @@ zip3 _ _ _ = [] -- For example, @'zipWith' (+)@ is applied to two lists to produce the -- list of corresponding sums. -- --- NOTE: GHC's implementation of @zipWith@ deviates slightly from the --- standard. In particular, Haskell 98 and Haskell 2010 require that --- @zipWith (,) [x1,x2,...,xn] (y1:y2:...:yn:_|_) = [(x1,y1),(x2,y2),...,(xn,yn)]@ --- In GHC, however, --- @zipWith (,) [x1,x2,...,xn] (y1:y2:...:yn:_|_) = (x1,y1):(x2,y2):...:(xn,yn):_|_@ --- That is, you cannot use termination of the left list to avoid hitting --- bottom in the right list. - --- This deviation is necessary to make fusion with 'build' in the right --- list preserve semantics. - +-- 'zipWith' is right-lazy: +-- +-- > zipWith f [] _|_ = [] {-# NOINLINE [1] zipWith #-} zipWith :: (a->b->c) -> [a]->[b]->[c] -zipWith _f [] !_bs = [] -- see #9495 for the ! +zipWith _f [] _bs = [] zipWith _f _as [] = [] zipWith f (a:as) (b:bs) = f a b : zipWith f as bs diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 0d7ebcf..89caf01 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -77,10 +77,6 @@ * Generalise `Control.Monad.{foldM,foldM_}` to `Foldable` - * `foldr2` (together with `zip` and `zipWith`) is made a bit stricter in the - second argument, so that the fusion RULES for it do not change the - semantics. (#9596) - * `scanr`, `mapAccumL` and `filterM` now take part in list fusion (#9355, #9502, #9546) From git at git.haskell.org Fri Jan 23 10:10:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 10:10:25 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Revert zipWith strictification (re #9949) (19ad227) Message-ID: <20150123101025.8ABC73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/19ad227fbfa23f64f7422751b9559b4ac44d5081/ghc >--------------------------------------------------------------- commit 19ad227fbfa23f64f7422751b9559b4ac44d5081 Author: David Feuer Date: Fri Jan 23 10:04:49 2015 +0100 Revert zipWith strictification (re #9949) Also remove foldr2/right rule to avoid possibly introducing bottoms with rules. This effectively reverts most of 488e95b433d4f7568aa89622c729e64aa3b6520d (cherry picked from commit f44bbc83bab62f9a2d25e69d87c2b4af25318d52) >--------------------------------------------------------------- 19ad227fbfa23f64f7422751b9559b4ac44d5081 docs/users_guide/bugs.xml | 8 ------- libraries/base/GHC/List.hs | 57 +++++++++++++++++++-------------------------- libraries/base/changelog.md | 4 ---- 3 files changed, 24 insertions(+), 45 deletions(-) diff --git a/docs/users_guide/bugs.xml b/docs/users_guide/bugs.xml index 30770f0..a23c75c 100644 --- a/docs/users_guide/bugs.xml +++ b/docs/users_guide/bugs.xml @@ -302,14 +302,6 @@ checking for duplicates. The reason for this is efficiency, pure and simple. splitAt undefined [] = undefined - - zip and zipWith semantics - zip and zipWith can give - less defined results than the Report specifies in certain cases. This deviation - is needed to allow more opportunities for list fusion. In particular, - termination of the left list cannot be used to avoid hitting bottom in the - right list. See the documentation for details. - Reading integers diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs index 34ba445..a712f9e 100644 --- a/libraries/base/GHC/List.hs +++ b/libraries/base/GHC/List.hs @@ -875,7 +875,7 @@ xs !! n foldr2 :: (a -> b -> c -> c) -> c -> [a] -> [b] -> c foldr2 k z = go where - go [] !_ys = z -- see #9495 for the ! + go [] _ys = z go _xs [] = z go (x:xs) (y:ys) = k x y (go xs ys) {-# INLINE [0] foldr2 #-} @@ -884,20 +884,26 @@ foldr2_left :: (a -> b -> c -> d) -> d -> a -> ([b] -> c) -> [b] -> d foldr2_left _k z _x _r [] = z foldr2_left k _z x r (y:ys) = k x y (r ys) -foldr2_right :: (a -> b -> c -> d) -> d -> b -> ([a] -> c) -> [a] -> d -foldr2_right _k z _y _r [] = z -foldr2_right k _z y r (x:xs) = k x y (r xs) - -- foldr2 k z xs ys = foldr (foldr2_left k z) (\_ -> z) xs ys --- foldr2 k z xs ys = foldr (foldr2_right k z) (\_ -> z) ys xs {-# RULES "foldr2/left" forall k z ys (g::forall b.(a->b->b)->b->b) . foldr2 k z (build g) ys = g (foldr2_left k z) (\_ -> z) ys - -"foldr2/right" forall k z xs (g::forall b.(a->b->b)->b->b) . - foldr2 k z xs (build g) = g (foldr2_right k z) (\_ -> z) xs #-} - +-- There used to be a foldr2/right rule, allowing foldr2 to fuse with a build +-- form on the right. However, this causes trouble if the right list ends in +-- a bottom that is only avoided by the left list ending at that spot. That is, +-- foldr2 f z [a,b,c] (d:e:f:_|_), where the right list is produced by a build +-- form, would cause the foldr2/right rule to introduce bottom. Example: +-- +-- zip [1,2,3,4] (unfoldr (\s -> if s > 4 then undefined else Just (s,s+1)) 1) +-- +-- should produce +-- +-- [(1,1),(2,2),(3,3),(4,4)] +-- +-- but with the foldr2/right rule it would instead produce +-- +-- (1,1):(2,2):(3,3):(4,4):_|_ -- Zips for larger tuples are in the List module. @@ -906,19 +912,12 @@ foldr2_right k _z y r (x:xs) = k x y (r xs) -- If one input list is short, excess elements of the longer list are -- discarded. -- --- NOTE: GHC's implementation of @zip@ deviates slightly from the --- standard. In particular, Haskell 98 and Haskell 2010 require that --- @zip [x1,x2,...,xn] (y1:y2:...:yn:_|_) = [(x1,y1),(x2,y2),...,(xn,yn)]@ --- In GHC, however, --- @zip [x1,x2,...,xn] (y1:y2:...:yn:_|_) = (x1,y1):(x2,y2):...:(xn,yn):_|_@ --- That is, you cannot use termination of the left list to avoid hitting --- bottom in the right list. - --- This deviation is necessary to make fusion with 'build' in the right --- list preserve semantics. +-- 'zip' is right-lazy: +-- +-- > zip [] _|_ = [] {-# NOINLINE [1] zip #-} zip :: [a] -> [b] -> [(a,b)] -zip [] !_bs = [] -- see #9495 for the ! +zip [] _bs = [] zip _as [] = [] zip (a:as) (b:bs) = (a,b) : zip as bs @@ -950,20 +949,12 @@ zip3 _ _ _ = [] -- For example, @'zipWith' (+)@ is applied to two lists to produce the -- list of corresponding sums. -- --- NOTE: GHC's implementation of @zipWith@ deviates slightly from the --- standard. In particular, Haskell 98 and Haskell 2010 require that --- @zipWith (,) [x1,x2,...,xn] (y1:y2:...:yn:_|_) = [(x1,y1),(x2,y2),...,(xn,yn)]@ --- In GHC, however, --- @zipWith (,) [x1,x2,...,xn] (y1:y2:...:yn:_|_) = (x1,y1):(x2,y2):...:(xn,yn):_|_@ --- That is, you cannot use termination of the left list to avoid hitting --- bottom in the right list. - --- This deviation is necessary to make fusion with 'build' in the right --- list preserve semantics. - +-- 'zipWith' is right-lazy: +-- +-- > zipWith f [] _|_ = [] {-# NOINLINE [1] zipWith #-} zipWith :: (a->b->c) -> [a]->[b]->[c] -zipWith _f [] !_bs = [] -- see #9495 for the ! +zipWith _f [] _bs = [] zipWith _f _as [] = [] zipWith f (a:as) (b:bs) = f a b : zipWith f as bs diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 0d7ebcf..89caf01 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -77,10 +77,6 @@ * Generalise `Control.Monad.{foldM,foldM_}` to `Foldable` - * `foldr2` (together with `zip` and `zipWith`) is made a bit stricter in the - second argument, so that the fusion RULES for it do not change the - semantics. (#9596) - * `scanr`, `mapAccumL` and `filterM` now take part in list fusion (#9355, #9502, #9546) From git at git.haskell.org Fri Jan 23 12:55:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 12:55:54 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Improve documentation of pattern synonyms, to reflect conclusion of Trac #9953 (53af4bb) Message-ID: <20150123125554.DF2FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/53af4bb5cd4531f0615a2a60b6d213495261e41a/ghc >--------------------------------------------------------------- commit 53af4bb5cd4531f0615a2a60b6d213495261e41a Author: Simon Peyton Jones Date: Mon Jan 19 11:58:54 2015 +0000 Improve documentation of pattern synonyms, to reflect conclusion of Trac #9953 (cherry picked from commit 8e774ba1c0fb38a1e01d156734c8a1acf0b1e59b) >--------------------------------------------------------------- 53af4bb5cd4531f0615a2a60b6d213495261e41a docs/users_guide/glasgow_exts.xml | 145 ++++++++++++++++++++++++-------------- 1 file changed, 92 insertions(+), 53 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 9c095bc..0221421 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -1072,90 +1072,129 @@ would bring into scope the data constructor Just from the Given a pattern synonym definition of the form - pattern P var1 var2 ... varN <- pat - it is assigned a pattern type of the form - pattern P :: CProv => CReq => t1 -> t2 -> ... -> tN -> t - where CProv and CReq are type contexts, and t1, t2, ..., tN and t are - types. If CReq is empty - (()) it can be omitted. - - - -A pattern synonym of this type can be used in a pattern if the -instatiated (monomorphic) type satisfies the constraints of -CReq. In this case, it extends the context -available in the right-hand side of the match with -CProv, just like how an existentially-typed -data constructor can extend the context. - - - -For example, in the following program: - + types. +Notice the unusual form of the type, with two contexts CProv and CReq: + +CReq are the constraints required to match the pattern. +CProv are the constraints made available (provided) +by a successful pattern match. + +For example, consider -{-# LANGUAGE PatternSynonyms, GADTs #-} -module ShouldCompile where - data T a where - MkT :: (Show b) => a -> b -> T a - -pattern ExNumPat x = MkT 42 x - + MkT :: (Show b) => a -> b -> T a - -the inferred pattern type of ExNumPat is - +f1 :: (Eq a, Num a) => MkT a -> String +f1 (MkT 42 x) = show x - pattern ExNumPat :: (Show b) => (Num a, Eq a) => b -> T a - +pattern ExNumPat x = MkT 42 x +f2 :: (Eq a, Num a) => MkT a -> String +f2 (ExNumPat x) = show x + +Here f1 does not use pattern synonyms. To match against the +numeric pattern 42 requires the caller to +satisfy the constraints (Num a, Eq a), +so they appear in f1's type. The call to show generates a (Show b) +constraint, where b is an existentially type variable bound by the pattern match +on MkT. But the same pattern match also provides the constraint +(Show b) (see MkT's type), and so all is well. + - and so can be used in a function definition like the following: +Exactly the same reasoning applies to ExNumPat: +matching against ExNumPat requires +the constraints (Num a, Eq a), and provides +the constraint (Show b). + +Note also the following points + + +In the common case where CReq is empty, + (), it can be omitted altogether. + + +You may specify an explicit pattern signature, as +we did for ExNumPat above, to specify the type of a pattern, +just as you can for a function. As usual, the type signature can be less polymorphic +than the inferred type. For example - f :: (Num t, Eq t) => T t -> String - f (ExNumPat x) = show x + -- Inferred type would be 'a -> [a]' + pattern SinglePair :: (a, a) -> [(a, a)] + pattern SinglePair x = [x] + - - For bidirectional pattern synonyms, uses as expressions have the type - + +The GHCi :info command shows pattern types in this format. + + + +For a bidirectional pattern synonym, a use of the pattern synonym as an expression has the type (CProv, CReq) => t1 -> t2 -> ... -> tN -> t - - - So in the previous example, ExNumPat, - when used in an expression, has type - + So in the previous example, when used in an expression, ExNumPat has type ExNumPat :: (Show b, Num a, Eq a) => b -> T t - - - - Pattern synonyms can also be given a type signature in the source - program, e.g.: - +Notice that this is a tiny bit more restrictive than the expression MkT 42 x +which would not require (Eq a). + + +Consider these two pattern synonyms: - -- Inferred type would be 'a -> [a]' - pattern SinglePair :: (a, a) -> [(a, a)] - pattern SinglePair x = [x] +data S a where + S1 :: Bool -> S Bool + +pattern P1 b = Just b -- P1 :: Bool -> Maybe Bool +pattern P2 b = S1 b -- P2 :: (b~Bool) => Bool -> S b + +f :: Maybe a -> String +f (P1 x) = "no no no" -- Type-incorrect + +g :: S a -> String +g (P2 b) = "yes yes yes" -- Fine +Pattern P1 can only match against a value of type Maybe Bool, +so function f is rejected because the type signature is Maybe a. +(To see this, imagine expanding the pattern synonym.) + + +On the other hand, function g works fine, becuase matching against P2 +(which wraps the GADT S) provides the local equality (a~Bool). +If you were to give an explicit pattern signature P2 :: Bool -> S Bool, then P2 +would become less polymorphic, and would behave exactly like P1 so that g +would then be rejected. + + +In short, if you want GADT-like behaviour for pattern synonyms, +then (unlike unlike concrete data constructors like S1) +you must write its type with explicit provided equalities. +For a concrete data construoctr like S1 you can write +its type signature as eigher S1 :: Bool -> S Bool or +S1 :: (b~Bool) => Bool -> S b; the two are equivalent. +Not so for pattern synonyms: the two forms are different, in order to +distinguish the two cases above. (See Trac #9953 for +discussion of this choice.) + + + + Matching of pattern synonyms @@ -1173,7 +1212,7 @@ f (Pair True True) = True f _ = False f' [x, y] | True <- x, True <- y = True -f' _ = False +f' _ = False From git at git.haskell.org Fri Jan 23 12:55:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 12:55:58 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Make the linker_unload test less fragile (7f9704f) Message-ID: <20150123125558.010113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/7f9704f49525e0e0ec556f5d003914e66b11e437/ghc >--------------------------------------------------------------- commit 7f9704f49525e0e0ec556f5d003914e66b11e437 Author: Simon Marlow Date: Tue Jan 20 03:59:25 2015 -0800 Make the linker_unload test less fragile Summary: Now it invokes the GHC API to load packages, rather than trying to do it manually. This should fix most of the issues we've had with this test, and might make it work on Windows too. (cherry picked from commit 6108d95a73f93d486223064ad72bf6bedc116cbd) >--------------------------------------------------------------- 7f9704f49525e0e0ec556f5d003914e66b11e437 testsuite/tests/rts/LinkerUnload.hs | 20 ++++++++++++++++++ testsuite/tests/rts/Makefile | 21 ++----------------- testsuite/tests/rts/linker_unload.c | 35 ++++---------------------------- testsuite/tests/rts/linker_unload.stdout | 4 +++- 4 files changed, 29 insertions(+), 51 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7f9704f49525e0e0ec556f5d003914e66b11e437 From git at git.haskell.org Fri Jan 23 12:56:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 12:56:00 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Respect package visibility when deciding wired in packages. (57df7b3) Message-ID: <20150123125600.9BF073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/57df7b312c408338401140474f5afc6951d49cf9/ghc >--------------------------------------------------------------- commit 57df7b312c408338401140474f5afc6951d49cf9 Author: Edward Z. Yang Date: Mon Jan 19 10:23:46 2015 -0800 Respect package visibility when deciding wired in packages. Summary: Previously, we would consider ALL versions of a wired-in package, no matter if they were exposed or not, and pick the latest version. This patch is a minor refinement on the behavior: now we try to pick the wired in package from just the list of exposed packages, and if there are no candidates fall back on the full list. This means that if you do: -hide-all-packages -package wired-in-OLD-VERSION it will actually work by default (whereas previously you needed to *explicitly* -ignore-package the newer version). This is especially useful for the 'ghc' package. Fixes #9955. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D603 GHC Trac Issues: #9955 (cherry picked from commit 1f1595195443700b7c2708fa903969fa2f0a927b) >--------------------------------------------------------------- 57df7b312c408338401140474f5afc6951d49cf9 compiler/main/Packages.hs | 84 ++++++++++++++++++++++++++--------------------- 1 file changed, 47 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 57df7b312c408338401140474f5afc6951d49cf9 From git at git.haskell.org Fri Jan 23 15:24:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 15:24:14 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Improve HsBang (bba041e) Message-ID: <20150123152414.43F2A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/bba041e05562080cc8bea29b6a3bda572705c56b/ghc >--------------------------------------------------------------- commit bba041e05562080cc8bea29b6a3bda572705c56b Author: Simon Peyton Jones Date: Thu Jan 8 15:54:39 2015 +0000 Improve HsBang Provoked by questions from Johan - Improve comments, fix misleading stuff - Add commented synonyms for HsSrcBang, HsImplBang, and use them throughout - Rename HsUserBang to HsSrcBang - Rename dataConStrictMarks to dataConSrcBangs dataConRepBangs to dataConImplBangs This renaming affects Haddock in a trivial way, hence submodule update (cherry picked from commit 9564bb8c84cbc0397a414e946cc8c28801f0fbe7) >--------------------------------------------------------------- bba041e05562080cc8bea29b6a3bda572705c56b compiler/basicTypes/DataCon.hs | 105 ++++++++++++++++--------- compiler/basicTypes/MkId.hs | 30 +++---- compiler/deSugar/DsMeta.hs | 6 +- compiler/hsSyn/Convert.hs | 4 +- compiler/hsSyn/HsTypes.hs | 10 +-- compiler/iface/BuildTyCl.hs | 2 +- compiler/iface/MkIface.hs | 6 +- compiler/main/GHC.hs | 2 +- compiler/parser/Parser.y | 10 +-- compiler/typecheck/TcExpr.hs | 2 +- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcSplice.hs | 16 ++-- compiler/typecheck/TcTyClsDecls.hs | 10 +-- compiler/vectorise/Vectorise/Type/TyConDecl.hs | 2 +- utils/haddock | 2 +- 15 files changed, 119 insertions(+), 90 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bba041e05562080cc8bea29b6a3bda572705c56b From git at git.haskell.org Fri Jan 23 15:24:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 15:24:17 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Return a [HsImplBang] from dataConImplBangs even with NoDataConRep (ccb7d96) Message-ID: <20150123152417.0A1D53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/ccb7d96da42663407f1cd73355821ca5a7f55e7f/ghc >--------------------------------------------------------------- commit ccb7d96da42663407f1cd73355821ca5a7f55e7f Author: Simon Peyton Jones Date: Fri Jan 9 09:46:37 2015 +0000 Return a [HsImplBang] from dataConImplBangs even with NoDataConRep This fixes Trac #9969, a new crash in T7562 that I somehow missed when fiddling with HsBang (cherry picked from commit 327ce1d336c8fbdb068be900a187f96d1c60b851) >--------------------------------------------------------------- ccb7d96da42663407f1cd73355821ca5a7f55e7f compiler/basicTypes/DataCon.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs index e77af96..3f27acd 100644 --- a/compiler/basicTypes/DataCon.hs +++ b/compiler/basicTypes/DataCon.hs @@ -830,9 +830,10 @@ dataConRepStrictness dc = case dcRep dc of dataConImplBangs :: DataCon -> [HsImplBang] -- The implementation decisions about the strictness/unpack of each -- source program argument to the data constructor -dataConImplBangs dc = case dcRep dc of - NoDataConRep -> dcSrcBangs dc - DCR { dcr_bangs = bangs } -> bangs +dataConImplBangs dc + = case dcRep dc of + NoDataConRep -> replicate (dcSourceArity dc) HsNoBang + DCR { dcr_bangs = bangs } -> bangs dataConBoxer :: DataCon -> Maybe DataConBoxer dataConBoxer (MkData { dcRep = DCR { dcr_boxer = boxer } }) = Just boxer From git at git.haskell.org Fri Jan 23 15:24:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 15:24:19 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: More comments on HsBang (5651b41) Message-ID: <20150123152419.BAFDF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/5651b41e3b39763da3580a445ae0288271ca78b7/ghc >--------------------------------------------------------------- commit 5651b41e3b39763da3580a445ae0288271ca78b7 Author: Simon Peyton Jones Date: Sun Jan 11 23:07:24 2015 +0000 More comments on HsBang In particular about the dcSrcBangs field of an imported DataCon (cherry picked from commit c506f254b8e14fe422186322a580f9f7effca7f8) >--------------------------------------------------------------- 5651b41e3b39763da3580a445ae0288271ca78b7 compiler/basicTypes/DataCon.hs | 74 ++++++++++++++++++++++++------------------ compiler/basicTypes/MkId.hs | 9 ++++- compiler/iface/BuildTyCl.hs | 2 +- compiler/iface/IfaceSyn.hs | 3 +- compiler/iface/TcIface.hs | 6 +++- 5 files changed, 58 insertions(+), 36 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5651b41e3b39763da3580a445ae0288271ca78b7 From git at git.haskell.org Fri Jan 23 15:24:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 15:24:22 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Correct typos in comments to mkDataCon (1f934a5) Message-ID: <20150123152422.612203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/1f934a5b33bc154e5fbdfc79375b066511189908/ghc >--------------------------------------------------------------- commit 1f934a5b33bc154e5fbdfc79375b066511189908 Author: Simon Peyton Jones Date: Mon Jan 12 11:19:10 2015 +0000 Correct typos in comments to mkDataCon (cherry picked from commit 0afa37aa342c5c2087b225de76afa23cc2229d9f) >--------------------------------------------------------------- 1f934a5b33bc154e5fbdfc79375b066511189908 compiler/basicTypes/DataCon.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs index 593e0ed..200bf21 100644 --- a/compiler/basicTypes/DataCon.hs +++ b/compiler/basicTypes/DataCon.hs @@ -619,8 +619,8 @@ isMarkedStrict _ = True -- All others are strict -- | Build a new data constructor mkDataCon :: Name -> Bool -- ^ Is the constructor declared infix? - -> [HsBang] -- ^ Strictness/unpack annotations, from user, of - -- (for imported DataCons) from the interface file + -> [HsBang] -- ^ Strictness/unpack annotations, from user; + -- or, for imported DataCons, from the interface file -> [FieldLabel] -- ^ Field labels for the constructor, if it is a record, -- otherwise empty -> [TyVar] -- ^ Universally quantified type variables From git at git.haskell.org Fri Jan 23 15:28:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 15:28:03 +0000 (UTC) Subject: [commit: ghc] branch 'wip/api-annot-tweaks-7.10' created Message-ID: <20150123152803.7E8EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/api-annot-tweaks-7.10 Referencing: 5b7a79780b709f4a9d1c110bb786bae1031d1614 From git at git.haskell.org Fri Jan 23 15:28:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 15:28:06 +0000 (UTC) Subject: [commit: ghc] wip/api-annot-tweaks-7.10: API Annotations tweaks. (3a7a30d) Message-ID: <20150123152806.62B063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/api-annot-tweaks-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/3a7a30d765d272f10b150c28dcc28726b513b091/ghc >--------------------------------------------------------------- commit 3a7a30d765d272f10b150c28dcc28726b513b091 Author: Alan Zimmerman Date: Thu Jan 15 13:11:21 2015 -0600 API Annotations tweaks. Summary: HsTyLit now has SourceText Update documentation of HsSyn to reflect which annotations are attached to which element. Ensure that the parser always keeps HsSCC and HsTickPragma values, to be ignored in the desugar phase if not needed Bringing in SourceText for pragmas Add Location in NPlusKPat Add Location in FunDep Make RecCon payload Located Explicitly add AnnVal to RdrName where it is compound Add Location in IPBind Add Location to name in IEThingAbs Add Maybe (Located id,Bool) to Match to track fun_id,infix This includes converting Match into a record and adding a note about why the fun_id needs to be replicated in the Match. Add Location in KindedTyVar Sort out semi-colons for parsing - import statements - stmts - decls - decls_cls - decls_inst This updates the haddock submodule. Test Plan: ./validate Reviewers: hvr, austin, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D538 (cherry picked from commit 11881ec6f8d4db881671173441df87c2457409f4) >--------------------------------------------------------------- 3a7a30d765d272f10b150c28dcc28726b513b091 compiler/basicTypes/BasicTypes.hs | 135 +++- compiler/basicTypes/DataCon.hs | 21 +- compiler/basicTypes/MkId.hs | 14 +- compiler/basicTypes/RdrName.hs | 14 + compiler/basicTypes/SrcLoc.hs | 11 + compiler/deSugar/Check.hs | 8 +- compiler/deSugar/Coverage.hs | 22 +- compiler/deSugar/Desugar.hs | 8 +- compiler/deSugar/DsArrows.hs | 9 +- compiler/deSugar/DsExpr.hs | 27 +- compiler/deSugar/DsForeign.hs | 2 +- compiler/deSugar/DsMeta.hs | 61 +- compiler/deSugar/Match.hs | 9 +- compiler/deSugar/MatchLit.hs | 6 +- compiler/ghc.mk | 2 - compiler/hsSyn/Convert.hs | 70 +- compiler/hsSyn/HsBinds.hs | 48 +- compiler/hsSyn/HsDecls.hs | 161 ++-- compiler/hsSyn/HsExpr.hs | 171 ++-- compiler/hsSyn/HsImpExp.hs | 12 +- compiler/hsSyn/HsLit.hs | 39 +- compiler/hsSyn/HsPat.hs | 23 +- compiler/hsSyn/HsTypes.hs | 69 +- compiler/hsSyn/HsUtils.hs | 18 +- compiler/main/GHC.hs | 3 +- compiler/main/HeaderInfo.hs | 3 +- compiler/main/HscMain.hs | 6 +- compiler/main/HscTypes.hs | 1 + compiler/main/InteractiveEval.hs | 1 + compiler/parser/ApiAnnotation.hs | 55 +- compiler/parser/Lexer.x | 157 ++-- compiler/parser/Parser.y | 891 ++++++++++++--------- compiler/parser/RdrHsSyn.hs | 128 +-- compiler/prelude/ForeignCall.hs | 20 +- compiler/prelude/TysWiredIn.hs | 20 +- compiler/rename/RnBinds.hs | 12 +- compiler/rename/RnExpr.hs | 14 +- compiler/rename/RnNames.hs | 24 +- compiler/rename/RnPat.hs | 14 +- compiler/rename/RnSource.hs | 86 +- compiler/rename/RnTypes.hs | 10 +- compiler/stranal/WorkWrap.hs | 6 +- compiler/typecheck/Inst.hs | 6 +- compiler/typecheck/TcAnnotations.hs | 8 +- compiler/typecheck/TcArrows.hs | 6 +- compiler/typecheck/TcBinds.hs | 20 +- compiler/typecheck/TcClassDcl.hs | 4 +- compiler/typecheck/TcExpr.hs | 12 +- compiler/typecheck/TcGenGenerics.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 42 +- compiler/typecheck/TcHsType.hs | 15 +- compiler/typecheck/TcInstDcls.hs | 4 +- compiler/typecheck/TcMatches.hs | 6 +- compiler/typecheck/TcPat.hs | 8 +- compiler/typecheck/TcPatSyn.hs | 5 +- compiler/typecheck/TcRnDriver.hs | 3 +- compiler/typecheck/TcRules.hs | 9 +- compiler/typecheck/TcSplice.hs | 12 +- compiler/typecheck/TcTyClsDecls.hs | 32 +- compiler/types/Class.hs | 10 +- compiler/types/InstEnv.hs | 6 +- compiler/utils/Binary.hs | 42 +- compiler/utils/OrdList.hs | 10 +- .../tests/ghc-api/annotations/AnnotationLet.hs | 7 +- testsuite/tests/ghc-api/annotations/Makefile | 1 + .../tests/ghc-api/annotations/annotations.stdout | 86 +- .../tests/ghc-api/annotations/parseTree.stdout | 46 +- testsuite/tests/ghc-api/landmines/landmines.stdout | 8 +- utils/haddock | 2 +- 69 files changed, 1734 insertions(+), 1089 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3a7a30d765d272f10b150c28dcc28726b513b091 From git at git.haskell.org Fri Jan 23 15:28:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 15:28:09 +0000 (UTC) Subject: [commit: ghc] wip/api-annot-tweaks-7.10: API Annotations documentation update, parsing issue, add example test (5b7a797) Message-ID: <20150123152809.910D63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/api-annot-tweaks-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/5b7a79780b709f4a9d1c110bb786bae1031d1614/ghc >--------------------------------------------------------------- commit 5b7a79780b709f4a9d1c110bb786bae1031d1614 Author: Alan Zimmerman Date: Mon Jan 19 08:15:18 2015 -0600 API Annotations documentation update, parsing issue, add example test Summary: Add a reference note to each AnnKeywordId haddock comment so GHC developers will have an idea why they are there. Add a new test to ghc-api/annotations to serve as a template for other GHC developers when they need to update the parser. It provides output which checks that each SrcSpan that an annotation is attached to actually appears in the `ParsedSource`, and lists the individual annotations. The idea is that a developer writes a version of this which parses a sample file using whatever syntax is changed in Parser.y, and can then check that all the annotations come through. Depends on D538 Test Plan: ./validate Reviewers: simonpj, hvr, austin Reviewed By: austin Subscribers: thomie, jstolarek Differential Revision: https://phabricator.haskell.org/D620 (cherry picked from commit 851ed7211fb18fea938be84c99b6389f6762b30d) >--------------------------------------------------------------- 5b7a79780b709f4a9d1c110bb786bae1031d1614 compiler/basicTypes/BasicTypes.hs | 30 ++++---- compiler/basicTypes/DataCon.hs | 2 + compiler/basicTypes/RdrName.hs | 2 + compiler/hsSyn/HsBinds.hs | 28 +++++++ compiler/hsSyn/HsDecls.hs | 51 +++++++++++- compiler/hsSyn/HsExpr.hs | 90 ++++++++++++++++++++++ compiler/hsSyn/HsImpExp.hs | 17 +++- compiler/hsSyn/HsLit.hs | 4 +- compiler/hsSyn/HsPat.hs | 24 ++++++ compiler/hsSyn/HsSyn.hs | 11 ++- compiler/hsSyn/HsTypes.hs | 60 ++++++++++++++- compiler/parser/ApiAnnotation.hs | 16 ++-- compiler/parser/Lexer.x | 14 ++-- compiler/parser/Parser.y | 5 +- compiler/prelude/ForeignCall.hs | 2 + compiler/types/Class.hs | 2 + testsuite/tests/ghc-api/annotations/.gitignore | 1 + testsuite/tests/ghc-api/annotations/Makefile | 6 +- testsuite/tests/ghc-api/annotations/all.T | 1 + .../annotations/{parseTree.hs => exampleTest.hs} | 24 ++++-- .../{parseTree.stdout => exampleTest.stdout} | 20 ++--- 21 files changed, 352 insertions(+), 58 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5b7a79780b709f4a9d1c110bb786bae1031d1614 From git at git.haskell.org Fri Jan 23 18:01:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 18:01:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: API Annotations tweaks. (1a7621a) Message-ID: <20150123180108.77DBE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/1a7621a441c0d6e67ea1b2ccbc1e1d546981be5c/ghc >--------------------------------------------------------------- commit 1a7621a441c0d6e67ea1b2ccbc1e1d546981be5c Author: Alan Zimmerman Date: Thu Jan 15 13:11:21 2015 -0600 API Annotations tweaks. Summary: HsTyLit now has SourceText Update documentation of HsSyn to reflect which annotations are attached to which element. Ensure that the parser always keeps HsSCC and HsTickPragma values, to be ignored in the desugar phase if not needed Bringing in SourceText for pragmas Add Location in NPlusKPat Add Location in FunDep Make RecCon payload Located Explicitly add AnnVal to RdrName where it is compound Add Location in IPBind Add Location to name in IEThingAbs Add Maybe (Located id,Bool) to Match to track fun_id,infix This includes converting Match into a record and adding a note about why the fun_id needs to be replicated in the Match. Add Location in KindedTyVar Sort out semi-colons for parsing - import statements - stmts - decls - decls_cls - decls_inst This updates the haddock submodule. Test Plan: ./validate Reviewers: hvr, austin, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D538 (cherry picked from commit 11881ec6f8d4db881671173441df87c2457409f4) >--------------------------------------------------------------- 1a7621a441c0d6e67ea1b2ccbc1e1d546981be5c compiler/basicTypes/BasicTypes.hs | 135 +++- compiler/basicTypes/DataCon.hs | 21 +- compiler/basicTypes/MkId.hs | 14 +- compiler/basicTypes/RdrName.hs | 14 + compiler/basicTypes/SrcLoc.hs | 11 + compiler/deSugar/Check.hs | 8 +- compiler/deSugar/Coverage.hs | 22 +- compiler/deSugar/Desugar.hs | 8 +- compiler/deSugar/DsArrows.hs | 9 +- compiler/deSugar/DsExpr.hs | 27 +- compiler/deSugar/DsForeign.hs | 2 +- compiler/deSugar/DsMeta.hs | 61 +- compiler/deSugar/Match.hs | 9 +- compiler/deSugar/MatchLit.hs | 6 +- compiler/ghc.mk | 2 - compiler/hsSyn/Convert.hs | 70 +- compiler/hsSyn/HsBinds.hs | 48 +- compiler/hsSyn/HsDecls.hs | 161 ++-- compiler/hsSyn/HsExpr.hs | 171 ++-- compiler/hsSyn/HsImpExp.hs | 12 +- compiler/hsSyn/HsLit.hs | 39 +- compiler/hsSyn/HsPat.hs | 23 +- compiler/hsSyn/HsTypes.hs | 69 +- compiler/hsSyn/HsUtils.hs | 18 +- compiler/main/GHC.hs | 3 +- compiler/main/HeaderInfo.hs | 3 +- compiler/main/HscMain.hs | 6 +- compiler/main/HscTypes.hs | 1 + compiler/main/InteractiveEval.hs | 1 + compiler/parser/ApiAnnotation.hs | 55 +- compiler/parser/Lexer.x | 157 ++-- compiler/parser/Parser.y | 891 ++++++++++++--------- compiler/parser/RdrHsSyn.hs | 128 +-- compiler/prelude/ForeignCall.hs | 20 +- compiler/prelude/TysWiredIn.hs | 20 +- compiler/rename/RnBinds.hs | 12 +- compiler/rename/RnExpr.hs | 14 +- compiler/rename/RnNames.hs | 24 +- compiler/rename/RnPat.hs | 14 +- compiler/rename/RnSource.hs | 86 +- compiler/rename/RnTypes.hs | 10 +- compiler/stranal/WorkWrap.hs | 6 +- compiler/typecheck/Inst.hs | 6 +- compiler/typecheck/TcAnnotations.hs | 8 +- compiler/typecheck/TcArrows.hs | 6 +- compiler/typecheck/TcBinds.hs | 20 +- compiler/typecheck/TcClassDcl.hs | 4 +- compiler/typecheck/TcExpr.hs | 12 +- compiler/typecheck/TcGenGenerics.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 42 +- compiler/typecheck/TcHsType.hs | 15 +- compiler/typecheck/TcInstDcls.hs | 6 +- compiler/typecheck/TcMatches.hs | 6 +- compiler/typecheck/TcPat.hs | 8 +- compiler/typecheck/TcPatSyn.hs | 5 +- compiler/typecheck/TcRnDriver.hs | 3 +- compiler/typecheck/TcRules.hs | 9 +- compiler/typecheck/TcSplice.hs | 12 +- compiler/typecheck/TcTyClsDecls.hs | 32 +- compiler/types/Class.hs | 10 +- compiler/types/InstEnv.hs | 6 +- compiler/utils/Binary.hs | 42 +- compiler/utils/OrdList.hs | 10 +- .../tests/ghc-api/annotations/AnnotationLet.hs | 7 +- testsuite/tests/ghc-api/annotations/Makefile | 1 + .../tests/ghc-api/annotations/annotations.stdout | 86 +- .../tests/ghc-api/annotations/parseTree.stdout | 46 +- testsuite/tests/ghc-api/landmines/landmines.stdout | 8 +- utils/haddock | 2 +- 69 files changed, 1735 insertions(+), 1090 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1a7621a441c0d6e67ea1b2ccbc1e1d546981be5c From git at git.haskell.org Fri Jan 23 18:01:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 18:01:11 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: API Annotations documentation update, parsing issue, add example test (5eae13b) Message-ID: <20150123180111.A21133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/5eae13b9fc4227ccd6677a97dafa979e245e1711/ghc >--------------------------------------------------------------- commit 5eae13b9fc4227ccd6677a97dafa979e245e1711 Author: Alan Zimmerman Date: Mon Jan 19 08:15:18 2015 -0600 API Annotations documentation update, parsing issue, add example test Summary: Add a reference note to each AnnKeywordId haddock comment so GHC developers will have an idea why they are there. Add a new test to ghc-api/annotations to serve as a template for other GHC developers when they need to update the parser. It provides output which checks that each SrcSpan that an annotation is attached to actually appears in the `ParsedSource`, and lists the individual annotations. The idea is that a developer writes a version of this which parses a sample file using whatever syntax is changed in Parser.y, and can then check that all the annotations come through. Depends on D538 Test Plan: ./validate Reviewers: simonpj, hvr, austin Reviewed By: austin Subscribers: thomie, jstolarek Differential Revision: https://phabricator.haskell.org/D620 (cherry picked from commit 851ed7211fb18fea938be84c99b6389f6762b30d) >--------------------------------------------------------------- 5eae13b9fc4227ccd6677a97dafa979e245e1711 compiler/basicTypes/BasicTypes.hs | 30 ++++---- compiler/basicTypes/DataCon.hs | 2 + compiler/basicTypes/RdrName.hs | 2 + compiler/hsSyn/HsBinds.hs | 28 +++++++ compiler/hsSyn/HsDecls.hs | 51 +++++++++++- compiler/hsSyn/HsExpr.hs | 90 ++++++++++++++++++++++ compiler/hsSyn/HsImpExp.hs | 17 +++- compiler/hsSyn/HsLit.hs | 4 +- compiler/hsSyn/HsPat.hs | 24 ++++++ compiler/hsSyn/HsSyn.hs | 11 ++- compiler/hsSyn/HsTypes.hs | 60 ++++++++++++++- compiler/parser/ApiAnnotation.hs | 16 ++-- compiler/parser/Lexer.x | 14 ++-- compiler/parser/Parser.y | 5 +- compiler/prelude/ForeignCall.hs | 2 + compiler/types/Class.hs | 2 + testsuite/tests/ghc-api/annotations/.gitignore | 1 + testsuite/tests/ghc-api/annotations/Makefile | 6 +- testsuite/tests/ghc-api/annotations/all.T | 1 + .../annotations/{parseTree.hs => exampleTest.hs} | 24 ++++-- .../{parseTree.stdout => exampleTest.stdout} | 20 ++--- 21 files changed, 352 insertions(+), 58 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5eae13b9fc4227ccd6677a97dafa979e245e1711 From git at git.haskell.org Fri Jan 23 18:04:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 18:04:07 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Split stripTicks into expression editing and tick collection (174082f) Message-ID: <20150123180407.D5A463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/174082ffeb69b2f9df19e7af7b63a331dd074145/ghc >--------------------------------------------------------------- commit 174082ffeb69b2f9df19e7af7b63a331dd074145 Author: Peter Wortmann Date: Mon Jan 19 07:57:19 2015 -0600 Split stripTicks into expression editing and tick collection As with stripTicksTop, this is because we often need the stripped expression but not the ticks (at least not right away). This makes a big difference for CSE, see #9961. Signed-off-by: Austin Seipp (cherry picked from commit 55199a97c020761ff4bfdc06da0042e43bede697) >--------------------------------------------------------------- 174082ffeb69b2f9df19e7af7b63a331dd074145 compiler/coreSyn/CoreLint.hs | 2 +- compiler/coreSyn/CoreUtils.hs | 55 +++++++++++++++++++++---------------- compiler/simplCore/CSE.hs | 10 ++++--- compiler/simplCore/SimplUtils.hs | 4 +-- testsuite/tests/perf/compiler/all.T | 10 +++++++ 5 files changed, 51 insertions(+), 30 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 3dca78e..5ae7a59 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -1759,7 +1759,7 @@ withoutAnnots pass guts = do -- Nuke existing ticks in module. -- TODO: Ticks in unfoldings. Maybe change unfolding so it removes -- them in absence of @Opt_Debug@? - let nukeTicks = snd . stripTicks (not . tickishIsCode) + let nukeTicks = stripTicksE (not . tickishIsCode) nukeAnnotsBind :: CoreBind -> CoreBind nukeAnnotsBind bind = case bind of Rec bs -> Rec $ map (\(b,e) -> (b, nukeTicks e)) bs diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 913dda3..7030e39 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -44,7 +44,8 @@ module CoreUtils ( dataConRepInstPat, dataConRepFSInstPat, -- * Working with ticks - stripTicksTop, stripTicksTopE, stripTicksTopT, stripTicks, + stripTicksTop, stripTicksTopE, stripTicksTopT, + stripTicksE, stripTicksT ) where #include "HsVersions.h" @@ -77,10 +78,6 @@ import Pair import Data.Function ( on ) import Data.List import Data.Ord ( comparing ) -import Control.Applicative -#if __GLASGOW_HASKELL__ < 709 -import Data.Traversable ( traverse ) -#endif import OrdList {- @@ -358,25 +355,37 @@ stripTicksTopT p = go [] -- | Completely strip ticks satisfying a predicate from an -- expression. Note this is O(n) in the size of the expression! -stripTicks :: (Tickish Id -> Bool) -> Expr b -> ([Tickish Id], Expr b) -stripTicks p expr = (fromOL ticks, expr') - where (ticks, expr') = go expr - -- Note that OrdList (Tickish Id) is a Monoid, which makes - -- ((,) (OrdList (Tickish Id))) an Applicative. - go (App e a) = App <$> go e <*> go a - go (Lam b e) = Lam b <$> go e - go (Let b e) = Let <$> go_bs b <*> go e - go (Case e b t as) = Case <$> go e <*> pure b <*> pure t - <*> traverse go_a as - go (Cast e c) = Cast <$> go e <*> pure c +stripTicksE :: (Tickish Id -> Bool) -> Expr b -> Expr b +stripTicksE p expr = go expr + where go (App e a) = App (go e) (go a) + go (Lam b e) = Lam b (go e) + go (Let b e) = Let (go_bs b) (go e) + go (Case e b t as) = Case (go e) b t (map go_a as) + go (Cast e c) = Cast (go e) c go (Tick t e) - | p t = let (ts, e') = go e in (t `consOL` ts, e') - | otherwise = Tick t <$> go e - go other = pure other - go_bs (NonRec b e) = NonRec b <$> go e - go_bs (Rec bs) = Rec <$> traverse go_b bs - go_b (b, e) = (,) <$> pure b <*> go e - go_a (c,bs,e) = (,,) <$> pure c <*> pure bs <*> go e + | p t = go e + | otherwise = Tick t (go e) + go other = other + go_bs (NonRec b e) = NonRec b (go e) + go_bs (Rec bs) = Rec (map go_b bs) + go_b (b, e) = (b, go e) + go_a (c,bs,e) = (c,bs, go e) + +stripTicksT :: (Tickish Id -> Bool) -> Expr b -> [Tickish Id] +stripTicksT p expr = fromOL $ go expr + where go (App e a) = go e `appOL` go a + go (Lam _ e) = go e + go (Let b e) = go_bs b `appOL` go e + go (Case e _ _ as) = go e `appOL` concatOL (map go_a as) + go (Cast e _) = go e + go (Tick t e) + | p t = t `consOL` go e + | otherwise = go e + go _ = nilOL + go_bs (NonRec _ e) = go e + go_bs (Rec bs) = concatOL (map go_b bs) + go_b (_, e) = go e + go_a (_, _, e) = go e {- ************************************************************************ diff --git a/compiler/simplCore/CSE.hs b/compiler/simplCore/CSE.hs index a30c695..c43cbb7 100644 --- a/compiler/simplCore/CSE.hs +++ b/compiler/simplCore/CSE.hs @@ -15,7 +15,7 @@ import Var ( Var ) import Id ( Id, idType, idInlineActivation, zapIdOccInfo ) import CoreUtils ( mkAltExpr , exprIsTrivial - , stripTicks, stripTicksTopE, mkTick, mkTicks ) + , stripTicksE, stripTicksT, stripTicksTopE, mkTick, mkTicks ) import Type ( tyConAppArgs ) import CoreSyn import Outputable @@ -190,7 +190,8 @@ cseRhs env (id',rhs) where rhs' = cseExpr env rhs - (ticks, rhs'') = stripTicks tickishFloatable rhs' + ticks = stripTicksT tickishFloatable rhs' + rhs'' = stripTicksE tickishFloatable rhs' -- We don't want to lose the source notes when a common sub -- expression gets eliminated. Hence we push all (!) of them on -- top of the replaced sub-expression. This is probably not too @@ -206,7 +207,8 @@ tryForCSE env expr | otherwise = expr' where expr' = cseExpr env expr - (ticks, expr'') = stripTicks tickishFloatable expr' + expr'' = stripTicksE tickishFloatable expr' + ticks = stripTicksT tickishFloatable expr' cseExpr :: CSEnv -> InExpr -> OutExpr cseExpr env (Type t) = Type (substTy (csEnvSubst env) t) @@ -296,7 +298,7 @@ lookupCSEnv (CS { cs_map = csmap }) expr extendCSEnv :: CSEnv -> OutExpr -> Id -> CSEnv extendCSEnv cse expr id = cse { cs_map = extendCoreMap (cs_map cse) sexpr (sexpr,id) } - where (_, sexpr) = stripTicks tickishFloatable expr + where sexpr = stripTicksE tickishFloatable expr csEnvSubst :: CSEnv -> Subst csEnvSubst = cs_subst diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs index ccc8a56..6bb290e 100644 --- a/compiler/simplCore/SimplUtils.hs +++ b/compiler/simplCore/SimplUtils.hs @@ -1658,7 +1658,7 @@ combineIdenticalAlts case_bndr ((_con1,bndrs1,rhs1) : con_alts) cheapEqTicked e1 e2 = cheapEqExpr' tickishFloatable e1 e2 identical_to_alt1 (_con,bndrs,rhs) = all isDeadBinder bndrs && rhs `cheapEqTicked` rhs1 - tickss = map (fst . stripTicks tickishFloatable . thirdOf3) eliminated_alts + tickss = map (stripTicksT tickishFloatable . thirdOf3) eliminated_alts combineIdenticalAlts _ alts = return alts @@ -1755,7 +1755,7 @@ mkCase1 _dflags scrut case_bndr _ alts@((_,_,rhs1) : _) -- Identity case = do { tick (CaseIdentity case_bndr) ; return (mkTicks ticks $ re_cast scrut rhs1) } where - ticks = concatMap (fst . stripTicks tickishFloatable . thirdOf3) (tail alts) + ticks = concatMap (stripTicksT tickishFloatable . thirdOf3) (tail alts) identity_alt (con, args, rhs) = check_eq rhs con args check_eq (Cast rhs co) con args diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index ce48c11..31b0a5a 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -601,3 +601,13 @@ test('T9872d', ], compile, ['']) + +test('T9961', + [ only_ways(['normal']), + compiler_stats_num_field('bytes allocated', + [(wordsize(64), 772510192, 5) + # 2015-01-12 807117816 Initally created + ]), + ], + compile, + ['-O']) From git at git.haskell.org Fri Jan 23 22:38:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:09 +0000 (UTC) Subject: [commit: packages/containers] branch 'strict-tuples' created Message-ID: <20150123223809.28E8A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New branch : strict-tuples Referencing: cd8d45fb8c4132a5bf56b140a40d9f37f04cfd56 From git at git.haskell.org Fri Jan 23 22:38:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:11 +0000 (UTC) Subject: [commit: packages/containers] branch 'develop-0.6' created Message-ID: <20150123223811.286D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New branch : develop-0.6 Referencing: 7ab1c399726c5a4a562cff3f56017ff5852ac82e From git at git.haskell.org Fri Jan 23 22:38:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:13 +0000 (UTC) Subject: [commit: packages/containers] branch 'develop' created Message-ID: <20150123223813.29DC03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New branch : develop Referencing: b44b6a727c123c0ec33e8ac0f1299ac73ee1d0ef From git at git.haskell.org Fri Jan 23 22:38:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:15 +0000 (UTC) Subject: [commit: packages/containers] branch 'develop-0.6-questionable' created Message-ID: <20150123223815.2A6873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New branch : develop-0.6-questionable Referencing: 2bf686d3dd0706eef416590100f8d1ebaa3eb80b From git at git.haskell.org Fri Jan 23 22:38:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:17 +0000 (UTC) Subject: [commit: packages/containers] branch 'zip-devel' created Message-ID: <20150123223817.2B3163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New branch : zip-devel Referencing: ce7f531605b5f2bb350f36c51a74d9ebd84ff8b6 From git at git.haskell.org Fri Jan 23 22:38:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:19 +0000 (UTC) Subject: [commit: packages/containers] branch 'ghc-head' deleted Message-ID: <20150123223819.2C1963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers Deleted branch: ghc-head From git at git.haskell.org Fri Jan 23 22:38:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:21 +0000 (UTC) Subject: [commit: packages/containers] tag 'containers-0.5.6.2-release' created Message-ID: <20150123223821.2D2C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New tag : containers-0.5.6.2-release Referencing: ab15b1f50d85199aebbe58c7e8efb7f3f1f09eda From git at git.haskell.org Fri Jan 23 22:38:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:23 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Add IsList instances for OverloadedLists (0e99ba8) Message-ID: <20150123223823.3D7903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/0e99ba8851f875c4b44631c7afad3b70e74842c2 >--------------------------------------------------------------- commit 0e99ba8851f875c4b44631c7afad3b70e74842c2 Author: Konstantine Rybnikov Date: Sun Apr 13 22:27:39 2014 +0200 Add IsList instances for OverloadedLists >--------------------------------------------------------------- 0e99ba8851f875c4b44631c7afad3b70e74842c2 Data/IntMap/Base.hs | 16 +++++++++++++++- Data/IntSet/Base.hs | 13 +++++++++++++ Data/Map/Base.hs | 13 +++++++++++++ Data/Set/Base.hs | 13 +++++++++++++ 4 files changed, 54 insertions(+), 1 deletion(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 34a263a..75b3ae9 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -5,6 +5,10 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +{-# LANGUAGE ScopedTypeVariables #-} +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE TypeFamilies #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.IntMap.Base @@ -231,6 +235,9 @@ import Data.StrictPair import Data.Data (Data(..), Constr, mkConstr, constrIndex, Fixity(Prefix), DataType, mkDataType) import GHC.Exts (build) +#if __GLASGOW_HASKELL__ >= 708 +import qualified GHC.Exts as GHCExts +#endif import Text.Read #endif @@ -1770,6 +1777,13 @@ fromSet f (IntSet.Tip kx bm) = buildTree f kx bm (IntSet.suffixBitMask + 1) {-------------------------------------------------------------------- Lists --------------------------------------------------------------------} +#if __GLASGOW_HASKELL__ >= 708 +instance GHCExts.IsList (IntMap a) where + type Item (IntMap a) = (Key,a) + fromList = fromList + toList = toList +#endif + -- | /O(n)/. Convert the map to a list of key\/value pairs. Subject to list -- fusion. -- @@ -1907,7 +1921,7 @@ fromAscListWithKey f (x0 : xs0) = fromDistinctAscList (combineEq x0 xs0) -- -- > fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")] -fromDistinctAscList :: [(Key,a)] -> IntMap a +fromDistinctAscList :: forall a. [(Key,a)] -> IntMap a fromDistinctAscList [] = Nil fromDistinctAscList (z0 : zs0) = work z0 zs0 Nada where diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index be41db5..0063c3f 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -5,6 +5,9 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE TypeFamilies #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.IntSet.Base @@ -198,6 +201,9 @@ import Text.Read #if __GLASGOW_HASKELL__ import GHC.Exts (Int(..), build) +#if __GLASGOW_HASKELL__ >= 708 +import qualified GHC.Exts as GHCExts +#endif import GHC.Prim (indexInt8OffAddr#) #endif @@ -936,6 +942,13 @@ elems {-------------------------------------------------------------------- Lists --------------------------------------------------------------------} +#if __GLASGOW_HASKELL__ >= 708 +instance GHCExts.IsList IntSet where + type Item IntSet = Key + fromList = fromList + toList = toList +#endif + -- | /O(n)/. Convert the set to a list of elements. Subject to list fusion. toList :: IntSet -> [Key] toList diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 6a93a73..69f8276 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -5,6 +5,9 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE TypeFamilies #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.Map.Base @@ -278,6 +281,9 @@ import qualified Data.Set.Base as Set #if __GLASGOW_HASKELL__ import GHC.Exts ( build ) +#if __GLASGOW_HASKELL__ >= 708 +import qualified GHC.Exts as GHCExts +#endif import Text.Read import Data.Data #endif @@ -1948,6 +1954,13 @@ fromSet f (Set.Bin sz x l r) = Bin sz x (f x) (fromSet f l) (fromSet f r) Lists use [foldlStrict] to reduce demand on the control-stack --------------------------------------------------------------------} +#if __GLASGOW_HASKELL__ >= 708 +instance (Ord k) => GHCExts.IsList (Map k v) where + type Item (Map k v) = (k,v) + fromList = fromList + toList = toList +#endif + -- | /O(n*log n)/. Build a map from a list of key\/value pairs. See also 'fromAscList'. -- If the list contains more than one value for the same key, the last value -- for the key is retained. diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index f863d17..94372df 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -5,6 +5,9 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE TypeFamilies #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.Set.Base @@ -194,6 +197,9 @@ import Data.StrictPair #if __GLASGOW_HASKELL__ import GHC.Exts ( build ) +#if __GLASGOW_HASKELL__ >= 708 +import qualified GHC.Exts as GHCExts +#endif import Text.Read import Data.Data #endif @@ -763,6 +769,13 @@ elems = toAscList {-------------------------------------------------------------------- Lists --------------------------------------------------------------------} +#if __GLASGOW_HASKELL__ >= 708 +instance (Ord a) => GHCExts.IsList (Set a) where + type Item (Set a) = a + fromList = fromList + toList = toList +#endif + -- | /O(n)/. Convert the set to a list of elements. Subject to list fusion. toList :: Set a -> [a] toList = toAscList From git at git.haskell.org Fri Jan 23 22:38:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:25 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Add LANGUAGE RoleAnnotations for ghc 7.8 (cb08a7e) Message-ID: <20150123223825.476583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/cb08a7e06676d38f2f5deb35d0035429c1c10eb1 >--------------------------------------------------------------- commit cb08a7e06676d38f2f5deb35d0035429c1c10eb1 Author: Konstantine Rybnikov Date: Sun Apr 13 23:52:57 2014 +0200 Add LANGUAGE RoleAnnotations for ghc 7.8 >--------------------------------------------------------------- cb08a7e06676d38f2f5deb35d0035429c1c10eb1 Data/Map/Base.hs | 3 +++ Data/Set/Base.hs | 3 +++ 2 files changed, 6 insertions(+) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 6a93a73..95f7b91 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -5,6 +5,9 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.Map.Base diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index f863d17..da3b21d 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -5,6 +5,9 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.Set.Base From git at git.haskell.org Fri Jan 23 22:38:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:27 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #42 from k-bx/add-role-annotations-lang (0098d41) Message-ID: <20150123223827.517213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/0098d41f0aa0460f96eb2251ac743bb7fa137a68 >--------------------------------------------------------------- commit 0098d41f0aa0460f96eb2251ac743bb7fa137a68 Merge: e787f05 cb08a7e Author: Johan Tibell Date: Mon Apr 14 07:01:33 2014 +0100 Merge pull request #42 from k-bx/add-role-annotations-lang Add LANGUAGE RoleAnnotations for ghc 7.8 >--------------------------------------------------------------- 0098d41f0aa0460f96eb2251ac743bb7fa137a68 Data/Map/Base.hs | 3 +++ Data/Set/Base.hs | 3 +++ 2 files changed, 6 insertions(+) From git at git.haskell.org Fri Jan 23 22:38:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:29 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Merge language pragmas (bae098f) Message-ID: <20150123223829.5E1393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/bae098fb0a3994bc2b0ec3313004b40cd097ed8d >--------------------------------------------------------------- commit bae098fb0a3994bc2b0ec3313004b40cd097ed8d Merge: 0098d41 0e99ba8 Author: Johan Tibell Date: Mon Apr 14 08:20:44 2014 +0200 Merge language pragmas >--------------------------------------------------------------- bae098fb0a3994bc2b0ec3313004b40cd097ed8d Data/IntMap/Base.hs | 16 +++++++++++++++- Data/IntSet/Base.hs | 13 +++++++++++++ Data/Map/Base.hs | 11 +++++++++++ Data/Set/Base.hs | 11 +++++++++++ 4 files changed, 50 insertions(+), 1 deletion(-) diff --cc Data/Map/Base.hs index 95f7b91,69f8276..db9549f --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@@ -6,7 -6,7 +6,8 @@@ {-# LANGUAGE Trustworthy #-} #endif #if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} + {-# LANGUAGE TypeFamilies #-} #endif ----------------------------------------------------------------------------- -- | diff --cc Data/Set/Base.hs index da3b21d,94372df..ffcdfd0 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@@ -6,7 -6,7 +6,8 @@@ {-# LANGUAGE Trustworthy #-} #endif #if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} + {-# LANGUAGE TypeFamilies #-} #endif ----------------------------------------------------------------------------- -- | From git at git.haskell.org Fri Jan 23 22:38:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:31 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Don't have tests depend on library to avoid dep conflicts (53da0d5) Message-ID: <20150123223831.6557B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/53da0d55d8592d86772691322cc7eebae511e29e >--------------------------------------------------------------- commit 53da0d55d8592d86772691322cc7eebae511e29e Author: Johan Tibell Date: Wed Apr 23 08:50:44 2014 +0200 Don't have tests depend on library to avoid dep conflicts >--------------------------------------------------------------- 53da0d55d8592d86772691322cc7eebae511e29e containers.cabal | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/containers.cabal b/containers.cabal index 8abca7a..640cb5e 100644 --- a/containers.cabal +++ b/containers.cabal @@ -211,14 +211,13 @@ Test-suite seq-properties test-framework-quickcheck2 test-suite map-strictness-properties - hs-source-dirs: tests + hs-source-dirs: tests, . main-is: MapStrictness.hs type: exitcode-stdio-1.0 build-depends: base, ChasingBottoms, - containers, QuickCheck >= 2.4.0.1, test-framework >= 0.3.3, test-framework-quickcheck2 >= 0.2.9 @@ -226,14 +225,13 @@ test-suite map-strictness-properties ghc-options: -Wall test-suite intmap-strictness-properties - hs-source-dirs: tests + hs-source-dirs: tests, . main-is: IntMapStrictness.hs type: exitcode-stdio-1.0 build-depends: base, ChasingBottoms, - containers, QuickCheck >= 2.4.0.1, test-framework >= 0.3.3, test-framework-quickcheck2 >= 0.2.9 From git at git.haskell.org Fri Jan 23 22:38:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:33 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Add missing test dependencies (c17cfaf) Message-ID: <20150123223833.6BE783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c17cfaf7996942ed305dc1db55ea82da40ed47e4 >--------------------------------------------------------------- commit c17cfaf7996942ed305dc1db55ea82da40ed47e4 Author: Johan Tibell Date: Wed Apr 23 09:25:40 2014 +0200 Add missing test dependencies >--------------------------------------------------------------- c17cfaf7996942ed305dc1db55ea82da40ed47e4 containers.cabal | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/containers.cabal b/containers.cabal index 640cb5e..209589b 100644 --- a/containers.cabal +++ b/containers.cabal @@ -216,9 +216,12 @@ test-suite map-strictness-properties type: exitcode-stdio-1.0 build-depends: - base, + array, + base >= 4.2 && < 5, ChasingBottoms, + deepseq >= 1.2 && < 1.4, QuickCheck >= 2.4.0.1, + ghc-prim, test-framework >= 0.3.3, test-framework-quickcheck2 >= 0.2.9 @@ -230,9 +233,12 @@ test-suite intmap-strictness-properties type: exitcode-stdio-1.0 build-depends: - base, + array, + base >= 4.2 && < 5, ChasingBottoms, + deepseq >= 1.2 && < 1.4, QuickCheck >= 2.4.0.1, + ghc-prim, test-framework >= 0.3.3, test-framework-quickcheck2 >= 0.2.9 From git at git.haskell.org Fri Jan 23 22:38:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:35 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Add Travis-CI job control file (234896a) Message-ID: <20150123223835.742783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/234896a2bb2c1f57f033b1f19f38ef039e99fe1e >--------------------------------------------------------------- commit 234896a2bb2c1f57f033b1f19f38ef039e99fe1e Author: Herbert Valerio Riedel Date: Tue Apr 22 22:48:36 2014 +0200 Add Travis-CI job control file This builds and tests containers with GHC 7.0, 7.4, 7.6, 7.8, and GHC HEAD (Once haskell/cabal#1806 is fixed we can use CABALVER=1.20 w/ GHCVER=7.8.2) >--------------------------------------------------------------- 234896a2bb2c1f57f033b1f19f38ef039e99fe1e .travis.yml | 60 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 60 insertions(+) diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..67d893c --- /dev/null +++ b/.travis.yml @@ -0,0 +1,60 @@ +# NB: don't set `language: haskell` here + +# See also https://github.com/hvr/multi-ghc-travis for more information +env: + - GHCVER=7.0.4 CABALVER=1.16 + # we have to use CABALVER=1.16 for GHC<7.6 as well, as there's + # no package for earlier cabal versions in the PPA + - GHCVER=7.4.2 CABALVER=1.16 + - GHCVER=7.6.3 CABALVER=1.16 + - GHCVER=7.8.2 CABALVER=1.18 + # NOTE: we can't use Cabal 1.20 yet due to + # https://github.com/haskell/cabal/issues/1806 + - GHCVER=head CABALVER=1.18 + +matrix: + allow_failures: + - env: GHCVER=head CABALVER=1.18 + +# Note: the distinction between `before_install` and `install` is not +# important. +before_install: + - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH + - cabal --version + +install: + - travis_retry cabal update + - cabal install --only-dependencies + # we need to install the test-suite deps manually as the cabal solver would + # otherwise complaing about cyclic deps + - cabal install 'test-framework >= 0.3.3' 'test-framework-quickcheck2 >= 0.2.9' 'QuickCheck >= 2.4.0.1' 'ChasingBottoms' 'HUnit' 'test-framework-hunit' + +# Here starts the actual work to be performed for the package under +# test; any command which exits with a non-zero exit code causes the +# build to fail. +script: + # -v2 provides useful information for debugging + - cabal configure -v2 --enable-tests + + # this builds all libraries and executables + # (including tests/benchmarks) + - cabal build + - cabal test + + # tests that a source-distribution can be generated + - cabal sdist + + # check that the generated source-distribution can be built & installed + - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; + cd dist/; + if [ -f "$SRC_TGZ" ]; then + cabal install --force-reinstalls "$SRC_TGZ"; + else + echo "expected '$SRC_TGZ' not found"; + exit 1; + fi + +# EOF From git at git.haskell.org Fri Jan 23 22:38:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:37 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Markdownify and extend README (7d8360a) Message-ID: <20150123223837.7AFCC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/7d8360ac1e3a484bae714b5253e287a0f77b80c3 >--------------------------------------------------------------- commit 7d8360ac1e3a484bae714b5253e287a0f77b80c3 Author: Herbert Valerio Riedel Date: Wed Apr 23 12:42:06 2014 +0200 Markdownify and extend README >--------------------------------------------------------------- 7d8360ac1e3a484bae714b5253e287a0f77b80c3 README | 6 ------ README.md | 12 ++++++++++++ 2 files changed, 12 insertions(+), 6 deletions(-) diff --git a/README b/README deleted file mode 100644 index 1fb326b..0000000 --- a/README +++ /dev/null @@ -1,6 +0,0 @@ -POTENTIAL CONTRIBUTORS -====================== - -Please follow the guidelines outlined on the Haskell Wiki when proposing an API change. - -http://www.haskell.org/haskellwiki/Library_submissions#Guidance_for_proposers diff --git a/README.md b/README.md new file mode 100644 index 0000000..0eab2ca --- /dev/null +++ b/README.md @@ -0,0 +1,12 @@ +The `containers` Package [![Build Status](https://travis-ci.org/haskell/containers.svg?branch=master)](https://travis-ci.org/haskell/containers) +======================== + +See [`containers` on Hackage](http://hackage.haskell.org/package/containers) for more information. + + +Contributing +------------ + +For reporting bugs (and maybe even the respective fix), please use the [GitHub issue tracker](https://github.com/haskell/containers/issues). + +For proposing API changes/enhancements, please follow the [guidelines outlined on the Haskell Wiki](http://www.haskell.org/haskellwiki/Library_submissions#Guidance_for_proposers) (but use the GitHub facilities instead of GHC's Trac for submitting patches). From git at git.haskell.org Fri Jan 23 22:38:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:39 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Try to use CABALVER=1.20 again (e5d74fa) Message-ID: <20150123223839.824363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/e5d74fa883ef2d66511d12cdb62b9586abff14c5 >--------------------------------------------------------------- commit e5d74fa883ef2d66511d12cdb62b9586abff14c5 Author: Herbert Valerio Riedel Date: Sat May 3 17:45:13 2014 +0200 Try to use CABALVER=1.20 again ...hoping that haskell/cabal#1806 has been resolved for good >--------------------------------------------------------------- e5d74fa883ef2d66511d12cdb62b9586abff14c5 .travis.yml | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 67d893c..8af3116 100644 --- a/.travis.yml +++ b/.travis.yml @@ -8,13 +8,11 @@ env: - GHCVER=7.4.2 CABALVER=1.16 - GHCVER=7.6.3 CABALVER=1.16 - GHCVER=7.8.2 CABALVER=1.18 - # NOTE: we can't use Cabal 1.20 yet due to - # https://github.com/haskell/cabal/issues/1806 - - GHCVER=head CABALVER=1.18 + - GHCVER=head CABALVER=1.20 matrix: allow_failures: - - env: GHCVER=head CABALVER=1.18 + - env: GHCVER=head CABALVER=1.20 # Note: the distinction between `before_install` and `install` is not # important. From git at git.haskell.org Fri Jan 23 22:38:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:41 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: tree: Fix imports for the Applicative/Monad change (c40e6dd) Message-ID: <20150123223841.890413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c40e6dd40861d788ee0cc337775d803d8907b6ff >--------------------------------------------------------------- commit c40e6dd40861d788ee0cc337775d803d8907b6ff Author: Austin Seipp Date: Mon May 12 07:31:59 2014 -0500 tree: Fix imports for the Applicative/Monad change Due to various problems with orphans and cycles in base, while implementing the Applicative/Monad Proposal, Alternative joined MonadPlus in Control.Monad. A knock-on effect of this is that Control.Monad now exports 'empty', which conflicts with Data.Sequence in this case. Luckily the fix is actually quite easy: just restrict the imports to liftM, since that's all we use anyway. Signed-off-by: Austin Seipp >--------------------------------------------------------------- c40e6dd40861d788ee0cc337775d803d8907b6ff Data/Tree.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Tree.hs b/Data/Tree.hs index 56af20f..dab25c2 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -32,7 +32,7 @@ module Data.Tree( ) where import Control.Applicative (Applicative(..), (<$>)) -import Control.Monad +import Control.Monad (liftM) import Data.Monoid (Monoid(..)) import Data.Sequence (Seq, empty, singleton, (<|), (|>), fromList, ViewL(..), ViewR(..), viewl, viewr) From git at git.haskell.org Fri Jan 23 22:38:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:43 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #44 from thoughtpolice/amp (e84c5d2) Message-ID: <20150123223843.9099C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/e84c5d2145415cb0beacce0909a551ae5e28d396 >--------------------------------------------------------------- commit e84c5d2145415cb0beacce0909a551ae5e28d396 Merge: e5d74fa c40e6dd Author: Milan Straka Date: Mon May 12 15:05:18 2014 +0200 Merge pull request #44 from thoughtpolice/amp tree: Fix imports for the Applicative/Monad change >--------------------------------------------------------------- e84c5d2145415cb0beacce0909a551ae5e28d396 Data/Tree.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:38:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:45 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Added fixity declarations for member, notMember, union, and intersection. (3999b51) Message-ID: <20150123223845.9C6873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/3999b512f5aa28a7b119a18b286a8485d1285319 >--------------------------------------------------------------- commit 3999b512f5aa28a7b119a18b286a8485d1285319 Author: Peter Selinger Date: Fri Jul 4 10:31:20 2014 -0300 Added fixity declarations for member, notMember, union, and intersection. >--------------------------------------------------------------- 3999b512f5aa28a7b119a18b286a8485d1285319 Data/IntMap/Base.hs | 8 ++++++++ Data/IntSet/Base.hs | 7 +++++++ Data/Map/Base.hs | 8 ++++++++ Data/Set/Base.hs | 8 ++++++++ 4 files changed, 31 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 75b3ae9..9f7be70 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,6 +395,8 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the key not a member of the map? -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -403,6 +405,8 @@ member k = k `seq` go notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m +infix 4 notMember + -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. -- See Note: Local 'go' functions and capturing] @@ -818,6 +822,8 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 +infixl 5 union + -- | /O(n+m)/. The union with a combining function. -- -- > unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")] @@ -881,6 +887,8 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 +infixl 5 intersection + -- | /O(n+m)/. The intersection with a combining function. -- -- > intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA" diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 0063c3f..9719de1 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,10 +332,14 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -523,6 +527,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t +infixl 5 union {-------------------------------------------------------------------- Difference @@ -597,6 +602,8 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil +infixl 5 intersection + {-------------------------------------------------------------------- Subset --------------------------------------------------------------------} diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index db9549f..9d066fa 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,6 +456,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -469,6 +471,8 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. find :: Ord k => k -> Map k a -> a @@ -1230,6 +1234,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b hedgeUnion _ _ t1 Tip = t1 @@ -1350,6 +1356,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index ffcdfd0..5727de6 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,6 +318,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool notMember a t = not $ member a t @@ -327,6 +329,8 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -578,6 +582,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 hedgeUnion blo bhi Tip (Bin _ x l r) = link x (filterGt blo l) (filterLt bhi r) @@ -636,6 +642,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip From git at git.haskell.org Fri Jan 23 22:38:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:47 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Fixed syntax of fixity declarations. (07ab0fa) Message-ID: <20150123223847.A8AB33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/07ab0fa052843dc8fd4c874876d03d8a71525f87 >--------------------------------------------------------------- commit 07ab0fa052843dc8fd4c874876d03d8a71525f87 Author: Peter Selinger Date: Fri Jul 4 10:47:35 2014 -0300 Fixed syntax of fixity declarations. >--------------------------------------------------------------- 07ab0fa052843dc8fd4c874876d03d8a71525f87 Data/IntMap/Base.hs | 8 ++++---- Data/IntSet/Base.hs | 8 ++++---- Data/Map/Base.hs | 8 ++++---- Data/Set/Base.hs | 8 ++++---- 4 files changed, 16 insertions(+), 16 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 9f7be70..237aea8 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,7 +395,7 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the key not a member of the map? -- @@ -405,7 +405,7 @@ infix 4 member notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 notMember +infix 4 `notMember` -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. @@ -822,7 +822,7 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 union +infixl 5 `union` -- | /O(n+m)/. The union with a combining function. -- @@ -887,7 +887,7 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 intersection +infixl 5 `intersection` -- | /O(n+m)/. The intersection with a combining function. -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 9719de1..5aee4ef 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,13 +332,13 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -527,7 +527,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 union +infixl 5 `union` {-------------------------------------------------------------------- Difference @@ -602,7 +602,7 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 intersection +infixl 5 `intersection` {-------------------------------------------------------------------- Subset diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 9d066fa..bc2fd47 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,7 +456,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- @@ -471,7 +471,7 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. @@ -1234,7 +1234,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b @@ -1356,7 +1356,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 5727de6..d0533f5 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,7 +318,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool @@ -329,7 +329,7 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -582,7 +582,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 @@ -642,7 +642,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip From git at git.haskell.org Fri Jan 23 22:38:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:49 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Revert "Fixed syntax of fixity declarations." (fa2c888) Message-ID: <20150123223849.B31CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/fa2c8880efd7adf81e33de72f1a38a0c2b31e90b >--------------------------------------------------------------- commit fa2c8880efd7adf81e33de72f1a38a0c2b31e90b Author: Johan Tibell Date: Tue Jul 22 17:09:30 2014 +0200 Revert "Fixed syntax of fixity declarations." This reverts commit 07ab0fa052843dc8fd4c874876d03d8a71525f87. >--------------------------------------------------------------- fa2c8880efd7adf81e33de72f1a38a0c2b31e90b Data/IntMap/Base.hs | 8 ++++---- Data/IntSet/Base.hs | 8 ++++---- Data/Map/Base.hs | 8 ++++---- Data/Set/Base.hs | 8 ++++---- 4 files changed, 16 insertions(+), 16 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 237aea8..9f7be70 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,7 +395,7 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 `member` +infix 4 member -- | /O(min(n,W))/. Is the key not a member of the map? -- @@ -405,7 +405,7 @@ infix 4 `member` notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 `notMember` +infix 4 notMember -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. @@ -822,7 +822,7 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 `union` +infixl 5 union -- | /O(n+m)/. The union with a combining function. -- @@ -887,7 +887,7 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 `intersection` +infixl 5 intersection -- | /O(n+m)/. The intersection with a combining function. -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 5aee4ef..9719de1 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,13 +332,13 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 `member` +infix 4 member -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k -infix 4 `notMember` +infix 4 notMember -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -527,7 +527,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 `union` +infixl 5 union {-------------------------------------------------------------------- Difference @@ -602,7 +602,7 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 `intersection` +infixl 5 intersection {-------------------------------------------------------------------- Subset diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index bc2fd47..9d066fa 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,7 +456,7 @@ member = go {-# INLINE member #-} #endif -infix 4 `member` +infix 4 member -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- @@ -471,7 +471,7 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 `notMember` +infix 4 notMember -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. @@ -1234,7 +1234,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 `union` +infixl 5 union -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b @@ -1356,7 +1356,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 `intersection` +infixl 5 intersection hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index d0533f5..5727de6 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,7 +318,7 @@ member = go {-# INLINE member #-} #endif -infix 4 `member` +infix 4 member -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool @@ -329,7 +329,7 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 `notMember` +infix 4 notMember -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -582,7 +582,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 `union` +infixl 5 union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 @@ -642,7 +642,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 `intersection` +infixl 5 intersection hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip From git at git.haskell.org Fri Jan 23 22:38:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:51 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Revert "Added fixity declarations for member, notMember, union, and intersection." (3b1eee5) Message-ID: <20150123223851.BF2043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/3b1eee514581edcc51c3c4304087e2dff30e05cd >--------------------------------------------------------------- commit 3b1eee514581edcc51c3c4304087e2dff30e05cd Author: Johan Tibell Date: Tue Jul 22 17:09:50 2014 +0200 Revert "Added fixity declarations for member, notMember, union, and intersection." This reverts commit 3999b512f5aa28a7b119a18b286a8485d1285319. >--------------------------------------------------------------- 3b1eee514581edcc51c3c4304087e2dff30e05cd Data/IntMap/Base.hs | 8 -------- Data/IntSet/Base.hs | 7 ------- Data/Map/Base.hs | 8 -------- Data/Set/Base.hs | 8 -------- 4 files changed, 31 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 9f7be70..75b3ae9 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,8 +395,6 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 member - -- | /O(min(n,W))/. Is the key not a member of the map? -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -405,8 +403,6 @@ infix 4 member notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 notMember - -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. -- See Note: Local 'go' functions and capturing] @@ -822,8 +818,6 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 union - -- | /O(n+m)/. The union with a combining function. -- -- > unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")] @@ -887,8 +881,6 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 intersection - -- | /O(n+m)/. The intersection with a combining function. -- -- > intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA" diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 9719de1..0063c3f 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,14 +332,10 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 member - -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k -infix 4 notMember - -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -527,7 +523,6 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 union {-------------------------------------------------------------------- Difference @@ -602,8 +597,6 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 intersection - {-------------------------------------------------------------------- Subset --------------------------------------------------------------------} diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 9d066fa..db9549f 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,8 +456,6 @@ member = go {-# INLINE member #-} #endif -infix 4 member - -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -471,8 +469,6 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 notMember - -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. find :: Ord k => k -> Map k a -> a @@ -1234,8 +1230,6 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union - -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b hedgeUnion _ _ t1 Tip = t1 @@ -1356,8 +1350,6 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection - hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 5727de6..ffcdfd0 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,8 +318,6 @@ member = go {-# INLINE member #-} #endif -infix 4 member - -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool notMember a t = not $ member a t @@ -329,8 +327,6 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 notMember - -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -582,8 +578,6 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union - hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 hedgeUnion blo bhi Tip (Bin _ x l r) = link x (filterGt blo l) (filterLt bhi r) @@ -642,8 +636,6 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection - hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip From git at git.haskell.org Fri Jan 23 22:38:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:53 +0000 (UTC) Subject: [commit: packages/containers] develop: Added fixity declarations for member, notMember, union, and intersection. (4dd6e01) Message-ID: <20150123223853.CA5A63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop Link : http://git.haskell.org/packages/containers.git/commitdiff/4dd6e01a78774de5e5dd6639b55a2902e610e0cc >--------------------------------------------------------------- commit 4dd6e01a78774de5e5dd6639b55a2902e610e0cc Author: Peter Selinger Date: Fri Jul 4 10:31:20 2014 -0300 Added fixity declarations for member, notMember, union, and intersection. >--------------------------------------------------------------- 4dd6e01a78774de5e5dd6639b55a2902e610e0cc Data/IntMap/Base.hs | 8 ++++++++ Data/IntSet/Base.hs | 7 +++++++ Data/Map/Base.hs | 8 ++++++++ Data/Set/Base.hs | 8 ++++++++ 4 files changed, 31 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 75b3ae9..9f7be70 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,6 +395,8 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the key not a member of the map? -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -403,6 +405,8 @@ member k = k `seq` go notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m +infix 4 notMember + -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. -- See Note: Local 'go' functions and capturing] @@ -818,6 +822,8 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 +infixl 5 union + -- | /O(n+m)/. The union with a combining function. -- -- > unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")] @@ -881,6 +887,8 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 +infixl 5 intersection + -- | /O(n+m)/. The intersection with a combining function. -- -- > intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA" diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 0063c3f..9719de1 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,10 +332,14 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -523,6 +527,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t +infixl 5 union {-------------------------------------------------------------------- Difference @@ -597,6 +602,8 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil +infixl 5 intersection + {-------------------------------------------------------------------- Subset --------------------------------------------------------------------} diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index db9549f..9d066fa 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,6 +456,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -469,6 +471,8 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. find :: Ord k => k -> Map k a -> a @@ -1230,6 +1234,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b hedgeUnion _ _ t1 Tip = t1 @@ -1350,6 +1356,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index ffcdfd0..5727de6 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,6 +318,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool notMember a t = not $ member a t @@ -327,6 +329,8 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -578,6 +582,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 hedgeUnion blo bhi Tip (Bin _ x l r) = link x (filterGt blo l) (filterLt bhi r) @@ -636,6 +642,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip From git at git.haskell.org Fri Jan 23 22:38:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:55 +0000 (UTC) Subject: [commit: packages/containers] develop: Fixed syntax of fixity declarations. (6ec9b1b) Message-ID: <20150123223855.D55A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop Link : http://git.haskell.org/packages/containers.git/commitdiff/6ec9b1b4be2d7c264ebd2aa9d6ed06c98029cf8f >--------------------------------------------------------------- commit 6ec9b1b4be2d7c264ebd2aa9d6ed06c98029cf8f Author: Peter Selinger Date: Fri Jul 4 10:47:35 2014 -0300 Fixed syntax of fixity declarations. >--------------------------------------------------------------- 6ec9b1b4be2d7c264ebd2aa9d6ed06c98029cf8f Data/IntMap/Base.hs | 8 ++++---- Data/IntSet/Base.hs | 8 ++++---- Data/Map/Base.hs | 8 ++++---- Data/Set/Base.hs | 8 ++++---- 4 files changed, 16 insertions(+), 16 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 9f7be70..237aea8 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,7 +395,7 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the key not a member of the map? -- @@ -405,7 +405,7 @@ infix 4 member notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 notMember +infix 4 `notMember` -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. @@ -822,7 +822,7 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 union +infixl 5 `union` -- | /O(n+m)/. The union with a combining function. -- @@ -887,7 +887,7 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 intersection +infixl 5 `intersection` -- | /O(n+m)/. The intersection with a combining function. -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 9719de1..5aee4ef 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,13 +332,13 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -527,7 +527,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 union +infixl 5 `union` {-------------------------------------------------------------------- Difference @@ -602,7 +602,7 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 intersection +infixl 5 `intersection` {-------------------------------------------------------------------- Subset diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 9d066fa..bc2fd47 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,7 +456,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- @@ -471,7 +471,7 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. @@ -1234,7 +1234,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b @@ -1356,7 +1356,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 5727de6..d0533f5 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,7 +318,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool @@ -329,7 +329,7 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -582,7 +582,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 @@ -642,7 +642,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip From git at git.haskell.org Fri Jan 23 22:38:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:57 +0000 (UTC) Subject: [commit: packages/containers] develop: Merge branch 'selinger-master' into develop. (f8629a2) Message-ID: <20150123223857.DEF783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop Link : http://git.haskell.org/packages/containers.git/commitdiff/f8629a228545896ed9133fd72ebbcf97336767da >--------------------------------------------------------------- commit f8629a228545896ed9133fd72ebbcf97336767da Merge: 3b1eee5 6ec9b1b Author: Milan Straka Date: Fri Aug 8 11:06:49 2014 +0200 Merge branch 'selinger-master' into develop. PVP: Major version bump is needed. >--------------------------------------------------------------- f8629a228545896ed9133fd72ebbcf97336767da Data/IntMap/Base.hs | 8 ++++++++ Data/IntSet/Base.hs | 7 +++++++ Data/Map/Base.hs | 8 ++++++++ Data/Set/Base.hs | 8 ++++++++ 4 files changed, 31 insertions(+) From git at git.haskell.org Fri Jan 23 22:38:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:38:59 +0000 (UTC) Subject: [commit: packages/containers] develop: Make types of the drawing functions more generic, i.e. Show s => Tree s instead of Tree String (2c85f08) Message-ID: <20150123223859.E5BE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop Link : http://git.haskell.org/packages/containers.git/commitdiff/2c85f0823848ef7f70a27944bc4741c91ca1c0ef >--------------------------------------------------------------- commit 2c85f0823848ef7f70a27944bc4741c91ca1c0ef Author: jonasc Date: Fri Aug 8 00:15:10 2014 +0200 Make types of the drawing functions more generic, i.e. Show s => Tree s instead of Tree String >--------------------------------------------------------------- 2c85f0823848ef7f70a27944bc4741c91ca1c0ef Data/Tree.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/Data/Tree.hs b/Data/Tree.hs index dab25c2..7cfba42 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -83,15 +83,15 @@ instance NFData a => NFData (Tree a) where rnf (Node x ts) = rnf x `seq` rnf ts -- | Neat 2-dimensional drawing of a tree. -drawTree :: Tree String -> String +drawTree :: Show a => Tree a -> String drawTree = unlines . draw -- | Neat 2-dimensional drawing of a forest. -drawForest :: Forest String -> String +drawForest :: Show a => Forest a -> String drawForest = unlines . map drawTree -draw :: Tree String -> [String] -draw (Node x ts0) = x : drawSubTrees ts0 +draw :: Show a => Tree a -> [String] +draw (Node x ts0) = show x : drawSubTrees ts0 where drawSubTrees [] = [] drawSubTrees [t] = From git at git.haskell.org Fri Jan 23 22:39:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:01 +0000 (UTC) Subject: [commit: packages/containers] develop: Merge branch 'jonasc-master' into develop (b44b6a7) Message-ID: <20150123223901.EC7F03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop Link : http://git.haskell.org/packages/containers.git/commitdiff/b44b6a727c123c0ec33e8ac0f1299ac73ee1d0ef >--------------------------------------------------------------- commit b44b6a727c123c0ec33e8ac0f1299ac73ee1d0ef Merge: f8629a2 2c85f08 Author: Milan Straka Date: Fri Aug 8 11:07:42 2014 +0200 Merge branch 'jonasc-master' into develop PVP: Major version bump is needed. >--------------------------------------------------------------- b44b6a727c123c0ec33e8ac0f1299ac73ee1d0ef Data/Tree.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) From git at git.haskell.org Fri Jan 23 22:39:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:03 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Use defensive `Data.Foldable` import (74f9b89) Message-ID: <20150123223904.004E83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/74f9b89a542240e7ab510ee4fb73a4d46035b8ea >--------------------------------------------------------------- commit 74f9b89a542240e7ab510ee4fb73a4d46035b8ea Author: Herbert Valerio Riedel Date: Sat Sep 27 15:12:33 2014 +0200 Use defensive `Data.Foldable` import With this `import`-style containers will compile warning free with existing GHC versions as well as GHC HEAD (in its current form) This change is also needed because `Data.Foldable` is planned to export `null` and `length` which will otherwise clash with `Data.Sequence` >--------------------------------------------------------------- 74f9b89a542240e7ab510ee4fb73a4d46035b8ea Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 9bfd6f9..6bbebdb 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -149,7 +149,7 @@ import Control.DeepSeq (NFData(rnf)) import Control.Monad (MonadPlus(..), ap) import Data.Monoid (Monoid(..)) import Data.Functor (Functor(..)) -import Data.Foldable +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1), foldl', toList) import Data.Traversable import Data.Typeable From git at git.haskell.org Fri Jan 23 22:39:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:06 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #54 from hvr/pr-foldable (085e1b8) Message-ID: <20150123223906.084513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/085e1b8b2cfbd1159bbc9f8cbf6a4127cc32227b >--------------------------------------------------------------- commit 085e1b8b2cfbd1159bbc9f8cbf6a4127cc32227b Merge: 3b1eee5 74f9b89 Author: Milan Straka Date: Sun Sep 28 12:45:42 2014 +0200 Merge pull request #54 from hvr/pr-foldable Use defensive `Data.Foldable` import >--------------------------------------------------------------- 085e1b8b2cfbd1159bbc9f8cbf6a4127cc32227b Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:39:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:08 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Move foldlStrict (defined 4 times) to Data.StrictFold. (27a5da9) Message-ID: <20150123223908.1695F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/27a5da9e0a99b2df2cfb267eed2dae8167c746a2 >--------------------------------------------------------------- commit 27a5da9e0a99b2df2cfb267eed2dae8167c746a2 Author: Milan Straka Date: Sun Oct 12 11:06:53 2014 +0200 Move foldlStrict (defined 4 times) to Data.StrictFold. The foldlStrict is Data.List.foldl' which is always inlined, which allows more optimizations. Also, foldl' is not Haskell 98, although it is Haskell 2010. >--------------------------------------------------------------- 27a5da9e0a99b2df2cfb267eed2dae8167c746a2 Data/IntMap/Base.hs | 9 +-------- Data/IntMap/Strict.hs | 1 + Data/IntSet/Base.hs | 7 +------ Data/Map/Base.hs | 9 +-------- Data/Map/Strict.hs | 2 ++ Data/Set/Base.hs | 7 +------ Data/StrictFold.hs | 16 ++++++++++++++++ containers.cabal | 1 + 8 files changed, 24 insertions(+), 28 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 75b3ae9..8d04bfa 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -211,7 +211,6 @@ module Data.IntMap.Base ( , shorter , branchMask , highestBitMask - , foldlStrict ) where import Control.Applicative (Applicative(pure, (<*>)), (<$>)) @@ -229,6 +228,7 @@ import Prelude hiding (lookup, map, filter, foldr, foldl, null) import Data.BitUtil import Data.IntSet.Base (Key) import qualified Data.IntSet.Base as IntSet +import Data.StrictFold import Data.StrictPair #if __GLASGOW_HASKELL__ @@ -2085,13 +2085,6 @@ branchMask p1 p2 Utilities --------------------------------------------------------------------} -foldlStrict :: (a -> b -> a) -> a -> [b] -> a -foldlStrict f = go - where - go z [] = z - go z (x:xs) = let z' = f z x in z' `seq` go z' xs -{-# INLINE foldlStrict #-} - -- | /O(1)/. Decompose a map into pieces based on the structure of the underlying -- tree. This function is useful for consuming a map in parallel. -- diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs index 2ca3707..f19682e 100644 --- a/Data/IntMap/Strict.hs +++ b/Data/IntMap/Strict.hs @@ -258,6 +258,7 @@ import Data.IntMap.Base hiding import Data.BitUtil import qualified Data.IntSet.Base as IntSet +import Data.StrictFold import Data.StrictPair -- $strictness diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 0063c3f..c843d46 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -192,6 +192,7 @@ import Data.Word (Word) import Prelude hiding (filter, foldr, foldl, null, map) import Data.BitUtil +import Data.StrictFold import Data.StrictPair #if __GLASGOW_HASKELL__ @@ -1491,12 +1492,6 @@ bitcount a0 x0 = go a0 x0 {-------------------------------------------------------------------- Utilities --------------------------------------------------------------------} -foldlStrict :: (a -> b -> a) -> a -> [b] -> a -foldlStrict f = go - where - go z [] = z - go z (x:xs) = let z' = f z x in z' `seq` go z' xs -{-# INLINE foldlStrict #-} -- | /O(1)/. Decompose a set into pieces based on the structure of the underlying -- tree. This function is useful for consuming a set in parallel. diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index db9549f..650e003 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -262,7 +262,6 @@ module Data.Map.Base ( , glue , trim , trimLookupLo - , foldlStrict , MaybeS(..) , filterGt , filterLt @@ -279,6 +278,7 @@ import Data.Typeable import Prelude hiding (lookup, map, filter, foldr, foldl, null) import qualified Data.Set.Base as Set +import Data.StrictFold #if __GLASGOW_HASKELL__ import GHC.Exts ( build ) @@ -2826,13 +2826,6 @@ validsize t {-------------------------------------------------------------------- Utilities --------------------------------------------------------------------} -foldlStrict :: (a -> b -> a) -> a -> [b] -> a -foldlStrict f = go - where - go z [] = z - go z (x:xs) = let z' = f z x in z' `seq` go z' xs -{-# INLINE foldlStrict #-} - -- | /O(1)/. Decompose a map into pieces based on the structure of the underlying -- tree. This function is useful for consuming a map in parallel. diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs index 75a29c8..4e0d820 100644 --- a/Data/Map/Strict.hs +++ b/Data/Map/Strict.hs @@ -269,7 +269,9 @@ import Data.Map.Base hiding , updateMaxWithKey ) import qualified Data.Set.Base as Set +import Data.StrictFold import Data.StrictPair + import Data.Bits (shiftL, shiftR) -- Use macros to define strictness of functions. STRICT_x_OF_y diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index ffcdfd0..3a2c938 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -194,6 +194,7 @@ import qualified Data.Foldable as Foldable import Data.Typeable import Control.DeepSeq (NFData(rnf)) +import Data.StrictFold import Data.StrictPair #if __GLASGOW_HASKELL__ @@ -1416,12 +1417,6 @@ bin x l r {-------------------------------------------------------------------- Utilities --------------------------------------------------------------------} -foldlStrict :: (a -> b -> a) -> a -> [b] -> a -foldlStrict f = go - where - go z [] = z - go z (x:xs) = let z' = f z x in z' `seq` go z' xs -{-# INLINE foldlStrict #-} -- | /O(1)/. Decompose a set into pieces based on the structure of the underlying -- tree. This function is useful for consuming a set in parallel. diff --git a/Data/StrictFold.hs b/Data/StrictFold.hs new file mode 100644 index 0000000..9c90a66 --- /dev/null +++ b/Data/StrictFold.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE CPP #-} +#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 +{-# LANGUAGE Trustworthy #-} +#endif +module Data.StrictFold (foldlStrict) where + +-- | Same as regular 'Data.List.foldl'', but marked INLINE so that it is always +-- inlined. This allows further optimization of the call to f, which can be +-- optimized/specialised/inlined. + +foldlStrict :: (a -> b -> a) -> a -> [b] -> a +foldlStrict f = go + where + go z [] = z + go z (x:xs) = let z' = f z x in z' `seq` go z' xs +{-# INLINE foldlStrict #-} diff --git a/containers.cabal b/containers.cabal index 209589b..a952a77 100644 --- a/containers.cabal +++ b/containers.cabal @@ -57,6 +57,7 @@ Library Data.IntSet.Base Data.Map.Base Data.Set.Base + Data.StrictFold Data.StrictPair include-dirs: include From git at git.haskell.org Fri Jan 23 22:39:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:10 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Move utilities (BitUtils, Strict{Fold, Pair}) to Utils directory. (9cfe43a) Message-ID: <20150123223910.250D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/9cfe43a9790f8c8511f93f380e7d7168bb1c1a88 >--------------------------------------------------------------- commit 9cfe43a9790f8c8511f93f380e7d7168bb1c1a88 Author: Milan Straka Date: Sun Oct 12 11:13:13 2014 +0200 Move utilities (BitUtils,Strict{Fold,Pair}) to Utils directory. The Data directory was becoming a little too crowded. >--------------------------------------------------------------- 9cfe43a9790f8c8511f93f380e7d7168bb1c1a88 Data/IntMap/Base.hs | 6 +++--- Data/IntMap/Strict.hs | 6 +++--- Data/IntSet/Base.hs | 6 +++--- Data/Map/Base.hs | 4 ++-- Data/Map/Strict.hs | 4 ++-- Data/Set/Base.hs | 4 ++-- Data/{ => Utils}/BitUtil.hs | 4 ++-- Data/{ => Utils}/StrictFold.hs | 2 +- Data/{ => Utils}/StrictPair.hs | 2 +- containers.cabal | 6 +++--- 10 files changed, 22 insertions(+), 22 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 8d04bfa..fec5abe 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -225,11 +225,11 @@ import Data.Typeable import Data.Word (Word) import Prelude hiding (lookup, map, filter, foldr, foldl, null) -import Data.BitUtil import Data.IntSet.Base (Key) import qualified Data.IntSet.Base as IntSet -import Data.StrictFold -import Data.StrictPair +import Data.Utils.BitUtil +import Data.Utils.StrictFold +import Data.Utils.StrictPair #if __GLASGOW_HASKELL__ import Data.Data (Data(..), Constr, mkConstr, constrIndex, Fixity(Prefix), diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs index f19682e..3a7dde8 100644 --- a/Data/IntMap/Strict.hs +++ b/Data/IntMap/Strict.hs @@ -256,10 +256,10 @@ import Data.IntMap.Base hiding , fromDistinctAscList ) -import Data.BitUtil import qualified Data.IntSet.Base as IntSet -import Data.StrictFold -import Data.StrictPair +import Data.Utils.BitUtil +import Data.Utils.StrictFold +import Data.Utils.StrictPair -- $strictness -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index c843d46..309ab42 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -191,9 +191,9 @@ import Data.Typeable import Data.Word (Word) import Prelude hiding (filter, foldr, foldl, null, map) -import Data.BitUtil -import Data.StrictFold -import Data.StrictPair +import Data.Utils.BitUtil +import Data.Utils.StrictFold +import Data.Utils.StrictPair #if __GLASGOW_HASKELL__ import Data.Data (Data(..), Constr, mkConstr, constrIndex, Fixity(Prefix), DataType, mkDataType) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 650e003..d1d8ffe 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -272,13 +272,13 @@ import Control.DeepSeq (NFData(rnf)) import Data.Bits (shiftL, shiftR) import qualified Data.Foldable as Foldable import Data.Monoid (Monoid(..)) -import Data.StrictPair import Data.Traversable (Traversable(traverse)) import Data.Typeable import Prelude hiding (lookup, map, filter, foldr, foldl, null) import qualified Data.Set.Base as Set -import Data.StrictFold +import Data.Utils.StrictFold +import Data.Utils.StrictPair #if __GLASGOW_HASKELL__ import GHC.Exts ( build ) diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs index 4e0d820..5f286b9 100644 --- a/Data/Map/Strict.hs +++ b/Data/Map/Strict.hs @@ -269,8 +269,8 @@ import Data.Map.Base hiding , updateMaxWithKey ) import qualified Data.Set.Base as Set -import Data.StrictFold -import Data.StrictPair +import Data.Utils.StrictFold +import Data.Utils.StrictPair import Data.Bits (shiftL, shiftR) diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 3a2c938..6c39a8e 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -194,8 +194,8 @@ import qualified Data.Foldable as Foldable import Data.Typeable import Control.DeepSeq (NFData(rnf)) -import Data.StrictFold -import Data.StrictPair +import Data.Utils.StrictFold +import Data.Utils.StrictPair #if __GLASGOW_HASKELL__ import GHC.Exts ( build ) diff --git a/Data/BitUtil.hs b/Data/Utils/BitUtil.hs similarity index 97% rename from Data/BitUtil.hs rename to Data/Utils/BitUtil.hs index 848bac1..bea078e 100644 --- a/Data/BitUtil.hs +++ b/Data/Utils/BitUtil.hs @@ -7,7 +7,7 @@ #endif ----------------------------------------------------------------------------- -- | --- Module : Data.BitUtil +-- Module : Data.Utils.BitUtil -- Copyright : (c) Clark Gaebel 2012 -- (c) Johan Tibel 2012 -- License : BSD-style @@ -16,7 +16,7 @@ -- Portability : portable ----------------------------------------------------------------------------- -module Data.BitUtil +module Data.Utils.BitUtil ( highestBitMask , shiftLL , shiftRL diff --git a/Data/StrictFold.hs b/Data/Utils/StrictFold.hs similarity index 90% rename from Data/StrictFold.hs rename to Data/Utils/StrictFold.hs index 9c90a66..953c9f1 100644 --- a/Data/StrictFold.hs +++ b/Data/Utils/StrictFold.hs @@ -2,7 +2,7 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif -module Data.StrictFold (foldlStrict) where +module Data.Utils.StrictFold (foldlStrict) where -- | Same as regular 'Data.List.foldl'', but marked INLINE so that it is always -- inlined. This allows further optimization of the call to f, which can be diff --git a/Data/StrictPair.hs b/Data/Utils/StrictPair.hs similarity index 77% rename from Data/StrictPair.hs rename to Data/Utils/StrictPair.hs index 48609b3..6ae7ded 100644 --- a/Data/StrictPair.hs +++ b/Data/Utils/StrictPair.hs @@ -2,7 +2,7 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif -module Data.StrictPair (StrictPair(..), toPair) where +module Data.Utils.StrictPair (StrictPair(..), toPair) where -- | Same as regular Haskell pairs, but (x :*: _|_) = (_|_ :*: y) = -- _|_ diff --git a/containers.cabal b/containers.cabal index a952a77..dcf36fd 100644 --- a/containers.cabal +++ b/containers.cabal @@ -52,13 +52,13 @@ Library Data.Sequence Data.Tree other-modules: - Data.BitUtil Data.IntMap.Base Data.IntSet.Base Data.Map.Base Data.Set.Base - Data.StrictFold - Data.StrictPair + Data.Utils.BitUtil + Data.Utils.StrictFold + Data.Utils.StrictPair include-dirs: include From git at git.haskell.org Fri Jan 23 22:39:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:12 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Fix subtle bug in binary search (46b3b9d) Message-ID: <20150123223912.2DB9E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/46b3b9d4b34e761aa6f75335c717742bc89d922d >--------------------------------------------------------------- commit 46b3b9d4b34e761aa6f75335c717742bc89d922d Author: Josh Acay Date: Tue Oct 14 14:42:17 2014 -0400 Fix subtle bug in binary search >--------------------------------------------------------------- 46b3b9d4b34e761aa6f75335c717742bc89d922d Data/Graph.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Graph.hs b/Data/Graph.hs index c5cdf4b..65f3fb1 100644 --- a/Data/Graph.hs +++ b/Data/Graph.hs @@ -244,7 +244,7 @@ graphFromEdges edges0 EQ -> Just mid GT -> findVertex (mid+1) b where - mid = (a + b) `div` 2 + mid = a + (b - a) `div` 2 ------------------------------------------------------------------------- -- - From git at git.haskell.org Fri Jan 23 22:39:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:14 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #58 from cacay/master (828b60d) Message-ID: <20150123223914.34EFB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/828b60d394418132eb86993bbde29538b066aed8 >--------------------------------------------------------------- commit 828b60d394418132eb86993bbde29538b066aed8 Merge: 9cfe43a 46b3b9d Author: Milan Straka Date: Tue Oct 14 21:52:28 2014 +0200 Merge pull request #58 from cacay/master Fix bug in binary search >--------------------------------------------------------------- 828b60d394418132eb86993bbde29538b066aed8 Data/Graph.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:39:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:16 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Minor documentation fix. (864ebff) Message-ID: <20150123223916.4142B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/864ebff7995e7d4358475f8808f10329a832b78b >--------------------------------------------------------------- commit 864ebff7995e7d4358475f8808f10329a832b78b Author: strout Date: Tue Oct 14 22:53:42 2014 -0500 Minor documentation fix. Completed a sentence in maxView documentation. >--------------------------------------------------------------- 864ebff7995e7d4358475f8808f10329a832b78b Data/Map/Base.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index d1d8ffe..eafab03 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -1171,6 +1171,7 @@ minView x = Just (first snd $ deleteFindMin x) -- | /O(log n)/. Retrieves the value associated with maximal key of the -- map, and the map stripped of that element, or 'Nothing' if passed an +-- empty map. -- -- > maxView (fromList [(5,"a"), (3,"b")]) == Just ("a", singleton 3 "b") -- > maxView empty == Nothing From git at git.haskell.org Fri Jan 23 22:39:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:18 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #59 from strout/patch-1 (b9bd228) Message-ID: <20150123223918.463773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/b9bd228149bfb61fe9f87a6ca9858ce1df1aee9e >--------------------------------------------------------------- commit b9bd228149bfb61fe9f87a6ca9858ce1df1aee9e Merge: 828b60d 864ebff Author: Milan Straka Date: Wed Oct 15 08:48:37 2014 +0200 Merge pull request #59 from strout/patch-1 Minor documentation fix. >--------------------------------------------------------------- b9bd228149bfb61fe9f87a6ca9858ce1df1aee9e Data/Map/Base.hs | 1 + 1 file changed, 1 insertion(+) From git at git.haskell.org Fri Jan 23 22:39:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:20 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Define some new Foldable methods for containers (61b9066) Message-ID: <20150123223920.505573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/61b9066d79ac346743dfe56425307e27e2e5d060 >--------------------------------------------------------------- commit 61b9066d79ac346743dfe56425307e27e2e5d060 Author: Herbert Valerio Riedel Date: Tue Oct 14 20:25:29 2014 +0200 Define some new Foldable methods for containers This is a first attempt at addressing #56 >--------------------------------------------------------------- 61b9066d79ac346743dfe56425307e27e2e5d060 Data/IntMap/Base.hs | 15 +++++++++++++++ Data/Map/Base.hs | 15 +++++++++++++++ Data/Sequence.hs | 7 +++++++ Data/Set/Base.hs | 20 ++++++++++++++++++++ Data/Tree.hs | 7 +++++++ 5 files changed, 64 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index fec5abe..0de3e5b 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -320,6 +320,21 @@ instance Foldable.Foldable IntMap where go (Bin _ _ l r) = go l `mappend` go r {-# INLINE foldMap #-} +#if MIN_VERSION_base(4,6,0) + foldl' = foldl' + {-# INLINE foldl' #-} + foldr' = foldr' + {-# INLINE foldr' #-} +#endif +#if MIN_VERSION_base(4,8,0) + length = size + {-# INLINE length #-} + null = null + {-# INLINE null #-} + toList = elems -- NB: Foldable.toList /= IntMap.toList + {-# INLINE toList #-} +#endif + instance Traversable IntMap where traverse f = traverseWithKey (\_ -> f) {-# INLINE traverse #-} diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index d1d8ffe..d01367b 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -2653,6 +2653,21 @@ instance Foldable.Foldable (Map k) where go (Bin _ _ v l r) = go l `mappend` (f v `mappend` go r) {-# INLINE foldMap #-} +#if MIN_VERSION_base(4,6,0) + foldl' = foldl' + {-# INLINE foldl' #-} + foldr' = foldr' + {-# INLINE foldr' #-} +#endif +#if MIN_VERSION_base(4,8,0) + length = size + {-# INLINE length #-} + null = null + {-# INLINE null #-} + toList = elems -- NB: Foldable.toList /= Map.toList + {-# INLINE toList #-} +#endif + instance (NFData k, NFData a) => NFData (Map k a) where rnf Tip = () rnf (Bin _ kx x l r) = rnf kx `seq` rnf x `seq` rnf l `seq` rnf r diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 6bbebdb..f1385f5 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -189,6 +189,13 @@ instance Foldable Seq where foldl1 f (Seq xs) = getElem (foldl1 f' xs) where f' (Elem x) (Elem y) = Elem (f x y) +#if MIN_VERSION_base(4,8,0) + length = length + {-# INLINE length #-} + null = null + {-# INLINE null #-} +#endif + instance Traversable Seq where traverse f (Seq xs) = Seq <$> traverse (traverse f) xs diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 6c39a8e..9260aeb 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -262,6 +262,26 @@ instance Foldable.Foldable Set where go (Bin _ k l r) = go l `mappend` (f k `mappend` go r) {-# INLINE foldMap #-} +#if MIN_VERSION_base(4,6,0) + foldl' = foldl' + {-# INLINE foldl' #-} + foldr' = foldr' + {-# INLINE foldr' #-} +#endif +#if MIN_VERSION_base(4,8,0) + length = size + {-# INLINE length #-} + null = null + {-# INLINE null #-} + toList = toList + {-# INLINE toList #-} + minimum = findMin + {-# INLINE minimum #-} + maximum = findMax + {-# INLINE maximum #-} +#endif + + #if __GLASGOW_HASKELL__ {-------------------------------------------------------------------- diff --git a/Data/Tree.hs b/Data/Tree.hs index dab25c2..2f18c68 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -79,6 +79,13 @@ instance Traversable Tree where instance Foldable Tree where foldMap f (Node x ts) = f x `mappend` foldMap (foldMap f) ts +#if MIN_VERSION_base(4,8,0) + null _ = False + {-# INLINE null #-} + toList = flatten + {-# INLINE toList #-} +#endif + instance NFData a => NFData (Tree a) where rnf (Node x ts) = rnf x `seq` rnf ts From git at git.haskell.org Fri Jan 23 22:39:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:22 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Replace `MIN_VERSION_base_4_[57]_0` by `MIN_VERSION_base()` (3582252) Message-ID: <20150123223922.592A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/3582252bda944421c0a38c86684657e59dbe81be >--------------------------------------------------------------- commit 3582252bda944421c0a38c86684657e59dbe81be Author: Herbert Valerio Riedel Date: Thu Oct 16 22:35:13 2014 +0200 Replace `MIN_VERSION_base_4_[57]_0` by `MIN_VERSION_base()` >--------------------------------------------------------------- 3582252bda944421c0a38c86684657e59dbe81be Data/IntSet/Base.hs | 24 ++---------------------- 1 file changed, 2 insertions(+), 22 deletions(-) diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 309ab42..c8e70f6 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -162,26 +162,6 @@ module Data.IntSet.Base ( , bitmapOf ) where --- We want to be able to compile without cabal. Nevertheless --- #if defined(MIN_VERSION_base) && MIN_VERSION_base(4,5,0) --- does not work, because if MIN_VERSION_base is undefined, --- the last condition is syntactically wrong. -#define MIN_VERSION_base_4_5_0 0 -#ifdef MIN_VERSION_base -#if MIN_VERSION_base(4,5,0) -#undef MIN_VERSION_base_4_5_0 -#define MIN_VERSION_base_4_5_0 1 -#endif -#endif - -#define MIN_VERSION_base_4_7_0 0 -#ifdef MIN_VERSION_base -#if MIN_VERSION_base(4,7,0) -#undef MIN_VERSION_base_4_7_0 -#define MIN_VERSION_base_4_7_0 1 -#endif -#endif - import Control.DeepSeq (NFData) import Data.Bits import qualified Data.List as List @@ -1228,7 +1208,7 @@ tip kx bm = Tip kx bm ----------------------------------------------------------------------} suffixBitMask :: Int -#if MIN_VERSION_base_4_7_0 +#if MIN_VERSION_base(4,7,0) suffixBitMask = finiteBitSize (undefined::Word) - 1 #else suffixBitMask = bitSize (undefined::Word) - 1 @@ -1479,7 +1459,7 @@ foldr'Bits prefix f z bm = let lb = lowestBitSet bm ----------------------------------------------------------------------} bitcount :: Int -> Word -> Int -#if MIN_VERSION_base_4_5_0 +#if MIN_VERSION_base(4,5,0) bitcount a x = a + popCount x #else bitcount a0 x0 = go a0 x0 From git at git.haskell.org Fri Jan 23 22:39:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:24 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #57 from hvr/pr-foldable (daf640e) Message-ID: <20150123223924.65AC83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/daf640ec6c0c189a6c570a1dff4e958e2fa8d697 >--------------------------------------------------------------- commit daf640ec6c0c189a6c570a1dff4e958e2fa8d697 Merge: b9bd228 3582252 Author: Milan Straka Date: Sun Oct 19 10:24:41 2014 +0200 Merge pull request #57 from hvr/pr-foldable Define some new Foldable methods for containers >--------------------------------------------------------------- daf640ec6c0c189a6c570a1dff4e958e2fa8d697 Data/IntMap/Base.hs | 15 +++++++++++++++ Data/IntSet/Base.hs | 24 ++---------------------- Data/Map/Base.hs | 15 +++++++++++++++ Data/Sequence.hs | 7 +++++++ Data/Set/Base.hs | 20 ++++++++++++++++++++ Data/Tree.hs | 7 +++++++ 6 files changed, 66 insertions(+), 22 deletions(-) From git at git.haskell.org Fri Jan 23 22:39:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:26 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Provide default MIN_VERSION_base if not available. (0762786) Message-ID: <20150123223926.727023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/076278627b6b3fda9522a9ca971f2467947527d6 >--------------------------------------------------------------- commit 076278627b6b3fda9522a9ca971f2467947527d6 Author: Milan Straka Date: Sun Oct 19 10:43:09 2014 +0200 Provide default MIN_VERSION_base if not available. After #56, we use MIN_VERSION_base in many places. We now provide trivial MIN_VERSION_base if not available to allow compiling without cabal. >--------------------------------------------------------------- 076278627b6b3fda9522a9ca971f2467947527d6 Data/IntMap/Base.hs | 8 ++++++++ Data/IntSet/Base.hs | 8 ++++++++ Data/Map/Base.hs | 8 ++++++++ Data/Sequence.hs | 8 ++++++++ Data/Set/Base.hs | 8 ++++++++ Data/Tree.hs | 8 ++++++++ 6 files changed, 48 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 0de3e5b..8f2e32f 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -247,6 +247,14 @@ import Text.Read -- want the compilers to be compiled by as many compilers as possible. #define STRICT_1_OF_2(fn) fn arg _ | arg `seq` False = undefined +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + -- A "Nat" is a natural machine word (an unsigned Int) type Nat = Word diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index c8e70f6..b6f8014 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -202,6 +202,14 @@ import GHC.Prim (indexInt8OffAddr#) #define STRICT_1_OF_3(fn) fn arg _ _ | arg `seq` False = undefined #define STRICT_2_OF_3(fn) fn _ arg _ | arg `seq` False = undefined +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + infixl 9 \\{-This comment teaches CPP correct behaviour -} -- A "Nat" is a natural machine word (an unsigned Int) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 72934e9..edcfdb7 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -299,6 +299,14 @@ import Data.Data #define STRICT_1_OF_4(fn) fn arg _ _ _ | arg `seq` False = undefined #define STRICT_2_OF_4(fn) fn _ arg _ _ | arg `seq` False = undefined +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + {-------------------------------------------------------------------- Operators --------------------------------------------------------------------} diff --git a/Data/Sequence.hs b/Data/Sequence.hs index f1385f5..a2b4844 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -160,6 +160,14 @@ import Text.Read (Lexeme(Ident), lexP, parens, prec, import Data.Data #endif +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + infixr 5 `consTree` infixl 5 `snocTree` diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 9260aeb..e676a6f 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -214,6 +214,14 @@ import Data.Data #define STRICT_1_OF_3(fn) fn arg _ _ | arg `seq` False = undefined #define STRICT_2_OF_3(fn) fn _ arg _ | arg `seq` False = undefined +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + {-------------------------------------------------------------------- Operators --------------------------------------------------------------------} diff --git a/Data/Tree.hs b/Data/Tree.hs index 2f18c68..c880213 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -45,6 +45,14 @@ import Control.DeepSeq (NFData(rnf)) import Data.Data (Data) #endif +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + -- | Multi-way trees, also known as /rose trees/. data Tree a = Node { rootLabel :: a, -- ^ label value From git at git.haskell.org Fri Jan 23 22:39:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:28 +0000 (UTC) Subject: [commit: packages/containers] branch 'strict-tuples' created Message-ID: <20150123223928.3A5263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New branch : strict-tuples Referencing: cd8d45fb8c4132a5bf56b140a40d9f37f04cfd56 From git at git.haskell.org Fri Jan 23 22:39:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:28 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Remove RoleAnnotations extension from containers.cabal. (1d555a4) Message-ID: <20150123223928.78AE83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/1d555a4d7d2b902808d73c2fad4314672241e81d >--------------------------------------------------------------- commit 1d555a4d7d2b902808d73c2fad4314672241e81d Author: Milan Straka Date: Sun Oct 19 10:46:13 2014 +0200 Remove RoleAnnotations extension from containers.cabal. We switch the language extensions in specific files. We only provide extensions for GHC pre 7.0, as it cannot enable extensions conditionally using CPP. >--------------------------------------------------------------- 1d555a4d7d2b902808d73c2fad4314672241e81d containers.cabal | 2 -- 1 file changed, 2 deletions(-) diff --git a/containers.cabal b/containers.cabal index dcf36fd..815882e 100644 --- a/containers.cabal +++ b/containers.cabal @@ -64,8 +64,6 @@ Library if impl(ghc<7.0) extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types - if impl(ghc >= 7.8) - extensions: RoleAnnotations ------------------- -- T E S T I N G -- From git at git.haskell.org Fri Jan 23 22:39:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:30 +0000 (UTC) Subject: [commit: packages/containers] branch 'develop-0.6' created Message-ID: <20150123223930.3BBE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New branch : develop-0.6 Referencing: 7ab1c399726c5a4a562cff3f56017ff5852ac82e From git at git.haskell.org Fri Jan 23 22:39:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:30 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Make Foldable.fold be INLINABLE without an argument. (398e466) Message-ID: <20150123223930.84ACB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/398e46672e498f83f28733f3a7a188651e9576b8 >--------------------------------------------------------------- commit 398e46672e498f83f28733f3a7a188651e9576b8 Author: Milan Straka Date: Sun Oct 19 14:07:13 2014 +0200 Make Foldable.fold be INLINABLE without an argument. >--------------------------------------------------------------- 398e46672e498f83f28733f3a7a188651e9576b8 Data/IntMap/Base.hs | 2 +- Data/Map/Base.hs | 2 +- Data/Set/Base.hs | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 8f2e32f..c1b2f4d 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -313,7 +313,7 @@ instance Monoid (IntMap a) where mconcat = unions instance Foldable.Foldable IntMap where - fold t = go t + fold = go where go Nil = mempty go (Tip _ v) = v go (Bin _ _ l r) = go l `mappend` go r diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index edcfdb7..781ac3a 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -2647,7 +2647,7 @@ instance Traversable (Map k) where {-# INLINE traverse #-} instance Foldable.Foldable (Map k) where - fold t = go t + fold = go where go Tip = mempty go (Bin 1 _ v _ _) = v go (Bin _ _ v l r) = go l `mappend` (v `mappend` go r) diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index e676a6f..67ade4e 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -255,7 +255,7 @@ instance Ord a => Monoid (Set a) where mconcat = unions instance Foldable.Foldable Set where - fold t = go t + fold = go where go Tip = mempty go (Bin 1 k _ _) = k go (Bin _ k l r) = go l `mappend` (k `mappend` go r) From git at git.haskell.org Fri Jan 23 22:39:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:32 +0000 (UTC) Subject: [commit: packages/containers] branch 'develop' created Message-ID: <20150123223932.3CE2B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New branch : develop Referencing: b44b6a727c123c0ec33e8ac0f1299ac73ee1d0ef From git at git.haskell.org Fri Jan 23 22:39:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:32 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add Foldable.{elem, maximum, minimum, sum, product} specializations. (530fc76) Message-ID: <20150123223932.8E8243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/530fc76bdd17089fcaaa655d66156abbc2092c2c >--------------------------------------------------------------- commit 530fc76bdd17089fcaaa655d66156abbc2092c2c Author: Milan Straka Date: Sun Oct 19 14:07:42 2014 +0200 Add Foldable.{elem,maximum,minimum,sum,product} specializations. Following #56, add specializations for other base-4.8 Foldable methods, using strict folds and shortcircuiting. The Set.elem uses only Eq a, so it runs in linear time. >--------------------------------------------------------------- 530fc76bdd17089fcaaa655d66156abbc2092c2c Data/IntMap/Base.hs | 30 ++++++++++++++++++++++++++++++ Data/Map/Base.hs | 25 +++++++++++++++++++++++++ Data/Set/Base.hs | 9 +++++++++ 3 files changed, 64 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index c1b2f4d..007e41e 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -341,6 +341,36 @@ instance Foldable.Foldable IntMap where {-# INLINE null #-} toList = elems -- NB: Foldable.toList /= IntMap.toList {-# INLINE toList #-} + elem = go + where STRICT_1_OF_2(go) + go _ Nil = False + go x (Tip _ y) = x == y + go x (Bin _ _ l r) = go x l || go x r + {-# INLINABLE elem #-} + maximum = start + where start Nil = error "IntMap.Foldable.maximum: called with empty map" + start (Tip _ y) = y + start (Bin _ _ l r) = go (start l) r + + STRICT_1_OF_2(go) + go m Nil = m + go m (Tip _ y) = max m y + go m (Bin _ _ l r) = go (go m l) r + {-# INLINABLE maximum #-} + minimum = start + where start Nil = error "IntMap.Foldable.minimum: called with empty map" + start (Tip _ y) = y + start (Bin _ _ l r) = go (start l) r + + STRICT_1_OF_2(go) + go m Nil = m + go m (Tip _ y) = min m y + go m (Bin _ _ l r) = go (go m l) r + {-# INLINABLE minimum #-} + sum = foldl' (+) 0 + {-# INLINABLE sum #-} + product = foldl' (*) 1 + {-# INLINABLE product #-} #endif instance Traversable IntMap where diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 781ac3a..de074f4 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -2675,6 +2675,31 @@ instance Foldable.Foldable (Map k) where {-# INLINE null #-} toList = elems -- NB: Foldable.toList /= Map.toList {-# INLINE toList #-} + elem = go + where STRICT_1_OF_2(go) + go _ Tip = False + go x (Bin _ _ v l r) = x == v || go x l || go x r + {-# INLINABLE elem #-} + maximum = start + where start Tip = error "Map.Foldable.maximum: called with empty map" + start (Bin _ _ v l r) = go (go v l) r + + STRICT_1_OF_2(go) + go m Tip = m + go m (Bin _ _ v l r) = go (go (max m v) l) r + {-# INLINABLE maximum #-} + minimum = start + where start Tip = error "Map.Foldable.minumum: called with empty map" + start (Bin _ _ v l r) = go (go v l) r + + STRICT_1_OF_2(go) + go m Tip = m + go m (Bin _ _ v l r) = go (go (min m v) l) r + {-# INLINABLE minimum #-} + sum = foldl' (+) 0 + {-# INLINABLE sum #-} + product = foldl' (*) 1 + {-# INLINABLE product #-} #endif instance (NFData k, NFData a) => NFData (Map k a) where diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 67ade4e..7e792f4 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -283,10 +283,19 @@ instance Foldable.Foldable Set where {-# INLINE null #-} toList = toList {-# INLINE toList #-} + elem = go + where STRICT_1_OF_2(go) + go _ Tip = False + go x (Bin _ y l r) = x == y || go x l || go x r + {-# INLINABLE elem #-} minimum = findMin {-# INLINE minimum #-} maximum = findMax {-# INLINE maximum #-} + sum = foldl' (+) 0 + {-# INLINABLE sum #-} + product = foldl' (*) 1 + {-# INLINABLE product #-} #endif From git at git.haskell.org Fri Jan 23 22:39:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:34 +0000 (UTC) Subject: [commit: packages/containers] branch 'develop-0.6-questionable' created Message-ID: <20150123223934.3DCBE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New branch : develop-0.6-questionable Referencing: 2bf686d3dd0706eef416590100f8d1ebaa3eb80b From git at git.haskell.org Fri Jan 23 22:39:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:34 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Force prefix and suffix before middle (7dfdc33) Message-ID: <20150123223934.95FAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/7dfdc33f8cc740036cee5a5e94c5603722d6fd02 >--------------------------------------------------------------- commit 7dfdc33f8cc740036cee5a5e94c5603722d6fd02 Author: treeowl Date: Sat Nov 8 22:08:19 2014 -0500 Force prefix and suffix before middle This should be slightly more efficient. Probably very slightly, but there doesn't seem to be a good reason not to. >--------------------------------------------------------------- 7dfdc33f8cc740036cee5a5e94c5603722d6fd02 Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index a2b4844..1952b1c 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -346,7 +346,7 @@ instance Traversable FingerTree where instance NFData a => NFData (FingerTree a) where rnf (Empty) = () rnf (Single x) = rnf x - rnf (Deep _ pr m sf) = rnf pr `seq` rnf m `seq` rnf sf + rnf (Deep _ pr m sf) = rnf pr `seq` rnf sf `seq` rnf m {-# INLINE deep #-} deep :: Sized a => Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a From git at git.haskell.org Fri Jan 23 22:39:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:36 +0000 (UTC) Subject: [commit: packages/containers] branch 'zip-devel' created Message-ID: <20150123223936.3E8DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New branch : zip-devel Referencing: ce7f531605b5f2bb350f36c51a74d9ebd84ff8b6 From git at git.haskell.org Fri Jan 23 22:39:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:36 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #61 from treeowl/master (f9c23af) Message-ID: <20150123223936.9CD8C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/f9c23af0c7396aaf457ce9916392c7f949b60384 >--------------------------------------------------------------- commit f9c23af0c7396aaf457ce9916392c7f949b60384 Merge: 530fc76 7dfdc33 Author: Milan Straka Date: Sun Nov 9 07:11:13 2014 +0100 Merge pull request #61 from treeowl/master Force prefix and suffix before middle >--------------------------------------------------------------- f9c23af0c7396aaf457ce9916392c7f949b60384 Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:39:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:38 +0000 (UTC) Subject: [commit: packages/containers] branch 'ghc-head' deleted Message-ID: <20150123223938.3F7403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers Deleted branch: ghc-head From git at git.haskell.org Fri Jan 23 22:39:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:38 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. (245ef13) Message-ID: <20150123223938.A52523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/245ef135eb8701fcd139770e564f25e774d26422 >--------------------------------------------------------------- commit 245ef135eb8701fcd139770e564f25e774d26422 Author: David Terei Date: Wed Nov 12 18:19:51 2014 -0800 Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. >--------------------------------------------------------------- 245ef135eb8701fcd139770e564f25e774d26422 Data/IntMap.hs | 2 +- Data/IntMap/Lazy.hs | 2 +- Data/IntMap/Strict.hs | 4 +++- Data/Utils/StrictFold.hs | 2 +- Data/Utils/StrictPair.hs | 2 +- 5 files changed, 7 insertions(+), 5 deletions(-) diff --git a/Data/IntMap.hs b/Data/IntMap.hs index 29ca3f5..52b05c2 100644 --- a/Data/IntMap.hs +++ b/Data/IntMap.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif ----------------------------------------------------------------------------- -- | diff --git a/Data/IntMap/Lazy.hs b/Data/IntMap/Lazy.hs index ab89e1a..62bf835 100644 --- a/Data/IntMap/Lazy.hs +++ b/Data/IntMap/Lazy.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif ----------------------------------------------------------------------------- -- | diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs index 3a7dde8..f1c363c 100644 --- a/Data/IntMap/Strict.hs +++ b/Data/IntMap/Strict.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} -#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 +#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/Data/Utils/StrictFold.hs b/Data/Utils/StrictFold.hs index 953c9f1..b080e8a 100644 --- a/Data/Utils/StrictFold.hs +++ b/Data/Utils/StrictFold.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif module Data.Utils.StrictFold (foldlStrict) where diff --git a/Data/Utils/StrictPair.hs b/Data/Utils/StrictPair.hs index 6ae7ded..0c01ca4 100644 --- a/Data/Utils/StrictPair.hs +++ b/Data/Utils/StrictPair.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif module Data.Utils.StrictPair (StrictPair(..), toPair) where From git at git.haskell.org Fri Jan 23 22:39:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:40 +0000 (UTC) Subject: [commit: packages/containers] tag 'containers-0.5.6.2-release' created Message-ID: <20150123223940.4074D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New tag : containers-0.5.6.2-release Referencing: ab15b1f50d85199aebbe58c7e8efb7f3f1f09eda From git at git.haskell.org Fri Jan 23 22:39:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:40 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add support for `deepseq-1.4` (667cf94) Message-ID: <20150123223940.AF4CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/667cf94c6826738429485b806354d1e92136ba56 >--------------------------------------------------------------- commit 667cf94c6826738429485b806354d1e92136ba56 Author: Herbert Valerio Riedel Date: Fri Nov 14 16:09:27 2014 +0100 Add support for `deepseq-1.4` This change avoids relying on `rnf`'s default method implementation which has changed in `deepseq-1.4.0.0` >--------------------------------------------------------------- 667cf94c6826738429485b806354d1e92136ba56 Data/IntSet/Base.hs | 4 ++-- containers.cabal | 22 +++++++++++----------- 2 files changed, 13 insertions(+), 13 deletions(-) diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index b6f8014..6333eea 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -162,7 +162,7 @@ module Data.IntSet.Base ( , bitmapOf ) where -import Control.DeepSeq (NFData) +import Control.DeepSeq (NFData(rnf)) import Data.Bits import qualified Data.List as List import Data.Maybe (fromMaybe) @@ -1099,7 +1099,7 @@ INSTANCE_TYPEABLE0(IntSet,intSetTc,"IntSet") -- The IntSet constructors consist only of strict fields of Ints and -- IntSets, thus the default NFData instance which evaluates to whnf -- should suffice -instance NFData IntSet +instance NFData IntSet where rnf x = seq x () {-------------------------------------------------------------------- Debugging diff --git a/containers.cabal b/containers.cabal index 815882e..050257c 100644 --- a/containers.cabal +++ b/containers.cabal @@ -31,7 +31,7 @@ source-repository head location: http://github.com/haskell/containers.git Library - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4 + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5 if impl(ghc>=6.10) build-depends: ghc-prim @@ -83,7 +83,7 @@ Test-suite map-lazy-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -100,7 +100,7 @@ Test-suite map-strict-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING -DSTRICT - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -117,7 +117,7 @@ Test-suite set-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -134,7 +134,7 @@ Test-suite intmap-lazy-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -151,7 +151,7 @@ Test-suite intmap-strict-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING -DSTRICT - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -168,7 +168,7 @@ Test-suite intset-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -185,7 +185,7 @@ Test-suite deprecated-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -200,7 +200,7 @@ Test-suite seq-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -218,7 +218,7 @@ test-suite map-strictness-properties array, base >= 4.2 && < 5, ChasingBottoms, - deepseq >= 1.2 && < 1.4, + deepseq >= 1.2 && < 1.5, QuickCheck >= 2.4.0.1, ghc-prim, test-framework >= 0.3.3, @@ -235,7 +235,7 @@ test-suite intmap-strictness-properties array, base >= 4.2 && < 5, ChasingBottoms, - deepseq >= 1.2 && < 1.4, + deepseq >= 1.2 && < 1.5, QuickCheck >= 2.4.0.1, ghc-prim, test-framework >= 0.3.3, From git at git.haskell.org Fri Jan 23 22:39:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:42 +0000 (UTC) Subject: [commit: packages/containers] tag 'containers-0.5.6.3-release' created Message-ID: <20150123223942.416E73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New tag : containers-0.5.6.3-release Referencing: a401400fa89b2f942a2e2d22610c21259b45d016 From git at git.haskell.org Fri Jan 23 22:39:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:42 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #65 from dterei/safe710fixes (09ae752) Message-ID: <20150123223942.B66D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/09ae752eeffd06e24ffb4abeabcd6511dea0e68e >--------------------------------------------------------------- commit 09ae752eeffd06e24ffb4abeabcd6511dea0e68e Merge: f9c23af 245ef13 Author: Milan Straka Date: Fri Nov 14 16:15:41 2014 +0100 Merge pull request #65 from dterei/safe710fixes Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. >--------------------------------------------------------------- 09ae752eeffd06e24ffb4abeabcd6511dea0e68e Data/IntMap.hs | 2 +- Data/IntMap/Lazy.hs | 2 +- Data/IntMap/Strict.hs | 4 +++- Data/Utils/StrictFold.hs | 2 +- Data/Utils/StrictPair.hs | 2 +- 5 files changed, 7 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Jan 23 22:39:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:44 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Add IsList instances for OverloadedLists (0e99ba8) Message-ID: <20150123223944.5167A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/0e99ba8851f875c4b44631c7afad3b70e74842c2 >--------------------------------------------------------------- commit 0e99ba8851f875c4b44631c7afad3b70e74842c2 Author: Konstantine Rybnikov Date: Sun Apr 13 22:27:39 2014 +0200 Add IsList instances for OverloadedLists >--------------------------------------------------------------- 0e99ba8851f875c4b44631c7afad3b70e74842c2 Data/IntMap/Base.hs | 16 +++++++++++++++- Data/IntSet/Base.hs | 13 +++++++++++++ Data/Map/Base.hs | 13 +++++++++++++ Data/Set/Base.hs | 13 +++++++++++++ 4 files changed, 54 insertions(+), 1 deletion(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 34a263a..75b3ae9 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -5,6 +5,10 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +{-# LANGUAGE ScopedTypeVariables #-} +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE TypeFamilies #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.IntMap.Base @@ -231,6 +235,9 @@ import Data.StrictPair import Data.Data (Data(..), Constr, mkConstr, constrIndex, Fixity(Prefix), DataType, mkDataType) import GHC.Exts (build) +#if __GLASGOW_HASKELL__ >= 708 +import qualified GHC.Exts as GHCExts +#endif import Text.Read #endif @@ -1770,6 +1777,13 @@ fromSet f (IntSet.Tip kx bm) = buildTree f kx bm (IntSet.suffixBitMask + 1) {-------------------------------------------------------------------- Lists --------------------------------------------------------------------} +#if __GLASGOW_HASKELL__ >= 708 +instance GHCExts.IsList (IntMap a) where + type Item (IntMap a) = (Key,a) + fromList = fromList + toList = toList +#endif + -- | /O(n)/. Convert the map to a list of key\/value pairs. Subject to list -- fusion. -- @@ -1907,7 +1921,7 @@ fromAscListWithKey f (x0 : xs0) = fromDistinctAscList (combineEq x0 xs0) -- -- > fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")] -fromDistinctAscList :: [(Key,a)] -> IntMap a +fromDistinctAscList :: forall a. [(Key,a)] -> IntMap a fromDistinctAscList [] = Nil fromDistinctAscList (z0 : zs0) = work z0 zs0 Nada where diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index be41db5..0063c3f 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -5,6 +5,9 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE TypeFamilies #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.IntSet.Base @@ -198,6 +201,9 @@ import Text.Read #if __GLASGOW_HASKELL__ import GHC.Exts (Int(..), build) +#if __GLASGOW_HASKELL__ >= 708 +import qualified GHC.Exts as GHCExts +#endif import GHC.Prim (indexInt8OffAddr#) #endif @@ -936,6 +942,13 @@ elems {-------------------------------------------------------------------- Lists --------------------------------------------------------------------} +#if __GLASGOW_HASKELL__ >= 708 +instance GHCExts.IsList IntSet where + type Item IntSet = Key + fromList = fromList + toList = toList +#endif + -- | /O(n)/. Convert the set to a list of elements. Subject to list fusion. toList :: IntSet -> [Key] toList diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 6a93a73..69f8276 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -5,6 +5,9 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE TypeFamilies #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.Map.Base @@ -278,6 +281,9 @@ import qualified Data.Set.Base as Set #if __GLASGOW_HASKELL__ import GHC.Exts ( build ) +#if __GLASGOW_HASKELL__ >= 708 +import qualified GHC.Exts as GHCExts +#endif import Text.Read import Data.Data #endif @@ -1948,6 +1954,13 @@ fromSet f (Set.Bin sz x l r) = Bin sz x (f x) (fromSet f l) (fromSet f r) Lists use [foldlStrict] to reduce demand on the control-stack --------------------------------------------------------------------} +#if __GLASGOW_HASKELL__ >= 708 +instance (Ord k) => GHCExts.IsList (Map k v) where + type Item (Map k v) = (k,v) + fromList = fromList + toList = toList +#endif + -- | /O(n*log n)/. Build a map from a list of key\/value pairs. See also 'fromAscList'. -- If the list contains more than one value for the same key, the last value -- for the key is retained. diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index f863d17..94372df 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -5,6 +5,9 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE TypeFamilies #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.Set.Base @@ -194,6 +197,9 @@ import Data.StrictPair #if __GLASGOW_HASKELL__ import GHC.Exts ( build ) +#if __GLASGOW_HASKELL__ >= 708 +import qualified GHC.Exts as GHCExts +#endif import Text.Read import Data.Data #endif @@ -763,6 +769,13 @@ elems = toAscList {-------------------------------------------------------------------- Lists --------------------------------------------------------------------} +#if __GLASGOW_HASKELL__ >= 708 +instance (Ord a) => GHCExts.IsList (Set a) where + type Item (Set a) = a + fromList = fromList + toList = toList +#endif + -- | /O(n)/. Convert the set to a list of elements. Subject to list fusion. toList :: Set a -> [a] toList = toAscList From git at git.haskell.org Fri Jan 23 22:39:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:44 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #67 from hvr/pr-deepseq-14 (c802c36) Message-ID: <20150123223944.BF8C13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c802c36dbed4b800d8c2131181f5af3db837aded >--------------------------------------------------------------- commit c802c36dbed4b800d8c2131181f5af3db837aded Merge: 09ae752 667cf94 Author: Milan Straka Date: Fri Nov 14 16:27:16 2014 +0100 Merge pull request #67 from hvr/pr-deepseq-14 Add support for `deepseq-1.4` >--------------------------------------------------------------- c802c36dbed4b800d8c2131181f5af3db837aded Data/IntSet/Base.hs | 4 ++-- containers.cabal | 22 +++++++++++----------- 2 files changed, 13 insertions(+), 13 deletions(-) From git at git.haskell.org Fri Jan 23 22:39:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:46 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Add LANGUAGE RoleAnnotations for ghc 7.8 (cb08a7e) Message-ID: <20150123223946.5AE663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/cb08a7e06676d38f2f5deb35d0035429c1c10eb1 >--------------------------------------------------------------- commit cb08a7e06676d38f2f5deb35d0035429c1c10eb1 Author: Konstantine Rybnikov Date: Sun Apr 13 23:52:57 2014 +0200 Add LANGUAGE RoleAnnotations for ghc 7.8 >--------------------------------------------------------------- cb08a7e06676d38f2f5deb35d0035429c1c10eb1 Data/Map/Base.hs | 3 +++ Data/Set/Base.hs | 3 +++ 2 files changed, 6 insertions(+) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 6a93a73..95f7b91 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -5,6 +5,9 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.Map.Base diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index f863d17..da3b21d 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -5,6 +5,9 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif ----------------------------------------------------------------------------- -- | -- Module : Data.Set.Base From git at git.haskell.org Fri Jan 23 22:39:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:46 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Improve Foldable methods (c4884ad) Message-ID: <20150123223946.C78BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c4884ad0d7310e62c48ebd23600d73230718ae45 >--------------------------------------------------------------- commit c4884ad0d7310e62c48ebd23600d73230718ae45 Author: David Feuer Date: Mon Nov 17 17:48:10 2014 -0500 Improve Foldable methods Define foldMap for Seq directly, instead of relying on the default based on foldr. Define length and null for ViewR directly, instead of relying on (inappropriate) defaults. >--------------------------------------------------------------- c4884ad0d7310e62c48ebd23600d73230718ae45 Data/Sequence.hs | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 1952b1c..0c2be04 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -149,7 +149,7 @@ import Control.DeepSeq (NFData(rnf)) import Control.Monad (MonadPlus(..), ap) import Data.Monoid (Monoid(..)) import Data.Functor (Functor(..)) -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1), foldl', toList) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', foldr', toList) import Data.Traversable import Data.Typeable @@ -188,6 +188,7 @@ instance Functor Seq where #endif instance Foldable Seq where + foldMap f (Seq xs) = foldMap (foldMap f) xs foldr f z (Seq xs) = foldr (flip (foldr f)) z xs foldl f z (Seq xs) = foldl (foldl f) z xs @@ -310,6 +311,11 @@ instance Sized a => Sized (FingerTree a) where size (Deep v _ _ _) = v instance Foldable FingerTree where + foldMap _ Empty = mempty + foldMap f (Single x) = f x + foldMap f (Deep _ pr m sf) = + foldMap f pr `mappend` (foldMap (foldMap f) m `mappend` foldMap f sf) + foldr _ z Empty = z foldr f z (Single x) = x `f` z foldr f z (Deep _ pr m sf) = @@ -388,6 +394,11 @@ data Digit a #endif instance Foldable Digit where + foldMap f (One a) = f a + foldMap f (Two a b) = f a `mappend` f b + foldMap f (Three a b c) = f a `mappend` (f b `mappend` f c) + foldMap f (Four a b c d) = f a `mappend` (f b `mappend` (f c `mappend` f d)) + foldr f z (One a) = a `f` z foldr f z (Two a b) = a `f` (b `f` z) foldr f z (Three a b c) = a `f` (b `f` (c `f` z)) @@ -458,6 +469,9 @@ data Node a #endif instance Foldable Node where + foldMap f (Node2 _ a b) = f a `mappend` f b + foldMap f (Node3 _ a b c) = f a `mappend` (f b `mappend` f c) + foldr f z (Node2 _ a b) = a `f` (b `f` z) foldr f z (Node3 _ a b c) = a `f` (b `f` (c `f` z)) @@ -508,6 +522,7 @@ instance Functor Elem where fmap f (Elem x) = Elem (f x) instance Foldable Elem where + foldMap f (Elem x) = f x foldr f z (Elem x) = f x z foldl f z (Elem x) = f z x @@ -1009,6 +1024,9 @@ instance Functor ViewR where fmap f (xs :> x) = fmap f xs :> f x instance Foldable ViewR where + foldMap _ EmptyR = mempty + foldMap f (xs :> x) = foldMap f xs `mappend` f x + foldr _ z EmptyR = z foldr f z (xs :> x) = foldr f (f x z) xs @@ -1017,6 +1035,14 @@ instance Foldable ViewR where foldr1 _ EmptyR = error "foldr1: empty view" foldr1 f (xs :> x) = foldr f x xs +#if MIN_VERSION_base(4,8,0) + -- The default definitions are sensible for ViewL, but not so much for + -- ViewR. + null EmptyR = True + null (_ :> _) = False + + length = foldr' (\_ k -> k+1) 0 +#endif instance Traversable ViewR where traverse _ EmptyR = pure EmptyR From git at git.haskell.org Fri Jan 23 22:39:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:48 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #42 from k-bx/add-role-annotations-lang (0098d41) Message-ID: <20150123223948.645873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/0098d41f0aa0460f96eb2251ac743bb7fa137a68 >--------------------------------------------------------------- commit 0098d41f0aa0460f96eb2251ac743bb7fa137a68 Merge: e787f05 cb08a7e Author: Johan Tibell Date: Mon Apr 14 07:01:33 2014 +0100 Merge pull request #42 from k-bx/add-role-annotations-lang Add LANGUAGE RoleAnnotations for ghc 7.8 >--------------------------------------------------------------- 0098d41f0aa0460f96eb2251ac743bb7fa137a68 Data/Map/Base.hs | 3 +++ Data/Set/Base.hs | 3 +++ 2 files changed, 6 insertions(+) From git at git.haskell.org Fri Jan 23 22:39:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:48 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #68 from treeowl/foldmapseq (94fa013) Message-ID: <20150123223948.D16183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/94fa01318f3a575eb3045956415827b582ac9fb8 >--------------------------------------------------------------- commit 94fa01318f3a575eb3045956415827b582ac9fb8 Merge: c802c36 c4884ad Author: Milan Straka Date: Tue Nov 18 10:31:01 2014 +0100 Merge pull request #68 from treeowl/foldmapseq Improve Foldable methods >--------------------------------------------------------------- 94fa01318f3a575eb3045956415827b582ac9fb8 Data/Sequence.hs | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:39:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:50 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Merge language pragmas (bae098f) Message-ID: <20150123223950.6EAD93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/bae098fb0a3994bc2b0ec3313004b40cd097ed8d >--------------------------------------------------------------- commit bae098fb0a3994bc2b0ec3313004b40cd097ed8d Merge: 0098d41 0e99ba8 Author: Johan Tibell Date: Mon Apr 14 08:20:44 2014 +0200 Merge language pragmas >--------------------------------------------------------------- bae098fb0a3994bc2b0ec3313004b40cd097ed8d Data/IntMap/Base.hs | 16 +++++++++++++++- Data/IntSet/Base.hs | 13 +++++++++++++ Data/Map/Base.hs | 11 +++++++++++ Data/Set/Base.hs | 11 +++++++++++ 4 files changed, 50 insertions(+), 1 deletion(-) diff --cc Data/Map/Base.hs index 95f7b91,69f8276..db9549f --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@@ -6,7 -6,7 +6,8 @@@ {-# LANGUAGE Trustworthy #-} #endif #if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} + {-# LANGUAGE TypeFamilies #-} #endif ----------------------------------------------------------------------------- -- | diff --cc Data/Set/Base.hs index da3b21d,94372df..ffcdfd0 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@@ -6,7 -6,7 +6,8 @@@ {-# LANGUAGE Trustworthy #-} #endif #if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} + {-# LANGUAGE TypeFamilies #-} #endif ----------------------------------------------------------------------------- -- | From git at git.haskell.org Fri Jan 23 22:39:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:50 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Implement fmap/coerce rules (ad24ce6) Message-ID: <20150123223950.DF2B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/ad24ce6e10d2a0168dcb4d68765b4a25ae22ad88 >--------------------------------------------------------------- commit ad24ce6e10d2a0168dcb4d68765b4a25ae22ad88 Author: David Feuer Date: Thu Nov 13 00:16:28 2014 -0500 Implement fmap/coerce rules Implement fmap/coerce rules for Map, Sequence, and Tree. One concern: unfortunately, implementing the RULES forces the LANGUAGE to be turned from Safe to Trustworthy. This is rather sad. An alternative would be to do this in another module, but orphan rules are not so lovely either. >--------------------------------------------------------------- ad24ce6e10d2a0168dcb4d68765b4a25ae22ad88 Data/Map/Base.hs | 24 +++++++++++++++++------- Data/Map/Strict.hs | 19 ++++++++++++++++++- Data/Sequence.hs | 27 ++++++++++++++++++++------- Data/Tree.hs | 29 ++++++++++++++++++++++------- tests-ghc/all.T | 3 +++ tests-ghc/mapcoercemap.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoercemap.stdout | 3 +++ tests-ghc/mapcoerceseq.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoerceseq.stdout | 3 +++ tests-ghc/mapcoercesmap.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoercesmap.stdout | 3 +++ 11 files changed, 164 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ad24ce6e10d2a0168dcb4d68765b4a25ae22ad88 From git at git.haskell.org Fri Jan 23 22:39:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:52 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Don't have tests depend on library to avoid dep conflicts (53da0d5) Message-ID: <20150123223952.760283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/53da0d55d8592d86772691322cc7eebae511e29e >--------------------------------------------------------------- commit 53da0d55d8592d86772691322cc7eebae511e29e Author: Johan Tibell Date: Wed Apr 23 08:50:44 2014 +0200 Don't have tests depend on library to avoid dep conflicts >--------------------------------------------------------------- 53da0d55d8592d86772691322cc7eebae511e29e containers.cabal | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/containers.cabal b/containers.cabal index 8abca7a..640cb5e 100644 --- a/containers.cabal +++ b/containers.cabal @@ -211,14 +211,13 @@ Test-suite seq-properties test-framework-quickcheck2 test-suite map-strictness-properties - hs-source-dirs: tests + hs-source-dirs: tests, . main-is: MapStrictness.hs type: exitcode-stdio-1.0 build-depends: base, ChasingBottoms, - containers, QuickCheck >= 2.4.0.1, test-framework >= 0.3.3, test-framework-quickcheck2 >= 0.2.9 @@ -226,14 +225,13 @@ test-suite map-strictness-properties ghc-options: -Wall test-suite intmap-strictness-properties - hs-source-dirs: tests + hs-source-dirs: tests, . main-is: IntMapStrictness.hs type: exitcode-stdio-1.0 build-depends: base, ChasingBottoms, - containers, QuickCheck >= 2.4.0.1, test-framework >= 0.3.3, test-framework-quickcheck2 >= 0.2.9 From git at git.haskell.org Fri Jan 23 22:39:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:52 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #66 from treeowl/seqfmapcoerce (e083f68) Message-ID: <20150123223952.EB3523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/e083f683d833d6ffd98b7b91f27c1e10a2cded97 >--------------------------------------------------------------- commit e083f683d833d6ffd98b7b91f27c1e10a2cded97 Merge: 94fa013 ad24ce6 Author: Milan Straka Date: Tue Nov 18 14:50:46 2014 +0100 Merge pull request #66 from treeowl/seqfmapcoerce Implement fmap/coerce rules >--------------------------------------------------------------- e083f683d833d6ffd98b7b91f27c1e10a2cded97 Data/Map/Base.hs | 24 +++++++++++++++++------- Data/Map/Strict.hs | 19 ++++++++++++++++++- Data/Sequence.hs | 27 ++++++++++++++++++++------- Data/Tree.hs | 29 ++++++++++++++++++++++------- tests-ghc/all.T | 3 +++ tests-ghc/mapcoercemap.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoercemap.stdout | 3 +++ tests-ghc/mapcoerceseq.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoerceseq.stdout | 3 +++ tests-ghc/mapcoercesmap.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoercesmap.stdout | 3 +++ 11 files changed, 164 insertions(+), 22 deletions(-) diff --cc Data/Sequence.hs index 0c2be04,0bef765..1c4e143 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@@ -187,8 -189,18 +189,19 @@@ instance Functor Seq wher x <$ s = replicate (length s) x #endif + fmapSeq :: (a -> b) -> Seq a -> Seq b + fmapSeq f (Seq xs) = Seq (fmap (fmap f) xs) + #if MIN_VERSION_base(4,8,0) + -- Safe coercions were introduced in 4.7.0, but I am not sure if they played + -- well enough with RULES to do what we want. + {-# NOINLINE [1] fmapSeq #-} + {-# RULES + "fmapSeq/coerce" fmapSeq coerce = coerce + #-} + #endif + instance Foldable Seq where + foldMap f (Seq xs) = foldMap (foldMap f) xs foldr f z (Seq xs) = foldr (flip (foldr f)) z xs foldl f z (Seq xs) = foldl (foldl f) z xs From git at git.haskell.org Fri Jan 23 22:39:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:54 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Add missing test dependencies (c17cfaf) Message-ID: <20150123223954.7C1C53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c17cfaf7996942ed305dc1db55ea82da40ed47e4 >--------------------------------------------------------------- commit c17cfaf7996942ed305dc1db55ea82da40ed47e4 Author: Johan Tibell Date: Wed Apr 23 09:25:40 2014 +0200 Add missing test dependencies >--------------------------------------------------------------- c17cfaf7996942ed305dc1db55ea82da40ed47e4 containers.cabal | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/containers.cabal b/containers.cabal index 640cb5e..209589b 100644 --- a/containers.cabal +++ b/containers.cabal @@ -216,9 +216,12 @@ test-suite map-strictness-properties type: exitcode-stdio-1.0 build-depends: - base, + array, + base >= 4.2 && < 5, ChasingBottoms, + deepseq >= 1.2 && < 1.4, QuickCheck >= 2.4.0.1, + ghc-prim, test-framework >= 0.3.3, test-framework-quickcheck2 >= 0.2.9 @@ -230,9 +233,12 @@ test-suite intmap-strictness-properties type: exitcode-stdio-1.0 build-depends: - base, + array, + base >= 4.2 && < 5, ChasingBottoms, + deepseq >= 1.2 && < 1.4, QuickCheck >= 2.4.0.1, + ghc-prim, test-framework >= 0.3.3, test-framework-quickcheck2 >= 0.2.9 From git at git.haskell.org Fri Jan 23 22:39:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:55 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add fmap/fmap rules (352c73d) Message-ID: <20150123223955.024753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/352c73dca04572fc843417518b9f5dd684c1792c >--------------------------------------------------------------- commit 352c73dca04572fc843417518b9f5dd684c1792c Author: David Feuer Date: Tue Nov 18 09:41:29 2014 -0500 Add fmap/fmap rules Specifically, fuse map, mapWithIndex, mapWithKey, etc., with each other. >--------------------------------------------------------------- 352c73dca04572fc843417518b9f5dd684c1792c Data/IntMap/Base.hs | 19 +++++++++++++++++++ Data/IntMap/Strict.hs | 19 +++++++++++++++++++ Data/Map/Base.hs | 19 ++++++++++++++++++- Data/Map/Strict.hs | 24 +++++++++++++++++++++--- Data/Sequence.hs | 19 ++++++++++++++++++- 5 files changed, 95 insertions(+), 5 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 007e41e..3832e1c 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -1301,6 +1301,13 @@ map f t Tip k x -> Tip k (f x) Nil -> Nil +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] map #-} +{-# RULES +"map/map" forall f g xs . map f (map g xs) = map (f . g) xs + #-} +#endif + -- | /O(n)/. Map a function over all values in the map. -- -- > let f key x = (show key) ++ ":" ++ x @@ -1313,6 +1320,18 @@ mapWithKey f t Tip k x -> Tip k (f k x) Nil -> Nil +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] mapWithKey #-} +{-# RULES +"mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) = + mapWithKey (\k a -> f k (g k a)) xs +"mapWithKey/map" forall f g xs . mapWithKey f (map g xs) = + mapWithKey (\k a -> f k (g a)) xs +"map/mapWithKey" forall f g xs . map f (mapWithKey g xs) = + mapWithKey (\k a -> f (g k a)) xs + #-} +#endif + -- | /O(n)/. -- @'traverseWithKey' f s == 'fromList' <$> 'traverse' (\(k, v) -> (,) k <$> f k v) ('toList' m)@ -- That is, behaves exactly like a regular 'traverse' except that the traversing diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs index f1c363c..af44b2a 100644 --- a/Data/IntMap/Strict.hs +++ b/Data/IntMap/Strict.hs @@ -718,6 +718,13 @@ map f t Tip k x -> Tip k $! f x Nil -> Nil +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] map #-} +{-# RULES +"map/map" forall f g xs . map f (map g xs) = map (f . g) xs + #-} +#endif + -- | /O(n)/. Map a function over all values in the map. -- -- > let f key x = (show key) ++ ":" ++ x @@ -730,6 +737,18 @@ mapWithKey f t Tip k x -> Tip k $! f k x Nil -> Nil +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] mapWithKey #-} +{-# RULES +"mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) = + mapWithKey (\k a -> f k (g k a)) xs +"mapWithKey/map" forall f g xs . mapWithKey f (map g xs) = + mapWithKey (\k a -> f k (g a)) xs +"map/mapWithKey" forall f g xs . map f (mapWithKey g xs) = + mapWithKey (\k a -> f (g k a)) xs + #-} +#endif + -- | /O(n)/. The function @'mapAccum'@ threads an accumulating -- argument through the map in ascending order of keys. -- diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 89b851e..3911125 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -1662,10 +1662,15 @@ mapEitherWithKey f0 t0 = toPair $ go f0 t0 map :: (a -> b) -> Map k a -> Map k b map _ Tip = Tip map f (Bin sx kx x l r) = Bin sx kx (f x) (map f l) (map f r) +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] map #-} +{-# RULES +"map/map" forall f g xs . map f (map g xs) = map (f . g) xs + #-} +#endif #if MIN_VERSION_base(4,8,0) -- Safe coercions were introduced in 4.7.0, but I am not sure if they played -- well enough with RULES to do what we want. -{-# NOINLINE [1] map #-} {-# RULES "map/coerce" map coerce = coerce #-} @@ -1680,6 +1685,18 @@ mapWithKey :: (k -> a -> b) -> Map k a -> Map k b mapWithKey _ Tip = Tip mapWithKey f (Bin sx kx x l r) = Bin sx kx (f kx x) (mapWithKey f l) (mapWithKey f r) +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] mapWithKey #-} +{-# RULES +"mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) = + mapWithKey (\k a -> f k (g k a)) xs +"mapWithKey/map" forall f g xs . mapWithKey f (map g xs) = + mapWithKey (\k a -> f k (g a)) xs +"map/mapWithKey" forall f g xs . map f (mapWithKey g xs) = + mapWithKey (\k a -> f (g k a)) xs + #-} +#endif + -- | /O(n)/. -- @'traverseWithKey' f s == 'fromList' <$> 'traverse' (\(k, v) -> (,) k <$> f k v) ('toList' m)@ -- That is, behaves exactly like a regular 'traverse' except that the traversing diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs index 8c7ea0f..6255e91 100644 --- a/Data/Map/Strict.hs +++ b/Data/Map/Strict.hs @@ -935,10 +935,15 @@ mapEitherWithKey f0 t0 = toPair $ go f0 t0 map :: (a -> b) -> Map k a -> Map k b map _ Tip = Tip map f (Bin sx kx x l r) = let x' = f x in x' `seq` Bin sx kx x' (map f l) (map f r) +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] map #-} +{-# RULES +"map/map" forall f g xs . map f (map g xs) = map (f . g) xs + #-} +#endif #if MIN_VERSION_base(4,8,0) -- Safe coercions were introduced in 4.7.0, but I am not sure if they played -- well enough with RULES to do what we want. -{-# NOINLINE [1] map #-} {-# RULES "mapSeq/coerce" map coerce = coerce #-} @@ -951,8 +956,21 @@ map f (Bin sx kx x l r) = let x' = f x in x' `seq` Bin sx kx x' (map f l) (map f mapWithKey :: (k -> a -> b) -> Map k a -> Map k b mapWithKey _ Tip = Tip -mapWithKey f (Bin sx kx x l r) = let x' = f kx x - in x' `seq` Bin sx kx x' (mapWithKey f l) (mapWithKey f r) +mapWithKey f (Bin sx kx x l r) = + let x' = f kx x + in x' `seq` Bin sx kx x' (mapWithKey f l) (mapWithKey f r) + +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] mapWithKey #-} +{-# RULES +"mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) = + mapWithKey (\k a -> f k (g k a)) xs +"mapWithKey/map" forall f g xs . mapWithKey f (map g xs) = + mapWithKey (\k a -> f k (g a)) xs +"map/mapWithKey" forall f g xs . map f (mapWithKey g xs) = + mapWithKey (\k a -> f (g k a)) xs + #-} +#endif -- | /O(n)/. The function 'mapAccum' threads an accumulating -- argument through the map in ascending order of keys. diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 1c4e143..fe59172 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -191,10 +191,15 @@ instance Functor Seq where fmapSeq :: (a -> b) -> Seq a -> Seq b fmapSeq f (Seq xs) = Seq (fmap (fmap f) xs) +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] fmapSeq #-} +{-# RULES +"fmapSeq/fmapSeq" forall f g xs . fmapSeq f (fmapSeq g xs) = fmapSeq (f . g) xs + #-} +#endif #if MIN_VERSION_base(4,8,0) -- Safe coercions were introduced in 4.7.0, but I am not sure if they played -- well enough with RULES to do what we want. -{-# NOINLINE [1] fmapSeq #-} {-# RULES "fmapSeq/coerce" fmapSeq coerce = coerce #-} @@ -1265,6 +1270,18 @@ adjustDigit f i (Four a b c d) mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b mapWithIndex f xs = snd (mapAccumL' (\ i x -> (i + 1, f i x)) 0 xs) +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] mapWithIndex #-} +{-# RULES +"mapWithIndex/mapWithIndex" forall f g xs . mapWithIndex f (mapWithIndex g xs) = + mapWithIndex (\k a -> f k (g k a)) xs +"mapWithIndex/fmapSeq" forall f g xs . mapWithIndex f (fmapSeq g xs) = + mapWithIndex (\k a -> f k (g a)) xs +"fmapSeq/mapWithIndex" forall f g xs . fmapSeq f (mapWithIndex g xs) = + mapWithIndex (\k a -> f (g k a)) xs + #-} +#endif + -- Splitting -- | /O(log(min(i,n-i)))/. The first @i@ elements of a sequence. From git at git.haskell.org Fri Jan 23 22:39:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:56 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Add Travis-CI job control file (234896a) Message-ID: <20150123223956.84AF33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/234896a2bb2c1f57f033b1f19f38ef039e99fe1e >--------------------------------------------------------------- commit 234896a2bb2c1f57f033b1f19f38ef039e99fe1e Author: Herbert Valerio Riedel Date: Tue Apr 22 22:48:36 2014 +0200 Add Travis-CI job control file This builds and tests containers with GHC 7.0, 7.4, 7.6, 7.8, and GHC HEAD (Once haskell/cabal#1806 is fixed we can use CABALVER=1.20 w/ GHCVER=7.8.2) >--------------------------------------------------------------- 234896a2bb2c1f57f033b1f19f38ef039e99fe1e .travis.yml | 60 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 60 insertions(+) diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..67d893c --- /dev/null +++ b/.travis.yml @@ -0,0 +1,60 @@ +# NB: don't set `language: haskell` here + +# See also https://github.com/hvr/multi-ghc-travis for more information +env: + - GHCVER=7.0.4 CABALVER=1.16 + # we have to use CABALVER=1.16 for GHC<7.6 as well, as there's + # no package for earlier cabal versions in the PPA + - GHCVER=7.4.2 CABALVER=1.16 + - GHCVER=7.6.3 CABALVER=1.16 + - GHCVER=7.8.2 CABALVER=1.18 + # NOTE: we can't use Cabal 1.20 yet due to + # https://github.com/haskell/cabal/issues/1806 + - GHCVER=head CABALVER=1.18 + +matrix: + allow_failures: + - env: GHCVER=head CABALVER=1.18 + +# Note: the distinction between `before_install` and `install` is not +# important. +before_install: + - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH + - cabal --version + +install: + - travis_retry cabal update + - cabal install --only-dependencies + # we need to install the test-suite deps manually as the cabal solver would + # otherwise complaing about cyclic deps + - cabal install 'test-framework >= 0.3.3' 'test-framework-quickcheck2 >= 0.2.9' 'QuickCheck >= 2.4.0.1' 'ChasingBottoms' 'HUnit' 'test-framework-hunit' + +# Here starts the actual work to be performed for the package under +# test; any command which exits with a non-zero exit code causes the +# build to fail. +script: + # -v2 provides useful information for debugging + - cabal configure -v2 --enable-tests + + # this builds all libraries and executables + # (including tests/benchmarks) + - cabal build + - cabal test + + # tests that a source-distribution can be generated + - cabal sdist + + # check that the generated source-distribution can be built & installed + - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; + cd dist/; + if [ -f "$SRC_TGZ" ]; then + cabal install --force-reinstalls "$SRC_TGZ"; + else + echo "expected '$SRC_TGZ' not found"; + exit 1; + fi + +# EOF From git at git.haskell.org Fri Jan 23 22:39:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:57 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #69 from treeowl/fmapfmap (b2c1c79) Message-ID: <20150123223957.0BB2A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/b2c1c79893c4b112d98f82dccb006b7453dc4f21 >--------------------------------------------------------------- commit b2c1c79893c4b112d98f82dccb006b7453dc4f21 Merge: e083f68 352c73d Author: Milan Straka Date: Tue Nov 18 16:44:20 2014 +0100 Merge pull request #69 from treeowl/fmapfmap Add fmap/fmap rules >--------------------------------------------------------------- b2c1c79893c4b112d98f82dccb006b7453dc4f21 Data/IntMap/Base.hs | 19 +++++++++++++++++++ Data/IntMap/Strict.hs | 19 +++++++++++++++++++ Data/Map/Base.hs | 19 ++++++++++++++++++- Data/Map/Strict.hs | 24 +++++++++++++++++++++--- Data/Sequence.hs | 19 ++++++++++++++++++- 5 files changed, 95 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Jan 23 22:39:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:58 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Markdownify and extend README (7d8360a) Message-ID: <20150123223958.8F7AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/7d8360ac1e3a484bae714b5253e287a0f77b80c3 >--------------------------------------------------------------- commit 7d8360ac1e3a484bae714b5253e287a0f77b80c3 Author: Herbert Valerio Riedel Date: Wed Apr 23 12:42:06 2014 +0200 Markdownify and extend README >--------------------------------------------------------------- 7d8360ac1e3a484bae714b5253e287a0f77b80c3 README | 6 ------ README.md | 12 ++++++++++++ 2 files changed, 12 insertions(+), 6 deletions(-) diff --git a/README b/README deleted file mode 100644 index 1fb326b..0000000 --- a/README +++ /dev/null @@ -1,6 +0,0 @@ -POTENTIAL CONTRIBUTORS -====================== - -Please follow the guidelines outlined on the Haskell Wiki when proposing an API change. - -http://www.haskell.org/haskellwiki/Library_submissions#Guidance_for_proposers diff --git a/README.md b/README.md new file mode 100644 index 0000000..0eab2ca --- /dev/null +++ b/README.md @@ -0,0 +1,12 @@ +The `containers` Package [![Build Status](https://travis-ci.org/haskell/containers.svg?branch=master)](https://travis-ci.org/haskell/containers) +======================== + +See [`containers` on Hackage](http://hackage.haskell.org/package/containers) for more information. + + +Contributing +------------ + +For reporting bugs (and maybe even the respective fix), please use the [GitHub issue tracker](https://github.com/haskell/containers/issues). + +For proposing API changes/enhancements, please follow the [guidelines outlined on the Haskell Wiki](http://www.haskell.org/haskellwiki/Library_submissions#Guidance_for_proposers) (but use the GitHub facilities instead of GHC's Trac for submitting patches). From git at git.haskell.org Fri Jan 23 22:39:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:39:59 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Implement map/coerce for IntMap (ee3eb5f) Message-ID: <20150123223959.153D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/ee3eb5f19dbbd193e7c8b991c861f8568c7106d9 >--------------------------------------------------------------- commit ee3eb5f19dbbd193e7c8b991c861f8568c7106d9 Author: David Feuer Date: Tue Nov 18 17:39:18 2014 -0500 Implement map/coerce for IntMap I realized what I was doing with MIN_VERSION was kind of silly. The easy/sane thing to do is really to use __GLASGOW_HASKELL__ for the coercion stuff. >--------------------------------------------------------------- ee3eb5f19dbbd193e7c8b991c861f8568c7106d9 Data/IntMap/Base.hs | 23 +++++++++++++++------- Data/IntMap/Strict.hs | 12 ++++++++--- tests-ghc/all.T | 2 ++ tests-ghc/{mapcoercemap.hs => mapcoerceintmap.hs} | 8 ++++---- ...{mapcoercemap.stdout => mapcoerceintmap.stdout} | 0 .../{mapcoercemap.hs => mapcoerceintmapstrict.hs} | 14 ++++++------- ...emap.stdout => mapcoerceintmapstrict.hs.stdout} | 0 7 files changed, 38 insertions(+), 21 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 3832e1c..d5fd75a 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -9,6 +9,13 @@ #if __GLASGOW_HASKELL__ >= 708 {-# LANGUAGE TypeFamilies #-} #endif +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + ----------------------------------------------------------------------------- -- | -- Module : Data.IntMap.Base @@ -240,6 +247,9 @@ import qualified GHC.Exts as GHCExts #endif import Text.Read #endif +#if __GLASGOW_HASKELL__ >= 709 +import Data.Coerce +#endif -- Use macros to define strictness of functions. -- STRICT_x_OF_y denotes an y-ary function strict in the x-th parameter. @@ -247,13 +257,6 @@ import Text.Read -- want the compilers to be compiled by as many compilers as possible. #define STRICT_1_OF_2(fn) fn arg _ | arg `seq` False = undefined --- We use cabal-generated MIN_VERSION_base to adapt to changes of base. --- Nevertheless, as a convenience, we also allow compiling without cabal by --- defining trivial MIN_VERSION_base if needed. -#ifndef MIN_VERSION_base -#define MIN_VERSION_base(major1,major2,minor) 0 -#endif - -- A "Nat" is a natural machine word (an unsigned Int) type Nat = Word @@ -1307,6 +1310,12 @@ map f t "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} #endif +#if __GLASGOW_HASKELL__ >= 709 +-- Safe coercions were introduced in 7.8, but did not play well with RULES yet. +{-# RULES +"map/coerce" map coerce = coerce + #-} +#endif -- | /O(n)/. Map a function over all values in the map. -- diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs index af44b2a..d7f45f7 100644 --- a/Data/IntMap/Strict.hs +++ b/Data/IntMap/Strict.hs @@ -1,7 +1,5 @@ {-# LANGUAGE CPP #-} -#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 709 -{-# LANGUAGE Safe #-} -#elif !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 +#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- @@ -262,6 +260,9 @@ import qualified Data.IntSet.Base as IntSet import Data.Utils.BitUtil import Data.Utils.StrictFold import Data.Utils.StrictPair +#if __GLASGOW_HASKELL__ >= 709 +import Data.Coerce +#endif -- $strictness -- @@ -724,6 +725,11 @@ map f t "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} #endif +#if __GLASGOW_HASKELL__ >= 709 +{-# RULES +"map/coerce" map coerce = coerce + #-} +#endif -- | /O(n)/. Map a function over all values in the map. -- diff --git a/tests-ghc/all.T b/tests-ghc/all.T index 6a8a339..eba1dcc 100644 --- a/tests-ghc/all.T +++ b/tests-ghc/all.T @@ -8,3 +8,5 @@ test('sequence001', normal, compile_and_run, ['-package containers']) test('mapcoerceseq', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) test('mapcoercemap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) test('mapcoercesmap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) +test('mapcoerceintmap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) +test('mapcoerceintmapstrict', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) diff --git a/tests-ghc/mapcoercemap.hs b/tests-ghc/mapcoerceintmap.hs similarity index 76% copy from tests-ghc/mapcoercemap.hs copy to tests-ghc/mapcoerceintmap.hs index 6dd336d..ded48c7 100644 --- a/tests-ghc/mapcoercemap.hs +++ b/tests-ghc/mapcoerceintmap.hs @@ -2,15 +2,15 @@ import GHC.Exts hiding (fromList) import Unsafe.Coerce -import Data.Map +import Data.IntMap.Lazy newtype Age = Age Int -fooAge :: Map Int Int -> Map Int Age +fooAge :: IntMap Int -> IntMap Age fooAge = fmap Age -fooCoerce :: Map Int Int -> Map Int Age +fooCoerce :: IntMap Int -> IntMap Age fooCoerce = fmap coerce -fooUnsafeCoerce :: Map Int Int -> Map Int Age +fooUnsafeCoerce :: IntMap Int -> IntMap Age fooUnsafeCoerce = fmap unsafeCoerce same :: a -> b -> IO () diff --git a/tests-ghc/mapcoercemap.stdout b/tests-ghc/mapcoerceintmap.stdout similarity index 100% copy from tests-ghc/mapcoercemap.stdout copy to tests-ghc/mapcoerceintmap.stdout diff --git a/tests-ghc/mapcoercemap.hs b/tests-ghc/mapcoerceintmapstrict.hs similarity index 61% copy from tests-ghc/mapcoercemap.hs copy to tests-ghc/mapcoerceintmapstrict.hs index 6dd336d..2e97004 100644 --- a/tests-ghc/mapcoercemap.hs +++ b/tests-ghc/mapcoerceintmapstrict.hs @@ -2,16 +2,16 @@ import GHC.Exts hiding (fromList) import Unsafe.Coerce -import Data.Map +import Data.IntMap.Strict as IM newtype Age = Age Int -fooAge :: Map Int Int -> Map Int Age -fooAge = fmap Age -fooCoerce :: Map Int Int -> Map Int Age -fooCoerce = fmap coerce -fooUnsafeCoerce :: Map Int Int -> Map Int Age -fooUnsafeCoerce = fmap unsafeCoerce +fooAge :: IntMap Int -> IntMap Age +fooAge = IM.map Age +fooCoerce :: IntMap Int -> IntMap Age +fooCoerce = IM.map coerce +fooUnsafeCoerce :: IntMap Int -> IntMap Age +fooUnsafeCoerce = IM.map unsafeCoerce same :: a -> b -> IO () same x y = case reallyUnsafePtrEquality# (unsafeCoerce x) y of diff --git a/tests-ghc/mapcoercemap.stdout b/tests-ghc/mapcoerceintmapstrict.hs.stdout similarity index 100% copy from tests-ghc/mapcoercemap.stdout copy to tests-ghc/mapcoerceintmapstrict.hs.stdout From git at git.haskell.org Fri Jan 23 22:40:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:00 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Try to use CABALVER=1.20 again (e5d74fa) Message-ID: <20150123224000.95EA23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/e5d74fa883ef2d66511d12cdb62b9586abff14c5 >--------------------------------------------------------------- commit e5d74fa883ef2d66511d12cdb62b9586abff14c5 Author: Herbert Valerio Riedel Date: Sat May 3 17:45:13 2014 +0200 Try to use CABALVER=1.20 again ...hoping that haskell/cabal#1806 has been resolved for good >--------------------------------------------------------------- e5d74fa883ef2d66511d12cdb62b9586abff14c5 .travis.yml | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 67d893c..8af3116 100644 --- a/.travis.yml +++ b/.travis.yml @@ -8,13 +8,11 @@ env: - GHCVER=7.4.2 CABALVER=1.16 - GHCVER=7.6.3 CABALVER=1.16 - GHCVER=7.8.2 CABALVER=1.18 - # NOTE: we can't use Cabal 1.20 yet due to - # https://github.com/haskell/cabal/issues/1806 - - GHCVER=head CABALVER=1.18 + - GHCVER=head CABALVER=1.20 matrix: allow_failures: - - env: GHCVER=head CABALVER=1.18 + - env: GHCVER=head CABALVER=1.20 # Note: the distinction between `before_install` and `install` is not # important. From git at git.haskell.org Fri Jan 23 22:40:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:01 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Optimize *> and >> for Seq (22ef7de) Message-ID: <20150123224001.1D5BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/22ef7de71a5de7f9447f3fdcf16fa8f786cb84c0 >--------------------------------------------------------------- commit 22ef7de71a5de7f9447f3fdcf16fa8f786cb84c0 Author: David Feuer Date: Wed Nov 19 15:14:01 2014 -0500 Optimize *> and >> for Seq Based on a discussion with Ross Paterson, use a multiplication- by-doubling algorithm to improve asymptotic time and space performance. >--------------------------------------------------------------- 22ef7de71a5de7f9447f3fdcf16fa8f786cb84c0 Data/Sequence.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 1c4e143..2cfa9c7 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -228,11 +228,13 @@ instance Monad Seq where return = singleton xs >>= f = foldl' add empty xs where add ys x = ys >< f x + (>>) = (*>) instance Applicative Seq where pure = singleton fs <*> xs = foldl' add empty fs where add ys f = ys >< fmap f xs + xs *> ys = replicateSeq (length xs) ys instance MonadPlus Seq where mzero = empty @@ -655,6 +657,19 @@ replicateM n x | n >= 0 = unwrapMonad (replicateA n (WrapMonad x)) | otherwise = error "replicateM takes a nonnegative integer argument" +-- | @'replicateSeq' n xs@ concatenates @n@ copies of @xs at . +replicateSeq :: Int -> Seq a -> Seq a +replicateSeq n xs + | n < 0 = error "replicateSeq takes a nonnegative integer argument" + | n == 0 = empty + | otherwise = go n xs + where + -- Invariant: k >= 1 + go 1 xs = xs + go k xs | even k = kxs + | otherwise = xs >< kxs + where kxs = go (k `quot` 2) $! (xs >< xs) + -- | /O(1)/. Add an element to the left end of a sequence. -- Mnemonic: a triangle with the single element at the pointy end. (<|) :: a -> Seq a -> Seq a From git at git.haskell.org Fri Jan 23 22:40:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:02 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: tree: Fix imports for the Applicative/Monad change (c40e6dd) Message-ID: <20150123224002.9D90F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c40e6dd40861d788ee0cc337775d803d8907b6ff >--------------------------------------------------------------- commit c40e6dd40861d788ee0cc337775d803d8907b6ff Author: Austin Seipp Date: Mon May 12 07:31:59 2014 -0500 tree: Fix imports for the Applicative/Monad change Due to various problems with orphans and cycles in base, while implementing the Applicative/Monad Proposal, Alternative joined MonadPlus in Control.Monad. A knock-on effect of this is that Control.Monad now exports 'empty', which conflicts with Data.Sequence in this case. Luckily the fix is actually quite easy: just restrict the imports to liftM, since that's all we use anyway. Signed-off-by: Austin Seipp >--------------------------------------------------------------- c40e6dd40861d788ee0cc337775d803d8907b6ff Data/Tree.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Tree.hs b/Data/Tree.hs index 56af20f..dab25c2 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -32,7 +32,7 @@ module Data.Tree( ) where import Control.Applicative (Applicative(..), (<$>)) -import Control.Monad +import Control.Monad (liftM) import Data.Monoid (Monoid(..)) import Data.Sequence (Seq, empty, singleton, (<|), (|>), fromList, ViewL(..), ViewR(..), viewl, viewr) From git at git.haskell.org Fri Jan 23 22:40:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:03 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #71 from treeowl/fmapcoerceintmap (bcebc7a) Message-ID: <20150123224003.268823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/bcebc7af8d347d6229836847cd09ce6971dd6db4 >--------------------------------------------------------------- commit bcebc7af8d347d6229836847cd09ce6971dd6db4 Merge: b2c1c79 ee3eb5f Author: Milan Straka Date: Fri Nov 21 07:56:17 2014 +0100 Merge pull request #71 from treeowl/fmapcoerceintmap Implement map/coerce for IntMap >--------------------------------------------------------------- bcebc7af8d347d6229836847cd09ce6971dd6db4 Data/IntMap/Base.hs | 23 +++++++++++++++------- Data/IntMap/Strict.hs | 12 ++++++++--- tests-ghc/all.T | 2 ++ tests-ghc/{mapcoercemap.hs => mapcoerceintmap.hs} | 8 ++++---- ...{mapcoercemap.stdout => mapcoerceintmap.stdout} | 0 .../{mapcoercemap.hs => mapcoerceintmapstrict.hs} | 14 ++++++------- ...emap.stdout => mapcoerceintmapstrict.hs.stdout} | 0 7 files changed, 38 insertions(+), 21 deletions(-) From git at git.haskell.org Fri Jan 23 22:40:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:04 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #44 from thoughtpolice/amp (e84c5d2) Message-ID: <20150123224004.A543A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/e84c5d2145415cb0beacce0909a551ae5e28d396 >--------------------------------------------------------------- commit e84c5d2145415cb0beacce0909a551ae5e28d396 Merge: e5d74fa c40e6dd Author: Milan Straka Date: Mon May 12 15:05:18 2014 +0200 Merge pull request #44 from thoughtpolice/amp tree: Fix imports for the Applicative/Monad change >--------------------------------------------------------------- e84c5d2145415cb0beacce0909a551ae5e28d396 Data/Tree.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:40:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:05 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #72 from treeowl/then (dde7a53) Message-ID: <20150123224005.3001E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/dde7a531b506096ae32b358c2dc83f3edac91ec2 >--------------------------------------------------------------- commit dde7a531b506096ae32b358c2dc83f3edac91ec2 Merge: bcebc7a 22ef7de Author: Milan Straka Date: Fri Nov 21 08:06:03 2014 +0100 Merge pull request #72 from treeowl/then Optimize *> and >> for Seq >--------------------------------------------------------------- dde7a531b506096ae32b358c2dc83f3edac91ec2 Data/Sequence.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) From git at git.haskell.org Fri Jan 23 22:40:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:06 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Added fixity declarations for member, notMember, union, and intersection. (3999b51) Message-ID: <20150123224006.B04253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/3999b512f5aa28a7b119a18b286a8485d1285319 >--------------------------------------------------------------- commit 3999b512f5aa28a7b119a18b286a8485d1285319 Author: Peter Selinger Date: Fri Jul 4 10:31:20 2014 -0300 Added fixity declarations for member, notMember, union, and intersection. >--------------------------------------------------------------- 3999b512f5aa28a7b119a18b286a8485d1285319 Data/IntMap/Base.hs | 8 ++++++++ Data/IntSet/Base.hs | 7 +++++++ Data/Map/Base.hs | 8 ++++++++ Data/Set/Base.hs | 8 ++++++++ 4 files changed, 31 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 75b3ae9..9f7be70 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,6 +395,8 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the key not a member of the map? -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -403,6 +405,8 @@ member k = k `seq` go notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m +infix 4 notMember + -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. -- See Note: Local 'go' functions and capturing] @@ -818,6 +822,8 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 +infixl 5 union + -- | /O(n+m)/. The union with a combining function. -- -- > unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")] @@ -881,6 +887,8 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 +infixl 5 intersection + -- | /O(n+m)/. The intersection with a combining function. -- -- > intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA" diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 0063c3f..9719de1 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,10 +332,14 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -523,6 +527,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t +infixl 5 union {-------------------------------------------------------------------- Difference @@ -597,6 +602,8 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil +infixl 5 intersection + {-------------------------------------------------------------------- Subset --------------------------------------------------------------------} diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index db9549f..9d066fa 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,6 +456,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -469,6 +471,8 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. find :: Ord k => k -> Map k a -> a @@ -1230,6 +1234,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b hedgeUnion _ _ t1 Tip = t1 @@ -1350,6 +1356,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index ffcdfd0..5727de6 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,6 +318,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool notMember a t = not $ member a t @@ -327,6 +329,8 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -578,6 +582,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 hedgeUnion blo bhi Tip (Bin _ x l r) = link x (filterGt blo l) (filterLt bhi r) @@ -636,6 +642,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip From git at git.haskell.org Fri Jan 23 22:40:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:07 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Use GHC version for coercion rules (8da46db) Message-ID: <20150123224007.3BCFF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/8da46dbc4598062397c6a6b684f7bae9931f3d80 >--------------------------------------------------------------- commit 8da46dbc4598062397c6a6b684f7bae9931f3d80 Author: David Feuer Date: Fri Nov 21 10:14:38 2014 -0500 Use GHC version for coercion rules Using the library version didn't make much sense, especially since the tests-ghc tests had to switch on compiler version anyway, but also because compiling without cabal would prevent the code from being used. The conditional fake MIN_VERSION_base definition should probably stay up top where I moved it, though, in case someone needs to use it to adjust imports or exports in the future--the top seems an inherently better place for that. >--------------------------------------------------------------- 8da46dbc4598062397c6a6b684f7bae9931f3d80 Data/Map/Base.hs | 7 +++---- Data/Map/Strict.hs | 7 +++---- Data/Sequence.hs | 7 +++---- 3 files changed, 9 insertions(+), 12 deletions(-) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 3911125..e582e16 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -294,7 +294,7 @@ import qualified GHC.Exts as GHCExts import Text.Read import Data.Data #endif -#if MIN_VERSION_base(4,8,0) +#if __GLASGOW_HASKELL__ >= 709 import Data.Coerce #endif @@ -1668,9 +1668,8 @@ map f (Bin sx kx x l r) = Bin sx kx (f x) (map f l) (map f r) "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} #endif -#if MIN_VERSION_base(4,8,0) --- Safe coercions were introduced in 4.7.0, but I am not sure if they played --- well enough with RULES to do what we want. +#if __GLASGOW_HASKELL__ >= 709 +-- Safe coercions were introduced in 7.8, but did not work well with RULES yet. {-# RULES "map/coerce" map coerce = coerce #-} diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs index 6255e91..88f494e 100644 --- a/Data/Map/Strict.hs +++ b/Data/Map/Strict.hs @@ -279,7 +279,7 @@ import Data.Utils.StrictFold import Data.Utils.StrictPair import Data.Bits (shiftL, shiftR) -#if MIN_VERSION_base(4,8,0) +#if __GLASGOW_HASKELL__ >= 709 import Data.Coerce #endif @@ -941,9 +941,8 @@ map f (Bin sx kx x l r) = let x' = f x in x' `seq` Bin sx kx x' (map f l) (map f "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} #endif -#if MIN_VERSION_base(4,8,0) --- Safe coercions were introduced in 4.7.0, but I am not sure if they played --- well enough with RULES to do what we want. +#if __GLASGOW_HASKELL__ >= 709 +-- Safe coercions were introduced in 7.8, but did not work well with RULES yet. {-# RULES "mapSeq/coerce" map coerce = coerce #-} diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 331ac30..4799056 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -165,7 +165,7 @@ import Text.Read (Lexeme(Ident), lexP, parens, prec, readPrec, readListPrec, readListPrecDefault) import Data.Data #endif -#if MIN_VERSION_base(4,8,0) +#if __GLASGOW_HASKELL__ >= 709 import Data.Coerce #endif @@ -197,9 +197,8 @@ fmapSeq f (Seq xs) = Seq (fmap (fmap f) xs) "fmapSeq/fmapSeq" forall f g xs . fmapSeq f (fmapSeq g xs) = fmapSeq (f . g) xs #-} #endif -#if MIN_VERSION_base(4,8,0) --- Safe coercions were introduced in 4.7.0, but I am not sure if they played --- well enough with RULES to do what we want. +#if __GLASGOW_HASKELL__ >= 709 +-- Safe coercions were introduced in 7.8, but did not work well with RULES yet. {-# RULES "fmapSeq/coerce" fmapSeq coerce = coerce #-} From git at git.haskell.org Fri Jan 23 22:40:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:08 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Fixed syntax of fixity declarations. (07ab0fa) Message-ID: <20150123224008.BA9CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/07ab0fa052843dc8fd4c874876d03d8a71525f87 >--------------------------------------------------------------- commit 07ab0fa052843dc8fd4c874876d03d8a71525f87 Author: Peter Selinger Date: Fri Jul 4 10:47:35 2014 -0300 Fixed syntax of fixity declarations. >--------------------------------------------------------------- 07ab0fa052843dc8fd4c874876d03d8a71525f87 Data/IntMap/Base.hs | 8 ++++---- Data/IntSet/Base.hs | 8 ++++---- Data/Map/Base.hs | 8 ++++---- Data/Set/Base.hs | 8 ++++---- 4 files changed, 16 insertions(+), 16 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 9f7be70..237aea8 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,7 +395,7 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the key not a member of the map? -- @@ -405,7 +405,7 @@ infix 4 member notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 notMember +infix 4 `notMember` -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. @@ -822,7 +822,7 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 union +infixl 5 `union` -- | /O(n+m)/. The union with a combining function. -- @@ -887,7 +887,7 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 intersection +infixl 5 `intersection` -- | /O(n+m)/. The intersection with a combining function. -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 9719de1..5aee4ef 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,13 +332,13 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -527,7 +527,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 union +infixl 5 `union` {-------------------------------------------------------------------- Difference @@ -602,7 +602,7 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 intersection +infixl 5 `intersection` {-------------------------------------------------------------------- Subset diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 9d066fa..bc2fd47 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,7 +456,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- @@ -471,7 +471,7 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. @@ -1234,7 +1234,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b @@ -1356,7 +1356,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 5727de6..d0533f5 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,7 +318,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool @@ -329,7 +329,7 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -582,7 +582,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 @@ -642,7 +642,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip From git at git.haskell.org Fri Jan 23 22:40:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:09 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #75 from treeowl/coerce-version (ddf12fd) Message-ID: <20150123224009.441913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/ddf12fd51a0611cba8250bdbde9fdcbb66211b1d >--------------------------------------------------------------- commit ddf12fd51a0611cba8250bdbde9fdcbb66211b1d Merge: dde7a53 8da46db Author: Milan Straka Date: Fri Nov 21 18:50:11 2014 +0100 Merge pull request #75 from treeowl/coerce-version Use GHC version for coercion rules >--------------------------------------------------------------- ddf12fd51a0611cba8250bdbde9fdcbb66211b1d Data/Map/Base.hs | 7 +++---- Data/Map/Strict.hs | 7 +++---- Data/Sequence.hs | 7 +++---- 3 files changed, 9 insertions(+), 12 deletions(-) From git at git.haskell.org Fri Jan 23 22:40:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:10 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Revert "Fixed syntax of fixity declarations." (fa2c888) Message-ID: <20150123224010.C5AE33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/fa2c8880efd7adf81e33de72f1a38a0c2b31e90b >--------------------------------------------------------------- commit fa2c8880efd7adf81e33de72f1a38a0c2b31e90b Author: Johan Tibell Date: Tue Jul 22 17:09:30 2014 +0200 Revert "Fixed syntax of fixity declarations." This reverts commit 07ab0fa052843dc8fd4c874876d03d8a71525f87. >--------------------------------------------------------------- fa2c8880efd7adf81e33de72f1a38a0c2b31e90b Data/IntMap/Base.hs | 8 ++++---- Data/IntSet/Base.hs | 8 ++++---- Data/Map/Base.hs | 8 ++++---- Data/Set/Base.hs | 8 ++++---- 4 files changed, 16 insertions(+), 16 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 237aea8..9f7be70 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,7 +395,7 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 `member` +infix 4 member -- | /O(min(n,W))/. Is the key not a member of the map? -- @@ -405,7 +405,7 @@ infix 4 `member` notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 `notMember` +infix 4 notMember -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. @@ -822,7 +822,7 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 `union` +infixl 5 union -- | /O(n+m)/. The union with a combining function. -- @@ -887,7 +887,7 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 `intersection` +infixl 5 intersection -- | /O(n+m)/. The intersection with a combining function. -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 5aee4ef..9719de1 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,13 +332,13 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 `member` +infix 4 member -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k -infix 4 `notMember` +infix 4 notMember -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -527,7 +527,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 `union` +infixl 5 union {-------------------------------------------------------------------- Difference @@ -602,7 +602,7 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 `intersection` +infixl 5 intersection {-------------------------------------------------------------------- Subset diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index bc2fd47..9d066fa 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,7 +456,7 @@ member = go {-# INLINE member #-} #endif -infix 4 `member` +infix 4 member -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- @@ -471,7 +471,7 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 `notMember` +infix 4 notMember -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. @@ -1234,7 +1234,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 `union` +infixl 5 union -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b @@ -1356,7 +1356,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 `intersection` +infixl 5 intersection hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index d0533f5..5727de6 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,7 +318,7 @@ member = go {-# INLINE member #-} #endif -infix 4 `member` +infix 4 member -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool @@ -329,7 +329,7 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 `notMember` +infix 4 notMember -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -582,7 +582,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 `union` +infixl 5 union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 @@ -642,7 +642,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 `intersection` +infixl 5 intersection hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip From git at git.haskell.org Fri Jan 23 22:40:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:11 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Use Data.Functor.Identity (bd7b470) Message-ID: <20150123224011.4AEAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/bd7b470abda94c486c784fd7d6c69dd91e0ae2be >--------------------------------------------------------------- commit bd7b470abda94c486c784fd7d6c69dd91e0ae2be Author: David Feuer Date: Fri Nov 21 11:25:58 2014 -0500 Use Data.Functor.Identity This has just entered base, and includes some optimizations that may or may not be relevant. For older versions, don't bother making Identity a Monad instance--it's not exported, and that instance is never used. Make applicativeTree slightly more readable. >--------------------------------------------------------------- bd7b470abda94c486c784fd7d6c69dd91e0ae2be Data/Sequence.hs | 40 ++++++++++++++++++++-------------------- 1 file changed, 20 insertions(+), 20 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 4799056..4e37dbf 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -168,6 +168,9 @@ import Data.Data #if __GLASGOW_HASKELL__ >= 709 import Data.Coerce #endif +#if MIN_VERSION_base(4,8,0) +import Data.Functor.Identity (Identity(..)) +#endif infixr 5 `consTree` @@ -554,19 +557,16 @@ instance NFData a => NFData (Elem a) where ------------------------------------------------------- -- Applicative construction ------------------------------------------------------- +#if !MIN_VERSION_base(4,8,0) +newtype Identity a = Identity {runIdentity :: a} -newtype Id a = Id {runId :: a} - -instance Functor Id where - fmap f (Id x) = Id (f x) - -instance Monad Id where - return = Id - m >>= k = k (runId m) +instance Functor Identity where + fmap f (Identity x) = Identity (f x) -instance Applicative Id where - pure = return - (<*>) = ap +instance Applicative Identity where + pure = Identity + Identity f <*> Identity x = Identity (f x) +#endif -- | This is essentially a clone of Control.Monad.State.Strict. newtype State s a = State {runState :: s -> (s, a)} @@ -598,13 +598,13 @@ mapAccumL' f s t = runState (traverse (State . flip f) t) s -- specified. This is a generalization of 'replicateA', which itself -- is a generalization of many Data.Sequence methods. {-# SPECIALIZE applicativeTree :: Int -> Int -> State s a -> State s (FingerTree a) #-} -{-# SPECIALIZE applicativeTree :: Int -> Int -> Id a -> Id (FingerTree a) #-} --- Special note: the Id specialization automatically does node sharing, +{-# SPECIALIZE applicativeTree :: Int -> Int -> Identity a -> Identity (FingerTree a) #-} +-- Special note: the Identity specialization automatically does node sharing, -- reducing memory usage of the resulting tree to /O(log n)/. applicativeTree :: Applicative f => Int -> Int -> f a -> f (FingerTree a) applicativeTree n mSize m = mSize `seq` case n of 0 -> pure Empty - 1 -> liftA Single m + 1 -> fmap Single m 2 -> deepA one emptyTree one 3 -> deepA two emptyTree one 4 -> deepA two emptyTree two @@ -612,12 +612,12 @@ applicativeTree n mSize m = mSize `seq` case n of 6 -> deepA three emptyTree three 7 -> deepA four emptyTree three 8 -> deepA four emptyTree four - _ -> let (q, r) = n `quotRem` 3 in q `seq` case r of - 0 -> deepA three (applicativeTree (q - 2) mSize' n3) three - 1 -> deepA four (applicativeTree (q - 2) mSize' n3) three - _ -> deepA four (applicativeTree (q - 2) mSize' n3) four + _ -> case n `quotRem` 3 of + (q,0) -> deepA three (applicativeTree (q - 2) mSize' n3) three + (q,1) -> deepA four (applicativeTree (q - 2) mSize' n3) three + (q,_) -> deepA four (applicativeTree (q - 2) mSize' n3) four where - one = liftA One m + one = fmap One m two = liftA2 Two m m three = liftA3 Three m m m four = liftA3 Four m m m <*> m @@ -641,7 +641,7 @@ singleton x = Seq (Single (Elem x)) -- | /O(log n)/. @replicate n x@ is a sequence consisting of @n@ copies of @x at . replicate :: Int -> a -> Seq a replicate n x - | n >= 0 = runId (replicateA n (Id x)) + | n >= 0 = runIdentity (replicateA n (Identity x)) | otherwise = error "replicate takes a nonnegative integer argument" -- | 'replicateA' is an 'Applicative' version of 'replicate', and makes From git at git.haskell.org Fri Jan 23 22:40:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:12 +0000 (UTC) Subject: [commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Revert "Added fixity declarations for member, notMember, union, and intersection." (3b1eee5) Message-ID: <20150123224012.D0AE73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/3b1eee514581edcc51c3c4304087e2dff30e05cd >--------------------------------------------------------------- commit 3b1eee514581edcc51c3c4304087e2dff30e05cd Author: Johan Tibell Date: Tue Jul 22 17:09:50 2014 +0200 Revert "Added fixity declarations for member, notMember, union, and intersection." This reverts commit 3999b512f5aa28a7b119a18b286a8485d1285319. >--------------------------------------------------------------- 3b1eee514581edcc51c3c4304087e2dff30e05cd Data/IntMap/Base.hs | 8 -------- Data/IntSet/Base.hs | 7 ------- Data/Map/Base.hs | 8 -------- Data/Set/Base.hs | 8 -------- 4 files changed, 31 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 9f7be70..75b3ae9 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,8 +395,6 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 member - -- | /O(min(n,W))/. Is the key not a member of the map? -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -405,8 +403,6 @@ infix 4 member notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 notMember - -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. -- See Note: Local 'go' functions and capturing] @@ -822,8 +818,6 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 union - -- | /O(n+m)/. The union with a combining function. -- -- > unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")] @@ -887,8 +881,6 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 intersection - -- | /O(n+m)/. The intersection with a combining function. -- -- > intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA" diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 9719de1..0063c3f 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,14 +332,10 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 member - -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k -infix 4 notMember - -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -527,7 +523,6 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 union {-------------------------------------------------------------------- Difference @@ -602,8 +597,6 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 intersection - {-------------------------------------------------------------------- Subset --------------------------------------------------------------------} diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 9d066fa..db9549f 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,8 +456,6 @@ member = go {-# INLINE member #-} #endif -infix 4 member - -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -471,8 +469,6 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 notMember - -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. find :: Ord k => k -> Map k a -> a @@ -1234,8 +1230,6 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union - -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b hedgeUnion _ _ t1 Tip = t1 @@ -1356,8 +1350,6 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection - hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 5727de6..ffcdfd0 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,8 +318,6 @@ member = go {-# INLINE member #-} #endif -infix 4 member - -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool notMember a t = not $ member a t @@ -329,8 +327,6 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 notMember - -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -582,8 +578,6 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union - hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 hedgeUnion blo bhi Tip (Bin _ x l r) = link x (filterGt blo l) (filterLt bhi r) @@ -642,8 +636,6 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection - hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip From git at git.haskell.org Fri Jan 23 22:40:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:13 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #76 from treeowl/identity (c138008) Message-ID: <20150123224013.52E523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c1380089319e24ce1373b6cd0a027f7447b45d32 >--------------------------------------------------------------- commit c1380089319e24ce1373b6cd0a027f7447b45d32 Merge: ddf12fd bd7b470 Author: Milan Straka Date: Fri Nov 21 19:56:10 2014 +0100 Merge pull request #76 from treeowl/identity Use Data.Functor.Identity >--------------------------------------------------------------- c1380089319e24ce1373b6cd0a027f7447b45d32 Data/Sequence.hs | 40 ++++++++++++++++++++-------------------- 1 file changed, 20 insertions(+), 20 deletions(-) From git at git.haskell.org Fri Jan 23 22:40:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:14 +0000 (UTC) Subject: [commit: packages/containers] develop: Added fixity declarations for member, notMember, union, and intersection. (4dd6e01) Message-ID: <20150123224014.DC7163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop Link : http://git.haskell.org/packages/containers.git/commitdiff/4dd6e01a78774de5e5dd6639b55a2902e610e0cc >--------------------------------------------------------------- commit 4dd6e01a78774de5e5dd6639b55a2902e610e0cc Author: Peter Selinger Date: Fri Jul 4 10:31:20 2014 -0300 Added fixity declarations for member, notMember, union, and intersection. >--------------------------------------------------------------- 4dd6e01a78774de5e5dd6639b55a2902e610e0cc Data/IntMap/Base.hs | 8 ++++++++ Data/IntSet/Base.hs | 7 +++++++ Data/Map/Base.hs | 8 ++++++++ Data/Set/Base.hs | 8 ++++++++ 4 files changed, 31 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 75b3ae9..9f7be70 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,6 +395,8 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the key not a member of the map? -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -403,6 +405,8 @@ member k = k `seq` go notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m +infix 4 notMember + -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. -- See Note: Local 'go' functions and capturing] @@ -818,6 +822,8 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 +infixl 5 union + -- | /O(n+m)/. The union with a combining function. -- -- > unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")] @@ -881,6 +887,8 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 +infixl 5 intersection + -- | /O(n+m)/. The intersection with a combining function. -- -- > intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA" diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 0063c3f..9719de1 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,10 +332,14 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -523,6 +527,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t +infixl 5 union {-------------------------------------------------------------------- Difference @@ -597,6 +602,8 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil +infixl 5 intersection + {-------------------------------------------------------------------- Subset --------------------------------------------------------------------} diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index db9549f..9d066fa 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,6 +456,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -469,6 +471,8 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. find :: Ord k => k -> Map k a -> a @@ -1230,6 +1234,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b hedgeUnion _ _ t1 Tip = t1 @@ -1350,6 +1356,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index ffcdfd0..5727de6 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,6 +318,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool notMember a t = not $ member a t @@ -327,6 +329,8 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -578,6 +582,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 hedgeUnion blo bhi Tip (Bin _ x l r) = link x (filterGt blo l) (filterLt bhi r) @@ -636,6 +642,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip From git at git.haskell.org Fri Jan 23 22:40:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:15 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Make index middle-lazy (aedfe3f) Message-ID: <20150123224015.5B5533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/aedfe3f327f781484ec6fb4718156919791c4979 >--------------------------------------------------------------- commit aedfe3f327f781484ec6fb4718156919791c4979 Author: David Feuer Date: Sun Nov 23 15:36:39 2014 -0500 Make index middle-lazy `index` should not descend the finger tree spine unless it needs to. >--------------------------------------------------------------- aedfe3f327f781484ec6fb4718156919791c4979 Data/Sequence.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 4e37dbf..511cad9 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1159,14 +1159,14 @@ data Place a = Place {-# UNPACK #-} !Int a lookupTree :: Sized a => Int -> FingerTree a -> Place a lookupTree _ Empty = error "lookupTree of empty tree" lookupTree i (Single x) = Place i x -lookupTree i (Deep _ pr m sf) +lookupTree i (Deep totalSize pr m sf) | i < spr = lookupDigit i pr | i < spm = case lookupTree (i - spr) m of Place i' xs -> lookupNode i' xs | otherwise = lookupDigit (i - spm) sf where spr = size pr - spm = spr + size m + spm = totalSize - size sf {-# SPECIALIZE lookupNode :: Int -> Node (Elem a) -> Place (Elem a) #-} {-# SPECIALIZE lookupNode :: Int -> Node (Node a) -> Place (Node a) #-} From git at git.haskell.org Fri Jan 23 22:40:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:16 +0000 (UTC) Subject: [commit: packages/containers] develop: Fixed syntax of fixity declarations. (6ec9b1b) Message-ID: <20150123224016.E88ED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop Link : http://git.haskell.org/packages/containers.git/commitdiff/6ec9b1b4be2d7c264ebd2aa9d6ed06c98029cf8f >--------------------------------------------------------------- commit 6ec9b1b4be2d7c264ebd2aa9d6ed06c98029cf8f Author: Peter Selinger Date: Fri Jul 4 10:47:35 2014 -0300 Fixed syntax of fixity declarations. >--------------------------------------------------------------- 6ec9b1b4be2d7c264ebd2aa9d6ed06c98029cf8f Data/IntMap/Base.hs | 8 ++++---- Data/IntSet/Base.hs | 8 ++++---- Data/Map/Base.hs | 8 ++++---- Data/Set/Base.hs | 8 ++++---- 4 files changed, 16 insertions(+), 16 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 9f7be70..237aea8 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -395,7 +395,7 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the key not a member of the map? -- @@ -405,7 +405,7 @@ infix 4 member notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 notMember +infix 4 `notMember` -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. @@ -822,7 +822,7 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 union +infixl 5 `union` -- | /O(n+m)/. The union with a combining function. -- @@ -887,7 +887,7 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 intersection +infixl 5 `intersection` -- | /O(n+m)/. The intersection with a combining function. -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 9719de1..5aee4ef 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -332,13 +332,13 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -527,7 +527,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 union +infixl 5 `union` {-------------------------------------------------------------------- Difference @@ -602,7 +602,7 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 intersection +infixl 5 `intersection` {-------------------------------------------------------------------- Subset diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 9d066fa..bc2fd47 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -456,7 +456,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- @@ -471,7 +471,7 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. @@ -1234,7 +1234,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b @@ -1356,7 +1356,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 5727de6..d0533f5 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -318,7 +318,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool @@ -329,7 +329,7 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -582,7 +582,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 @@ -642,7 +642,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip From git at git.haskell.org Fri Jan 23 22:40:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:17 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #80 from treeowl/fix-index (e1e75b8) Message-ID: <20150123224017.641203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/e1e75b83e3f4bd4bf4031d01d3cec56428c2be33 >--------------------------------------------------------------- commit e1e75b83e3f4bd4bf4031d01d3cec56428c2be33 Merge: c138008 aedfe3f Author: Milan Straka Date: Sun Nov 23 23:05:14 2014 +0100 Merge pull request #80 from treeowl/fix-index Make index middle-lazy >--------------------------------------------------------------- e1e75b83e3f4bd4bf4031d01d3cec56428c2be33 Data/Sequence.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Jan 23 22:40:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:18 +0000 (UTC) Subject: [commit: packages/containers] develop: Merge branch 'selinger-master' into develop. (f8629a2) Message-ID: <20150123224018.F38EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop Link : http://git.haskell.org/packages/containers.git/commitdiff/f8629a228545896ed9133fd72ebbcf97336767da >--------------------------------------------------------------- commit f8629a228545896ed9133fd72ebbcf97336767da Merge: 3b1eee5 6ec9b1b Author: Milan Straka Date: Fri Aug 8 11:06:49 2014 +0200 Merge branch 'selinger-master' into develop. PVP: Major version bump is needed. >--------------------------------------------------------------- f8629a228545896ed9133fd72ebbcf97336767da Data/IntMap/Base.hs | 8 ++++++++ Data/IntSet/Base.hs | 7 +++++++ Data/Map/Base.hs | 8 ++++++++ Data/Set/Base.hs | 8 ++++++++ 4 files changed, 31 insertions(+) From git at git.haskell.org Fri Jan 23 22:40:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:19 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add an IsList instance for Data.Sequence.Seq (1931ecf) Message-ID: <20150123224019.6DA923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/1931ecf7da3d4e4ead4bd1ef5f5ed07807893339 >--------------------------------------------------------------- commit 1931ecf7da3d4e4ead4bd1ef5f5ed07807893339 Author: David Feuer Date: Wed Dec 3 17:16:39 2014 -0500 Add an IsList instance for Data.Sequence.Seq >--------------------------------------------------------------- 1931ecf7da3d4e4ead4bd1ef5f5ed07807893339 Data/Sequence.hs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 511cad9..757f677 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -5,6 +5,9 @@ #if __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE TypeFamilies #-} +#endif -- We use cabal-generated MIN_VERSION_base to adapt to changes of base. -- Nevertheless, as a convenience, we also allow compiling without cabal by -- defining trivial MIN_VERSION_base if needed. @@ -171,7 +174,9 @@ import Data.Coerce #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity(..)) #endif - +#if __GLASGOW_HASKELL__ >= 708 +import qualified GHC.Exts +#endif infixr 5 `consTree` infixl 5 `snocTree` @@ -1655,6 +1660,13 @@ findIndicesR p xs = foldlWithIndex g [] xs fromList :: [a] -> Seq a fromList = Data.List.foldl' (|>) empty +#if __GLASGOW_HASKELL__ >= 708 +instance GHC.Exts.IsList (Seq a) where + type Item (Seq a) = a + fromList = fromList + toList = toList +#endif + ------------------------------------------------------------------------ -- Reverse ------------------------------------------------------------------------ From git at git.haskell.org Fri Jan 23 22:40:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:21 +0000 (UTC) Subject: [commit: packages/containers] develop: Make types of the drawing functions more generic, i.e. Show s => Tree s instead of Tree String (2c85f08) Message-ID: <20150123224021.07F4F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop Link : http://git.haskell.org/packages/containers.git/commitdiff/2c85f0823848ef7f70a27944bc4741c91ca1c0ef >--------------------------------------------------------------- commit 2c85f0823848ef7f70a27944bc4741c91ca1c0ef Author: jonasc Date: Fri Aug 8 00:15:10 2014 +0200 Make types of the drawing functions more generic, i.e. Show s => Tree s instead of Tree String >--------------------------------------------------------------- 2c85f0823848ef7f70a27944bc4741c91ca1c0ef Data/Tree.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/Data/Tree.hs b/Data/Tree.hs index dab25c2..7cfba42 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -83,15 +83,15 @@ instance NFData a => NFData (Tree a) where rnf (Node x ts) = rnf x `seq` rnf ts -- | Neat 2-dimensional drawing of a tree. -drawTree :: Tree String -> String +drawTree :: Show a => Tree a -> String drawTree = unlines . draw -- | Neat 2-dimensional drawing of a forest. -drawForest :: Forest String -> String +drawForest :: Show a => Forest a -> String drawForest = unlines . map drawTree -draw :: Tree String -> [String] -draw (Node x ts0) = x : drawSubTrees ts0 +draw :: Show a => Tree a -> [String] +draw (Node x ts0) = show x : drawSubTrees ts0 where drawSubTrees [] = [] drawSubTrees [t] = From git at git.haskell.org Fri Jan 23 22:40:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:21 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #85 from treeowl/islist (cd5a854) Message-ID: <20150123224021.781513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/cd5a854691c34dbea4a7fddd166095b7d2f0b3e0 >--------------------------------------------------------------- commit cd5a854691c34dbea4a7fddd166095b7d2f0b3e0 Merge: e1e75b8 1931ecf Author: Milan Straka Date: Thu Dec 4 10:01:51 2014 +0100 Merge pull request #85 from treeowl/islist Add an IsList instance for Data.Sequence.Seq >--------------------------------------------------------------- cd5a854691c34dbea4a7fddd166095b7d2f0b3e0 Data/Sequence.hs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:40:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:23 +0000 (UTC) Subject: [commit: packages/containers] develop: Merge branch 'jonasc-master' into develop (b44b6a7) Message-ID: <20150123224023.0FA003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop Link : http://git.haskell.org/packages/containers.git/commitdiff/b44b6a727c123c0ec33e8ac0f1299ac73ee1d0ef >--------------------------------------------------------------- commit b44b6a727c123c0ec33e8ac0f1299ac73ee1d0ef Merge: f8629a2 2c85f08 Author: Milan Straka Date: Fri Aug 8 11:07:42 2014 +0200 Merge branch 'jonasc-master' into develop PVP: Major version bump is needed. >--------------------------------------------------------------- b44b6a727c123c0ec33e8ac0f1299ac73ee1d0ef Data/Tree.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) From git at git.haskell.org Fri Jan 23 22:40:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:23 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Make version-appropriate Foldable imports (39e9ee9) Message-ID: <20150123224023.7DD293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/39e9ee9992269eb2ad3a9b7e608457c6d1a92b04 >--------------------------------------------------------------- commit 39e9ee9992269eb2ad3a9b7e608457c6d1a92b04 Author: David Feuer Date: Thu Dec 4 10:59:22 2014 -0500 Make version-appropriate Foldable imports foldl' and foldr' moved into the Foldable class, then toList. This gets rid of a warning about the imports. >--------------------------------------------------------------- 39e9ee9992269eb2ad3a9b7e608457c6d1a92b04 Data/Sequence.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 511cad9..88faf62 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -155,7 +155,15 @@ import Control.DeepSeq (NFData(rnf)) import Control.Monad (MonadPlus(..), ap) import Data.Monoid (Monoid(..)) import Data.Functor (Functor(..)) +#if MIN_VERSION_base(4,8,0) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr', toList)) +#else +#if MIN_VERSION_base(4,6,0) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr'), toList) +#else import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', foldr', toList) +#endif +#endif import Data.Traversable import Data.Typeable From git at git.haskell.org Fri Jan 23 22:40:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:25 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Use defensive `Data.Foldable` import (74f9b89) Message-ID: <20150123224025.1B0013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/74f9b89a542240e7ab510ee4fb73a4d46035b8ea >--------------------------------------------------------------- commit 74f9b89a542240e7ab510ee4fb73a4d46035b8ea Author: Herbert Valerio Riedel Date: Sat Sep 27 15:12:33 2014 +0200 Use defensive `Data.Foldable` import With this `import`-style containers will compile warning free with existing GHC versions as well as GHC HEAD (in its current form) This change is also needed because `Data.Foldable` is planned to export `null` and `length` which will otherwise clash with `Data.Sequence` >--------------------------------------------------------------- 74f9b89a542240e7ab510ee4fb73a4d46035b8ea Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 9bfd6f9..6bbebdb 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -149,7 +149,7 @@ import Control.DeepSeq (NFData(rnf)) import Control.Monad (MonadPlus(..), ap) import Data.Monoid (Monoid(..)) import Data.Functor (Functor(..)) -import Data.Foldable +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1), foldl', toList) import Data.Traversable import Data.Typeable From git at git.haskell.org Fri Jan 23 22:40:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:25 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #86 from treeowl/foldableimports (f22d14b) Message-ID: <20150123224025.886253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/f22d14b56e2c70d6525436a178912c7010bd5169 >--------------------------------------------------------------- commit f22d14b56e2c70d6525436a178912c7010bd5169 Merge: cd5a854 39e9ee9 Author: Milan Straka Date: Fri Dec 5 07:12:40 2014 +0100 Merge pull request #86 from treeowl/foldableimports Make version-appropriate Foldable imports >--------------------------------------------------------------- f22d14b56e2c70d6525436a178912c7010bd5169 Data/Sequence.hs | 8 ++++++++ 1 file changed, 8 insertions(+) From git at git.haskell.org Fri Jan 23 22:40:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:27 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #54 from hvr/pr-foldable (085e1b8) Message-ID: <20150123224027.2252C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/085e1b8b2cfbd1159bbc9f8cbf6a4127cc32227b >--------------------------------------------------------------- commit 085e1b8b2cfbd1159bbc9f8cbf6a4127cc32227b Merge: 3b1eee5 74f9b89 Author: Milan Straka Date: Sun Sep 28 12:45:42 2014 +0200 Merge pull request #54 from hvr/pr-foldable Use defensive `Data.Foldable` import >--------------------------------------------------------------- 085e1b8b2cfbd1159bbc9f8cbf6a4127cc32227b Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:40:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:27 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6,develop-0.6-questionable,master,zip-devel: Specialize splitTraverse; strictify pair splitting (7e6d75f) Message-ID: <20150123224027.9202F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/7e6d75f9cfb524ccb3c7dfd149c6f7f74e276285 >--------------------------------------------------------------- commit 7e6d75f9cfb524ccb3c7dfd149c6f7f74e276285 Author: David Feuer Date: Wed Dec 3 13:27:41 2014 -0500 Specialize splitTraverse; strictify pair splitting Explicitly specialize `splitTraverse` functions to the necessary types. This has no immediate performance impact, but makes it clearer what the functions are about. Make splitting pairs a bit stricter; we don't need that much laziness. >--------------------------------------------------------------- 7e6d75f9cfb524ccb3c7dfd149c6f7f74e276285 Data/Sequence.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 10d3a92..9955584 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1726,14 +1726,18 @@ instance Splittable (Seq a) where splitState = splitAt instance (Splittable a, Splittable b) => Splittable (a, b) where - splitState i (a, b) = ((al, bl), (ar, br)) + splitState i (a, b) = (al `seq` bl `seq` (al, bl), ar `seq` br `seq` (ar, br)) where (al, ar) = splitState i a (bl, br) = splitState i b +{-# SPECIALIZE splitTraverseSeq :: (Seq x -> a -> b) -> Seq x -> Seq a -> Seq b #-} +{-# SPECIALIZE splitTraverseSeq :: ((Seq x, Seq y) -> a -> b) -> (Seq x, Seq y) -> Seq a -> Seq b #-} splitTraverseSeq :: (Splittable s) => (s -> a -> b) -> s -> Seq a -> Seq b splitTraverseSeq f s (Seq xs) = Seq $ splitTraverseTree (\s' (Elem a) -> Elem (f s' a)) s xs +{-# SPECIALIZE splitTraverseTree :: (Seq x -> Elem y -> b) -> Seq x -> FingerTree (Elem y) -> FingerTree b #-} +{-# SPECIALIZE splitTraverseTree :: (Seq x -> Node y -> b) -> Seq x -> FingerTree (Node y) -> FingerTree b #-} splitTraverseTree :: (Sized a, Splittable s) => (s -> a -> b) -> s -> FingerTree a -> FingerTree b splitTraverseTree _f _s Empty = Empty splitTraverseTree f s (Single xs) = Single $ f s xs @@ -1742,6 +1746,8 @@ splitTraverseTree f s (Deep n pr m sf) = Deep n (splitTraverseDigit f prs pr) (s (prs, r) = splitState (size pr) s (ms, sfs) = splitState (n - size pr - size sf) r +{-# SPECIALIZE splitTraverseDigit :: (Seq x -> Elem y -> b) -> Seq x -> Digit (Elem y) -> Digit b #-} +{-# SPECIALIZE splitTraverseDigit :: (Seq x -> Node y -> b) -> Seq x -> Digit (Node y) -> Digit b #-} splitTraverseDigit :: (Sized a, Splittable s) => (s -> a -> b) -> s -> Digit a -> Digit b splitTraverseDigit f s (One a) = One (f s a) splitTraverseDigit f s (Two a b) = Two (f first a) (f second b) @@ -1757,6 +1763,8 @@ splitTraverseDigit f s (Four a b c d) = Four (f first a) (f second b) (f third c (middle, fourth) = splitState (size b + size c) s' (second, third) = splitState (size b) middle +{-# SPECIALIZE splitTraverseNode :: (Seq x -> Elem y -> b) -> Seq x -> Node (Elem y) -> Node b #-} +{-# SPECIALIZE splitTraverseNode :: (Seq x -> Node y -> b) -> Seq x -> Node (Node y) -> Node b #-} splitTraverseNode :: (Sized a, Splittable s) => (s -> a -> b) -> s -> Node a -> Node b splitTraverseNode f s (Node2 ns a b) = Node2 ns (f first a) (f second b) where From git at git.haskell.org Fri Jan 23 22:40:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:29 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Move foldlStrict (defined 4 times) to Data.StrictFold. (27a5da9) Message-ID: <20150123224029.2E3193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/27a5da9e0a99b2df2cfb267eed2dae8167c746a2 >--------------------------------------------------------------- commit 27a5da9e0a99b2df2cfb267eed2dae8167c746a2 Author: Milan Straka Date: Sun Oct 12 11:06:53 2014 +0200 Move foldlStrict (defined 4 times) to Data.StrictFold. The foldlStrict is Data.List.foldl' which is always inlined, which allows more optimizations. Also, foldl' is not Haskell 98, although it is Haskell 2010. >--------------------------------------------------------------- 27a5da9e0a99b2df2cfb267eed2dae8167c746a2 Data/IntMap/Base.hs | 9 +-------- Data/IntMap/Strict.hs | 1 + Data/IntSet/Base.hs | 7 +------ Data/Map/Base.hs | 9 +-------- Data/Map/Strict.hs | 2 ++ Data/Set/Base.hs | 7 +------ Data/StrictFold.hs | 16 ++++++++++++++++ containers.cabal | 1 + 8 files changed, 24 insertions(+), 28 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 75b3ae9..8d04bfa 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -211,7 +211,6 @@ module Data.IntMap.Base ( , shorter , branchMask , highestBitMask - , foldlStrict ) where import Control.Applicative (Applicative(pure, (<*>)), (<$>)) @@ -229,6 +228,7 @@ import Prelude hiding (lookup, map, filter, foldr, foldl, null) import Data.BitUtil import Data.IntSet.Base (Key) import qualified Data.IntSet.Base as IntSet +import Data.StrictFold import Data.StrictPair #if __GLASGOW_HASKELL__ @@ -2085,13 +2085,6 @@ branchMask p1 p2 Utilities --------------------------------------------------------------------} -foldlStrict :: (a -> b -> a) -> a -> [b] -> a -foldlStrict f = go - where - go z [] = z - go z (x:xs) = let z' = f z x in z' `seq` go z' xs -{-# INLINE foldlStrict #-} - -- | /O(1)/. Decompose a map into pieces based on the structure of the underlying -- tree. This function is useful for consuming a map in parallel. -- diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs index 2ca3707..f19682e 100644 --- a/Data/IntMap/Strict.hs +++ b/Data/IntMap/Strict.hs @@ -258,6 +258,7 @@ import Data.IntMap.Base hiding import Data.BitUtil import qualified Data.IntSet.Base as IntSet +import Data.StrictFold import Data.StrictPair -- $strictness diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 0063c3f..c843d46 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -192,6 +192,7 @@ import Data.Word (Word) import Prelude hiding (filter, foldr, foldl, null, map) import Data.BitUtil +import Data.StrictFold import Data.StrictPair #if __GLASGOW_HASKELL__ @@ -1491,12 +1492,6 @@ bitcount a0 x0 = go a0 x0 {-------------------------------------------------------------------- Utilities --------------------------------------------------------------------} -foldlStrict :: (a -> b -> a) -> a -> [b] -> a -foldlStrict f = go - where - go z [] = z - go z (x:xs) = let z' = f z x in z' `seq` go z' xs -{-# INLINE foldlStrict #-} -- | /O(1)/. Decompose a set into pieces based on the structure of the underlying -- tree. This function is useful for consuming a set in parallel. diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index db9549f..650e003 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -262,7 +262,6 @@ module Data.Map.Base ( , glue , trim , trimLookupLo - , foldlStrict , MaybeS(..) , filterGt , filterLt @@ -279,6 +278,7 @@ import Data.Typeable import Prelude hiding (lookup, map, filter, foldr, foldl, null) import qualified Data.Set.Base as Set +import Data.StrictFold #if __GLASGOW_HASKELL__ import GHC.Exts ( build ) @@ -2826,13 +2826,6 @@ validsize t {-------------------------------------------------------------------- Utilities --------------------------------------------------------------------} -foldlStrict :: (a -> b -> a) -> a -> [b] -> a -foldlStrict f = go - where - go z [] = z - go z (x:xs) = let z' = f z x in z' `seq` go z' xs -{-# INLINE foldlStrict #-} - -- | /O(1)/. Decompose a map into pieces based on the structure of the underlying -- tree. This function is useful for consuming a map in parallel. diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs index 75a29c8..4e0d820 100644 --- a/Data/Map/Strict.hs +++ b/Data/Map/Strict.hs @@ -269,7 +269,9 @@ import Data.Map.Base hiding , updateMaxWithKey ) import qualified Data.Set.Base as Set +import Data.StrictFold import Data.StrictPair + import Data.Bits (shiftL, shiftR) -- Use macros to define strictness of functions. STRICT_x_OF_y diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index ffcdfd0..3a2c938 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -194,6 +194,7 @@ import qualified Data.Foldable as Foldable import Data.Typeable import Control.DeepSeq (NFData(rnf)) +import Data.StrictFold import Data.StrictPair #if __GLASGOW_HASKELL__ @@ -1416,12 +1417,6 @@ bin x l r {-------------------------------------------------------------------- Utilities --------------------------------------------------------------------} -foldlStrict :: (a -> b -> a) -> a -> [b] -> a -foldlStrict f = go - where - go z [] = z - go z (x:xs) = let z' = f z x in z' `seq` go z' xs -{-# INLINE foldlStrict #-} -- | /O(1)/. Decompose a set into pieces based on the structure of the underlying -- tree. This function is useful for consuming a set in parallel. diff --git a/Data/StrictFold.hs b/Data/StrictFold.hs new file mode 100644 index 0000000..9c90a66 --- /dev/null +++ b/Data/StrictFold.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE CPP #-} +#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 +{-# LANGUAGE Trustworthy #-} +#endif +module Data.StrictFold (foldlStrict) where + +-- | Same as regular 'Data.List.foldl'', but marked INLINE so that it is always +-- inlined. This allows further optimization of the call to f, which can be +-- optimized/specialised/inlined. + +foldlStrict :: (a -> b -> a) -> a -> [b] -> a +foldlStrict f = go + where + go z [] = z + go z (x:xs) = let z' = f z x in z' `seq` go z' xs +{-# INLINE foldlStrict #-} diff --git a/containers.cabal b/containers.cabal index 209589b..a952a77 100644 --- a/containers.cabal +++ b/containers.cabal @@ -57,6 +57,7 @@ Library Data.IntSet.Base Data.Map.Base Data.Set.Base + Data.StrictFold Data.StrictPair include-dirs: include From git at git.haskell.org Fri Jan 23 22:40:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:29 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Make zipWith faster (31e1234) Message-ID: <20150123224029.9A38A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/31e1234435ae734bbf3d33a79e9cce89d06ac738 >--------------------------------------------------------------- commit 31e1234435ae734bbf3d33a79e9cce89d06ac738 Author: David Feuer Date: Tue Dec 2 17:09:49 2014 -0500 Make zipWith faster Make `zipWith` build its result with the structure of its first argument, splitting up its second argument as it goes. This allows fast random access to the elements of the results immediately, without having to build large portions of the structure. It also seems to be slightly faster than the old implementation when the entire result is used, presumably by avoiding rebalancing costs. I believe most of this code will also help implement a fast `(<*>)`. Use the same approach to implement `zipWith3` and `zipWith4`. Clean up a couple warnings. Many thanks to Carter Schonwald for suggesting that I use the structure of the first sequence to structure the result, and for helping me come up with the splitTraverse approach. Benchmarks: Zipping two 100000 element lists and extracting the 50000th element takes about 11.4ms with the new implementation, as opposed to 88ms with the old. Zipping two 10000 element sequences and forcing the result to normal form takes 4.0ms now rather than 19.7ms. The indexing gains show up for even very short sequences, but the new implementation really starts to look good once the size gets to around 1000--presumably it handles cache effects better than the old one. Note that the naive approach of converting sequences to lists, zipping them, and then converting back, actually works very well for forcing short sequences to normal form, even better than the new implementation. But it starts to lose a lot of ground by the time the size gets to around 10000, and its performance on the indexing tests is bad. >--------------------------------------------------------------- 31e1234435ae734bbf3d33a79e9cce89d06ac738 Data/Sequence.hs | 106 +++++++++++++++++++++++++++++++++++++++++++++++-------- 1 file changed, 92 insertions(+), 14 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index b54f1e6..10d3a92 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -676,10 +676,10 @@ replicateM n x -- | @'replicateSeq' n xs@ concatenates @n@ copies of @xs at . replicateSeq :: Int -> Seq a -> Seq a -replicateSeq n xs +replicateSeq n s | n < 0 = error "replicateSeq takes a nonnegative integer argument" | n == 0 = empty - | otherwise = go n xs + | otherwise = go n s where -- Invariant: k >= 1 go 1 xs = xs @@ -1703,6 +1703,75 @@ reverseNode f (Node2 s a b) = Node2 s (f b) (f a) reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) ------------------------------------------------------------------------ +-- Traversing with splittable "state" +------------------------------------------------------------------------ + +-- For zipping, and probably also for (<*>), it is useful to build a result by +-- traversing a sequence while splitting up something else. For zipping, we +-- traverse the first sequence while splitting up the second [and third [and +-- fourth]]. For fs <*> xs, we expect soon to traverse +-- +-- > replicate (length fs * length xs) () +-- +-- while splitting something essentially equivalent to +-- +-- > fmap (\f -> fmap f xs) fs +-- +-- David Feuer, with excellent guidance from Carter Schonwald, December 2014 + +class Splittable s where + splitState :: Int -> s -> (s,s) + +instance Splittable (Seq a) where + splitState = splitAt + +instance (Splittable a, Splittable b) => Splittable (a, b) where + splitState i (a, b) = ((al, bl), (ar, br)) + where + (al, ar) = splitState i a + (bl, br) = splitState i b + +splitTraverseSeq :: (Splittable s) => (s -> a -> b) -> s -> Seq a -> Seq b +splitTraverseSeq f s (Seq xs) = Seq $ splitTraverseTree (\s' (Elem a) -> Elem (f s' a)) s xs + +splitTraverseTree :: (Sized a, Splittable s) => (s -> a -> b) -> s -> FingerTree a -> FingerTree b +splitTraverseTree _f _s Empty = Empty +splitTraverseTree f s (Single xs) = Single $ f s xs +splitTraverseTree f s (Deep n pr m sf) = Deep n (splitTraverseDigit f prs pr) (splitTraverseTree (splitTraverseNode f) ms m) (splitTraverseDigit f sfs sf) + where + (prs, r) = splitState (size pr) s + (ms, sfs) = splitState (n - size pr - size sf) r + +splitTraverseDigit :: (Sized a, Splittable s) => (s -> a -> b) -> s -> Digit a -> Digit b +splitTraverseDigit f s (One a) = One (f s a) +splitTraverseDigit f s (Two a b) = Two (f first a) (f second b) + where + (first, second) = splitState (size a) s +splitTraverseDigit f s (Three a b c) = Three (f first a) (f second b) (f third c) + where + (first, r) = splitState (size a) s + (second, third) = splitState (size b) r +splitTraverseDigit f s (Four a b c d) = Four (f first a) (f second b) (f third c) (f fourth d) + where + (first, s') = splitState (size a) s + (middle, fourth) = splitState (size b + size c) s' + (second, third) = splitState (size b) middle + +splitTraverseNode :: (Sized a, Splittable s) => (s -> a -> b) -> s -> Node a -> Node b +splitTraverseNode f s (Node2 ns a b) = Node2 ns (f first a) (f second b) + where + (first, second) = splitState (size a) s +splitTraverseNode f s (Node3 ns a b c) = Node3 ns (f first a) (f second b) (f third c) + where + (first, r) = splitState (size a) s + (second, third) = splitState (size b) r + +getSingleton :: Seq a -> a +getSingleton (Seq (Single (Elem a))) = a +getSingleton (Seq Empty) = error "getSingleton: Empty" +getSingleton _ = error "getSingleton: Not a singleton." + +------------------------------------------------------------------------ -- Zipping ------------------------------------------------------------------------ @@ -1717,17 +1786,11 @@ zip = zipWith (,) -- For example, @zipWith (+)@ is applied to two sequences to take the -- sequence of corresponding sums. zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c -zipWith f xs ys - | length xs <= length ys = zipWith' f xs ys - | otherwise = zipWith' (flip f) ys xs - --- like 'zipWith', but assumes length xs <= length ys -zipWith' :: (a -> b -> c) -> Seq a -> Seq b -> Seq c -zipWith' f xs ys = snd (mapAccumL k ys xs) +zipWith f s1 s2 = splitTraverseSeq (\s a -> f a (getSingleton s)) s2' s1' where - k kys x = case viewl kys of - (z :< zs) -> (zs, f x z) - EmptyL -> error "zipWith': unexpected EmptyL" + minLen = min (length s1) (length s2) + s1' = take minLen s1 + s2' = take minLen s2 -- | /O(min(n1,n2,n3))/. 'zip3' takes three sequences and returns a -- sequence of triples, analogous to 'zip'. @@ -1738,7 +1801,14 @@ zip3 = zipWith3 (,,) -- three elements, as well as three sequences and returns a sequence of -- their point-wise combinations, analogous to 'zipWith'. zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d -zipWith3 f s1 s2 s3 = zipWith ($) (zipWith f s1 s2) s3 +zipWith3 f s1 s2 s3 = splitTraverseSeq (\s a -> + case s of + (b, c) -> f a (getSingleton b) (getSingleton c)) (s2', s3') s1' + where + minLen = minimum [length s1, length s2, length s3] + s1' = take minLen s1 + s2' = take minLen s2 + s3' = take minLen s3 -- | /O(min(n1,n2,n3,n4))/. 'zip4' takes four sequences and returns a -- sequence of quadruples, analogous to 'zip'. @@ -1749,7 +1819,15 @@ zip4 = zipWith4 (,,,) -- four elements, as well as four sequences and returns a sequence of -- their point-wise combinations, analogous to 'zipWith'. zipWith4 :: (a -> b -> c -> d -> e) -> Seq a -> Seq b -> Seq c -> Seq d -> Seq e -zipWith4 f s1 s2 s3 s4 = zipWith ($) (zipWith ($) (zipWith f s1 s2) s3) s4 +zipWith4 f s1 s2 s3 s4 = splitTraverseSeq (\s a -> + case s of + (b, (c, d)) -> f a (getSingleton b) (getSingleton c) (getSingleton d)) (s2', (s3', s4')) s1' + where + minLen = minimum [length s1, length s2, length s3, length s4] + s1' = take minLen s1 + s2' = take minLen s2 + s3' = take minLen s3 + s4' = take minLen s4 ------------------------------------------------------------------------ -- Sorting From git at git.haskell.org Fri Jan 23 22:40:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:31 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Move utilities (BitUtils, Strict{Fold, Pair}) to Utils directory. (9cfe43a) Message-ID: <20150123224031.3D0483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/9cfe43a9790f8c8511f93f380e7d7168bb1c1a88 >--------------------------------------------------------------- commit 9cfe43a9790f8c8511f93f380e7d7168bb1c1a88 Author: Milan Straka Date: Sun Oct 12 11:13:13 2014 +0200 Move utilities (BitUtils,Strict{Fold,Pair}) to Utils directory. The Data directory was becoming a little too crowded. >--------------------------------------------------------------- 9cfe43a9790f8c8511f93f380e7d7168bb1c1a88 Data/IntMap/Base.hs | 6 +++--- Data/IntMap/Strict.hs | 6 +++--- Data/IntSet/Base.hs | 6 +++--- Data/Map/Base.hs | 4 ++-- Data/Map/Strict.hs | 4 ++-- Data/Set/Base.hs | 4 ++-- Data/{ => Utils}/BitUtil.hs | 4 ++-- Data/{ => Utils}/StrictFold.hs | 2 +- Data/{ => Utils}/StrictPair.hs | 2 +- containers.cabal | 6 +++--- 10 files changed, 22 insertions(+), 22 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 8d04bfa..fec5abe 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -225,11 +225,11 @@ import Data.Typeable import Data.Word (Word) import Prelude hiding (lookup, map, filter, foldr, foldl, null) -import Data.BitUtil import Data.IntSet.Base (Key) import qualified Data.IntSet.Base as IntSet -import Data.StrictFold -import Data.StrictPair +import Data.Utils.BitUtil +import Data.Utils.StrictFold +import Data.Utils.StrictPair #if __GLASGOW_HASKELL__ import Data.Data (Data(..), Constr, mkConstr, constrIndex, Fixity(Prefix), diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs index f19682e..3a7dde8 100644 --- a/Data/IntMap/Strict.hs +++ b/Data/IntMap/Strict.hs @@ -256,10 +256,10 @@ import Data.IntMap.Base hiding , fromDistinctAscList ) -import Data.BitUtil import qualified Data.IntSet.Base as IntSet -import Data.StrictFold -import Data.StrictPair +import Data.Utils.BitUtil +import Data.Utils.StrictFold +import Data.Utils.StrictPair -- $strictness -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index c843d46..309ab42 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -191,9 +191,9 @@ import Data.Typeable import Data.Word (Word) import Prelude hiding (filter, foldr, foldl, null, map) -import Data.BitUtil -import Data.StrictFold -import Data.StrictPair +import Data.Utils.BitUtil +import Data.Utils.StrictFold +import Data.Utils.StrictPair #if __GLASGOW_HASKELL__ import Data.Data (Data(..), Constr, mkConstr, constrIndex, Fixity(Prefix), DataType, mkDataType) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 650e003..d1d8ffe 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -272,13 +272,13 @@ import Control.DeepSeq (NFData(rnf)) import Data.Bits (shiftL, shiftR) import qualified Data.Foldable as Foldable import Data.Monoid (Monoid(..)) -import Data.StrictPair import Data.Traversable (Traversable(traverse)) import Data.Typeable import Prelude hiding (lookup, map, filter, foldr, foldl, null) import qualified Data.Set.Base as Set -import Data.StrictFold +import Data.Utils.StrictFold +import Data.Utils.StrictPair #if __GLASGOW_HASKELL__ import GHC.Exts ( build ) diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs index 4e0d820..5f286b9 100644 --- a/Data/Map/Strict.hs +++ b/Data/Map/Strict.hs @@ -269,8 +269,8 @@ import Data.Map.Base hiding , updateMaxWithKey ) import qualified Data.Set.Base as Set -import Data.StrictFold -import Data.StrictPair +import Data.Utils.StrictFold +import Data.Utils.StrictPair import Data.Bits (shiftL, shiftR) diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 3a2c938..6c39a8e 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -194,8 +194,8 @@ import qualified Data.Foldable as Foldable import Data.Typeable import Control.DeepSeq (NFData(rnf)) -import Data.StrictFold -import Data.StrictPair +import Data.Utils.StrictFold +import Data.Utils.StrictPair #if __GLASGOW_HASKELL__ import GHC.Exts ( build ) diff --git a/Data/BitUtil.hs b/Data/Utils/BitUtil.hs similarity index 97% rename from Data/BitUtil.hs rename to Data/Utils/BitUtil.hs index 848bac1..bea078e 100644 --- a/Data/BitUtil.hs +++ b/Data/Utils/BitUtil.hs @@ -7,7 +7,7 @@ #endif ----------------------------------------------------------------------------- -- | --- Module : Data.BitUtil +-- Module : Data.Utils.BitUtil -- Copyright : (c) Clark Gaebel 2012 -- (c) Johan Tibel 2012 -- License : BSD-style @@ -16,7 +16,7 @@ -- Portability : portable ----------------------------------------------------------------------------- -module Data.BitUtil +module Data.Utils.BitUtil ( highestBitMask , shiftLL , shiftRL diff --git a/Data/StrictFold.hs b/Data/Utils/StrictFold.hs similarity index 90% rename from Data/StrictFold.hs rename to Data/Utils/StrictFold.hs index 9c90a66..953c9f1 100644 --- a/Data/StrictFold.hs +++ b/Data/Utils/StrictFold.hs @@ -2,7 +2,7 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif -module Data.StrictFold (foldlStrict) where +module Data.Utils.StrictFold (foldlStrict) where -- | Same as regular 'Data.List.foldl'', but marked INLINE so that it is always -- inlined. This allows further optimization of the call to f, which can be diff --git a/Data/StrictPair.hs b/Data/Utils/StrictPair.hs similarity index 77% rename from Data/StrictPair.hs rename to Data/Utils/StrictPair.hs index 48609b3..6ae7ded 100644 --- a/Data/StrictPair.hs +++ b/Data/Utils/StrictPair.hs @@ -2,7 +2,7 @@ #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif -module Data.StrictPair (StrictPair(..), toPair) where +module Data.Utils.StrictPair (StrictPair(..), toPair) where -- | Same as regular Haskell pairs, but (x :*: _|_) = (_|_ :*: y) = -- _|_ diff --git a/containers.cabal b/containers.cabal index a952a77..dcf36fd 100644 --- a/containers.cabal +++ b/containers.cabal @@ -52,13 +52,13 @@ Library Data.Sequence Data.Tree other-modules: - Data.BitUtil Data.IntMap.Base Data.IntSet.Base Data.Map.Base Data.Set.Base - Data.StrictFold - Data.StrictPair + Data.Utils.BitUtil + Data.Utils.StrictFold + Data.Utils.StrictPair include-dirs: include From git at git.haskell.org Fri Jan 23 22:40:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:31 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add zip benchmarks (cdf173f) Message-ID: <20150123224031.9FF9F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/cdf173f4cb1f792a4ac54b939bf197c214abcd43 >--------------------------------------------------------------- commit cdf173f4cb1f792a4ac54b939bf197c214abcd43 Author: David Feuer Date: Wed Dec 3 12:31:45 2014 -0500 Add zip benchmarks >--------------------------------------------------------------- cdf173f4cb1f792a4ac54b939bf197c214abcd43 benchmarks/Sequence.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index 8c18582..ccaca6c 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -20,10 +20,16 @@ main = do r1000 = rlist 1000 rnf [r10, r100, r1000] `seq` return () defaultMain - [ bench "splitAt/append 10" $ nf (shuffle r10) s10 - , bench "splitAt/append 100" $ nf (shuffle r100) s100 - , bench "splitAt/append 1000" $ nf (shuffle r1000) s1000 - ] + [ bgroup "splitAt/append" + [ bench "10" $ nf (shuffle r10) s10 + , bench "100" $ nf (shuffle r100) s100 + , bench "1000" $ nf (shuffle r1000) s1000 + ] + , bgroup "zip" + [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (S.replicate 10000 (), S.fromList [1..10000::Int]) + , bench "nf150" $ nf (uncurry S.zip) (S.fromList [1..150::Int], S.replicate 150 ()) + , bench "nf10000" $ nf (uncurry S.zip) (S.fromList [1..10000::Int], S.replicate 10000 ()) + ] ] -- splitAt+append: repeatedly cut the sequence at a random point -- and rejoin the pieces in the opposite order. From git at git.haskell.org Fri Jan 23 22:40:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:33 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Nix the Splittable class; add fromFunction (4abaee4) Message-ID: <20150123224033.A9D383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/4abaee4c2edadc13413a78848c6eea0558ec06c8 >--------------------------------------------------------------- commit 4abaee4c2edadc13413a78848c6eea0558ec06c8 Author: David Feuer Date: Sat Dec 6 00:23:44 2014 -0500 Nix the Splittable class; add fromFunction Also export splitTraverse, and write mapWithIndex using a hand-unboxed mapWithIndex#. >--------------------------------------------------------------- 4abaee4c2edadc13413a78848c6eea0558ec06c8 Data/Sequence.hs | 220 +++++++++++++++++++++++++++++++++++-------------------- 1 file changed, 142 insertions(+), 78 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4abaee4c2edadc13413a78848c6eea0558ec06c8 From git at git.haskell.org Fri Jan 23 22:40:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:33 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Fix subtle bug in binary search (46b3b9d) Message-ID: <20150123224033.446383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/46b3b9d4b34e761aa6f75335c717742bc89d922d >--------------------------------------------------------------- commit 46b3b9d4b34e761aa6f75335c717742bc89d922d Author: Josh Acay Date: Tue Oct 14 14:42:17 2014 -0400 Fix subtle bug in binary search >--------------------------------------------------------------- 46b3b9d4b34e761aa6f75335c717742bc89d922d Data/Graph.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Graph.hs b/Data/Graph.hs index c5cdf4b..65f3fb1 100644 --- a/Data/Graph.hs +++ b/Data/Graph.hs @@ -244,7 +244,7 @@ graphFromEdges edges0 EQ -> Just mid GT -> findVertex (mid+1) b where - mid = (a + b) `div` 2 + mid = a + (b - a) `div` 2 ------------------------------------------------------------------------- -- - From git at git.haskell.org Fri Jan 23 22:40:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:35 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #58 from cacay/master (828b60d) Message-ID: <20150123224035.4C4443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/828b60d394418132eb86993bbde29538b066aed8 >--------------------------------------------------------------- commit 828b60d394418132eb86993bbde29538b066aed8 Merge: 9cfe43a 46b3b9d Author: Milan Straka Date: Tue Oct 14 21:52:28 2014 +0200 Merge pull request #58 from cacay/master Fix bug in binary search >--------------------------------------------------------------- 828b60d394418132eb86993bbde29538b066aed8 Data/Graph.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:40:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:35 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add comments explaining the splitting traversal (c0e8c7d) Message-ID: <20150123224035.B23103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c0e8c7d9e135527a188c5a932cab1e96c11c1de5 >--------------------------------------------------------------- commit c0e8c7d9e135527a188c5a932cab1e96c11c1de5 Author: David Feuer Date: Thu Dec 4 11:50:20 2014 -0500 Add comments explaining the splitting traversal Why it's a good idea, how it works, and what the benchmarks say. >--------------------------------------------------------------- c0e8c7d9e135527a188c5a932cab1e96c11c1de5 Data/Sequence.hs | 58 +++++++++++++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 57 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 9955584..212c926 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -128,6 +128,7 @@ module Data.Sequence ( foldlWithIndex, -- :: (b -> Int -> a -> b) -> b -> Seq a -> b foldrWithIndex, -- :: (Int -> a -> b -> b) -> b -> Seq a -> b -- * Transformations + genSplitTraverseSeq, mapWithIndex, -- :: (Int -> a -> b) -> Seq a -> Seq b reverse, -- :: Seq a -> Seq a -- ** Zips @@ -1709,7 +1710,7 @@ reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) -- For zipping, and probably also for (<*>), it is useful to build a result by -- traversing a sequence while splitting up something else. For zipping, we -- traverse the first sequence while splitting up the second [and third [and --- fourth]]. For fs <*> xs, we expect soon to traverse +-- fourth]]. For fs <*> xs, we hope to traverse -- -- > replicate (length fs * length xs) () -- @@ -1717,6 +1718,51 @@ reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) -- -- > fmap (\f -> fmap f xs) fs -- +-- What makes all this crazy code a good idea: +-- +-- Suppose we zip together two sequences of the same length: +-- +-- zs = zip xs ys +-- +-- We want to get reasonably fast indexing into zs immediately, rather than +-- needing to construct the entire thing first, as the previous implementation +-- required. The first aspect is that we build the result "outside-in" or +-- "top-down", rather than left to right. That gives us access to both ends +-- quickly. But that's not enough, by itself, to give immediate access to the +-- center of zs. For that, we need to be able to skip over larger segments of +-- zs, delaying their construction until we actually need them. The way we do +-- this is to traverse xs, while splitting up ys according to the structure of +-- xs. If we have a Deep _ pr m sf, we split ys into three pieces, and hand off +-- one piece to the prefix, one to the middle, and one to the suffix of the +-- result. The key point is that we don't need to actually do anything further +-- with those pieces until we actually need them; the computations to split +-- them up further and zip them with their matching pieces can be delayed until +-- they're actually needed. We do the same thing for Digits (splitting into +-- between one and four pieces) and Nodes (splitting into two or three). The +-- ultimate result is that we can index, or split at, any location in zs in +-- O(log(min{i,n-i})) time *immediately*, with only a constant-factor slowdown +-- as thunks are forced along the path. +-- +-- Benchmark info, and alternatives: +-- +-- The old zipping code used mapAccumL to traverse the first sequence while +-- cutting down the second sequence one piece at a time. +-- +-- An alternative way to express that basic idea is to convert both sequences +-- to lists, zip the lists, and then convert the result back to a sequence. +-- I'll call this the "listy" implementation. +-- +-- I benchmarked two operations: Each started by zipping two sequences +-- constructed with replicate and/or fromList. The first would then immediately +-- index into the result. The second would apply deepseq to force the entire +-- result. The new implementation worked much better than either of the others +-- on the immediate indexing test, as expected. It also worked better than the +-- old implementation for all the deepseq tests. For short sequences, the listy +-- implementation outperformed all the others on the deepseq test. However, the +-- splitting implementation caught up and surpassed it once the sequences grew +-- long enough. It seems likely that by avoiding rebuilding, it interacts +-- better with the cache hierarchy. +-- -- David Feuer, with excellent guidance from Carter Schonwald, December 2014 class Splittable s where @@ -1731,6 +1777,16 @@ instance (Splittable a, Splittable b) => Splittable (a, b) where (al, ar) = splitState i a (bl, br) = splitState i b +data GenSplittable s = GenSplittable s (Int -> s -> (s,s)) +instance Splittable (GenSplittable s) where + splitState i (GenSplittable s spl) = (GenSplittable l spl, GenSplittable r spl) + where + (l,r) = spl i s + +{-# INLINE genSplitTraverseSeq #-} +genSplitTraverseSeq :: (Int -> s -> (s, s)) -> (s -> a -> b) -> s -> Seq a -> Seq b +genSplitTraverseSeq spl f s = splitTraverseSeq (\(GenSplittable s _) -> f s) (GenSplittable s spl) + {-# SPECIALIZE splitTraverseSeq :: (Seq x -> a -> b) -> Seq x -> Seq a -> Seq b #-} {-# SPECIALIZE splitTraverseSeq :: ((Seq x, Seq y) -> a -> b) -> (Seq x, Seq y) -> Seq a -> Seq b #-} splitTraverseSeq :: (Splittable s) => (s -> a -> b) -> s -> Seq a -> Seq b From git at git.haskell.org Fri Jan 23 22:40:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:37 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Minor documentation fix. (864ebff) Message-ID: <20150123224037.541323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/864ebff7995e7d4358475f8808f10329a832b78b >--------------------------------------------------------------- commit 864ebff7995e7d4358475f8808f10329a832b78b Author: strout Date: Tue Oct 14 22:53:42 2014 -0500 Minor documentation fix. Completed a sentence in maxView documentation. >--------------------------------------------------------------- 864ebff7995e7d4358475f8808f10329a832b78b Data/Map/Base.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index d1d8ffe..eafab03 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -1171,6 +1171,7 @@ minView x = Just (first snd $ deleteFindMin x) -- | /O(log n)/. Retrieves the value associated with maximal key of the -- map, and the map stripped of that element, or 'Nothing' if passed an +-- empty map. -- -- > maxView (fromList [(5,"a"), (3,"b")]) == Just ("a", singleton 3 "b") -- > maxView empty == Nothing From git at git.haskell.org Fri Jan 23 22:40:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:37 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Make <*> fast (73c06d4) Message-ID: <20150123224037.BA73C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/73c06d4421aaca2dc3c06d07d452d3e8f586ecf4 >--------------------------------------------------------------- commit 73c06d4421aaca2dc3c06d07d452d3e8f586ecf4 Author: David Feuer Date: Sat Dec 6 18:46:49 2014 -0500 Make <*> fast Use the `splitTraverse` mechanism to implement `<*>` with optimal incremental performance. Stop exporting `splitTraverse`. Many thanks to Joachim Breitner for writing the splitting code for this. >--------------------------------------------------------------- 73c06d4421aaca2dc3c06d07d452d3e8f586ecf4 Data/Sequence.hs | 61 ++++++++++++++++++++++++++++++++++++++++++++++++++++---- 1 file changed, 57 insertions(+), 4 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 9e78ce1..f7d551c 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -133,7 +133,6 @@ module Data.Sequence ( -- * Transformations mapWithIndex, -- :: (Int -> a -> b) -> Seq a -> Seq b reverse, -- :: Seq a -> Seq a - splitTraverse, -- :: (Int -> s -> (s, s)) -> (s -> a -> b) -> s -> Seq a -> Seq b -- ** Zips zip, -- :: Seq a -> Seq b -> Seq (a, b) zipWith, -- :: (a -> b -> c) -> Seq a -> Seq b -> Seq c @@ -257,10 +256,65 @@ instance Monad Seq where instance Applicative Seq where pure = singleton - fs <*> xs = foldl' add empty fs - where add ys f = ys >< fmap f xs + + Seq Empty <*> _ = empty + _ <*> Seq Empty = empty + Seq (Single (Elem f)) <*> xs = fmap f xs + fs <*> Seq (Single (Elem x)) = fmap ($x) fs + fs <*> xs = splitTraverse splitCPs + (\s _ -> uncurry ($) (getSingletonCPs s)) + (createCPs fs xs) + (replicate (length fs * length xs) ()) + xs *> ys = replicateSeq (length xs) ys +-- The splitCPs code below, for splitting ragged-ended Cartesian products, +-- was generously provided by Joachim Breitner. + +data CPs x y = + CPs (Seq x) + (Seq y) + {-# UNPACK #-} !Int {- beginning column -} + {-# UNPACK #-} !Int {- last column -} + | SingleCPs x (Seq y) +#ifdef TESTING + deriving Show +#endif + +-- Note: The total length of CPs xs ys fc lc is +-- (length xs - 1) * length ys - fc + lc + 1 + +-- Create a non-trivial Cps given two sequences +createCPs :: Seq x -> Seq y -> CPs x y +createCPs xs ys = CPs xs ys 0 (length ys - 1) + +-- Smart constructor +mkCPs :: Seq x -> Seq y -> Int -> Int -> CPs x y +mkCPs (Seq (Single (Elem x))) ys fc lc = SingleCPs x (drop fc $ take (lc+1) ys) +mkCPs xs ys fc lc = CPs xs ys fc lc + +splitCPs:: Int -> CPs x y -> (CPs x y, CPs x y) +splitCPs n (SingleCPs x ys) + = ( SingleCPs x ys1, SingleCPs x ys2 ) + where (ys1, ys2) = splitAt n ys +splitCPs n (CPs xs ys fc lc) + = ( mkCPs (take r_end xs) ys fc c_end + , mkCPs (drop r_begin xs) ys c_begin lc + ) + where + -- Coordinates of the beginning of the second chunk + (r_begin, -- number of rows that do not go into the second chunk + c_begin) = (n + fc) `quotRem` length ys + + -- Coordinates of the end of the first chunk + r_end | c_begin == 0 = r_begin -- cut nicely along rows, keep the other rows + | otherwise = r_begin + 1 -- we need to keep one row in both chunks + c_end = (c_begin - 1 + length ys) `rem` length ys + +getSingletonCPs :: CPs x y -> (x, y) +getSingletonCPs (SingleCPs x ys) = (x, getSingleton ys) +getSingletonCPs _ = error "getSingletonCPs: Not a singleton" + instance MonadPlus Seq where mzero = empty mplus = (><) @@ -1370,7 +1424,6 @@ mapWithIndex# f (Seq xs) = Seq $ mapWithIndexTree# (\s (Elem a) -> Elem (f s a)) !(I# sb) = size b !sPsa = s +# sa !sPsab = sPsa +# sb - #endif -- | /O(n)/. Convert a given sequence length and a function representing that From git at git.haskell.org Fri Jan 23 22:40:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:39 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #59 from strout/patch-1 (b9bd228) Message-ID: <20150123224039.5CC553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/b9bd228149bfb61fe9f87a6ca9858ce1df1aee9e >--------------------------------------------------------------- commit b9bd228149bfb61fe9f87a6ca9858ce1df1aee9e Merge: 828b60d 864ebff Author: Milan Straka Date: Wed Oct 15 08:48:37 2014 +0200 Merge pull request #59 from strout/patch-1 Minor documentation fix. >--------------------------------------------------------------- b9bd228149bfb61fe9f87a6ca9858ce1df1aee9e Data/Map/Base.hs | 1 + 1 file changed, 1 insertion(+) From git at git.haskell.org Fri Jan 23 22:40:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:39 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Update benchmark running script to new Criterion options. (83f32bc) Message-ID: <20150123224039.C23BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/83f32bcf58a43dfec32a4151d2f677635da7e5cd >--------------------------------------------------------------- commit 83f32bcf58a43dfec32a4151d2f677635da7e5cd Author: Milan Straka Date: Sun Dec 7 14:57:04 2014 +0100 Update benchmark running script to new Criterion options. >--------------------------------------------------------------- 83f32bcf58a43dfec32a4151d2f677635da7e5cd benchmarks/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/benchmarks/Makefile b/benchmarks/Makefile index 1539a2a..ff45493 100644 --- a/benchmarks/Makefile +++ b/benchmarks/Makefile @@ -4,7 +4,7 @@ bench-%: %.hs force ghc -O2 -DTESTING $< -i../$(TOP) -o $@ -outputdir tmp -rtsopts bench-%.csv: bench-% - ./bench-$* $(BENCHMARK) -v -u bench-$*.csv + ./bench-$* $(BENCHMARK) -v 2 --csv bench-$*.csv .PHONY: force clean veryclean force: From git at git.haskell.org Fri Jan 23 22:40:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:41 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Define some new Foldable methods for containers (61b9066) Message-ID: <20150123224041.68FE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/61b9066d79ac346743dfe56425307e27e2e5d060 >--------------------------------------------------------------- commit 61b9066d79ac346743dfe56425307e27e2e5d060 Author: Herbert Valerio Riedel Date: Tue Oct 14 20:25:29 2014 +0200 Define some new Foldable methods for containers This is a first attempt at addressing #56 >--------------------------------------------------------------- 61b9066d79ac346743dfe56425307e27e2e5d060 Data/IntMap/Base.hs | 15 +++++++++++++++ Data/Map/Base.hs | 15 +++++++++++++++ Data/Sequence.hs | 7 +++++++ Data/Set/Base.hs | 20 ++++++++++++++++++++ Data/Tree.hs | 7 +++++++ 5 files changed, 64 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index fec5abe..0de3e5b 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -320,6 +320,21 @@ instance Foldable.Foldable IntMap where go (Bin _ _ l r) = go l `mappend` go r {-# INLINE foldMap #-} +#if MIN_VERSION_base(4,6,0) + foldl' = foldl' + {-# INLINE foldl' #-} + foldr' = foldr' + {-# INLINE foldr' #-} +#endif +#if MIN_VERSION_base(4,8,0) + length = size + {-# INLINE length #-} + null = null + {-# INLINE null #-} + toList = elems -- NB: Foldable.toList /= IntMap.toList + {-# INLINE toList #-} +#endif + instance Traversable IntMap where traverse f = traverseWithKey (\_ -> f) {-# INLINE traverse #-} diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index d1d8ffe..d01367b 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -2653,6 +2653,21 @@ instance Foldable.Foldable (Map k) where go (Bin _ _ v l r) = go l `mappend` (f v `mappend` go r) {-# INLINE foldMap #-} +#if MIN_VERSION_base(4,6,0) + foldl' = foldl' + {-# INLINE foldl' #-} + foldr' = foldr' + {-# INLINE foldr' #-} +#endif +#if MIN_VERSION_base(4,8,0) + length = size + {-# INLINE length #-} + null = null + {-# INLINE null #-} + toList = elems -- NB: Foldable.toList /= Map.toList + {-# INLINE toList #-} +#endif + instance (NFData k, NFData a) => NFData (Map k a) where rnf Tip = () rnf (Bin _ kx x l r) = rnf kx `seq` rnf x `seq` rnf l `seq` rnf r diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 6bbebdb..f1385f5 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -189,6 +189,13 @@ instance Foldable Seq where foldl1 f (Seq xs) = getElem (foldl1 f' xs) where f' (Elem x) (Elem y) = Elem (f x y) +#if MIN_VERSION_base(4,8,0) + length = length + {-# INLINE length #-} + null = null + {-# INLINE null #-} +#endif + instance Traversable Seq where traverse f (Seq xs) = Seq <$> traverse (traverse f) xs diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 6c39a8e..9260aeb 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -262,6 +262,26 @@ instance Foldable.Foldable Set where go (Bin _ k l r) = go l `mappend` (f k `mappend` go r) {-# INLINE foldMap #-} +#if MIN_VERSION_base(4,6,0) + foldl' = foldl' + {-# INLINE foldl' #-} + foldr' = foldr' + {-# INLINE foldr' #-} +#endif +#if MIN_VERSION_base(4,8,0) + length = size + {-# INLINE length #-} + null = null + {-# INLINE null #-} + toList = toList + {-# INLINE toList #-} + minimum = findMin + {-# INLINE minimum #-} + maximum = findMax + {-# INLINE maximum #-} +#endif + + #if __GLASGOW_HASKELL__ {-------------------------------------------------------------------- diff --git a/Data/Tree.hs b/Data/Tree.hs index dab25c2..2f18c68 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -79,6 +79,13 @@ instance Traversable Tree where instance Foldable Tree where foldMap f (Node x ts) = f x `mappend` foldMap (foldMap f) ts +#if MIN_VERSION_base(4,8,0) + null _ = False + {-# INLINE null #-} + toList = flatten + {-# INLINE toList #-} +#endif + instance NFData a => NFData (Tree a) where rnf (Node x ts) = rnf x `seq` rnf ts From git at git.haskell.org Fri Jan 23 22:40:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:41 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Add simple fromFunction benchmark. (fc87eee) Message-ID: <20150123224041.C88A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/fc87eeefa5907559b2669a16baed03db79f82981 >--------------------------------------------------------------- commit fc87eeefa5907559b2669a16baed03db79f82981 Author: Milan Straka Date: Sun Dec 7 14:57:24 2014 +0100 Add simple fromFunction benchmark. >--------------------------------------------------------------- fc87eeefa5907559b2669a16baed03db79f82981 benchmarks/Sequence.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index ccaca6c..58e1114 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -29,7 +29,13 @@ main = do [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (S.replicate 10000 (), S.fromList [1..10000::Int]) , bench "nf150" $ nf (uncurry S.zip) (S.fromList [1..150::Int], S.replicate 150 ()) , bench "nf10000" $ nf (uncurry S.zip) (S.fromList [1..10000::Int], S.replicate 10000 ()) - ] ] + ] + , bgroup "fromFunction" + [ bench "ix10000/5000" $ nf (\size -> S.fromFunction size id `S.index` (size `div` 2)) 10000 + , bench "nf100" $ nf (\size -> S.fromFunction size id) 100 + , bench "nf10000" $ nf (\size -> S.fromFunction size id) 10000 + ] + ] -- splitAt+append: repeatedly cut the sequence at a random point -- and rejoin the pieces in the opposite order. From git at git.haskell.org Fri Jan 23 22:40:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:43 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Replace `MIN_VERSION_base_4_[57]_0` by `MIN_VERSION_base()` (3582252) Message-ID: <20150123224043.71B353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/3582252bda944421c0a38c86684657e59dbe81be >--------------------------------------------------------------- commit 3582252bda944421c0a38c86684657e59dbe81be Author: Herbert Valerio Riedel Date: Thu Oct 16 22:35:13 2014 +0200 Replace `MIN_VERSION_base_4_[57]_0` by `MIN_VERSION_base()` >--------------------------------------------------------------- 3582252bda944421c0a38c86684657e59dbe81be Data/IntSet/Base.hs | 24 ++---------------------- 1 file changed, 2 insertions(+), 22 deletions(-) diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 309ab42..c8e70f6 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -162,26 +162,6 @@ module Data.IntSet.Base ( , bitmapOf ) where --- We want to be able to compile without cabal. Nevertheless --- #if defined(MIN_VERSION_base) && MIN_VERSION_base(4,5,0) --- does not work, because if MIN_VERSION_base is undefined, --- the last condition is syntactically wrong. -#define MIN_VERSION_base_4_5_0 0 -#ifdef MIN_VERSION_base -#if MIN_VERSION_base(4,5,0) -#undef MIN_VERSION_base_4_5_0 -#define MIN_VERSION_base_4_5_0 1 -#endif -#endif - -#define MIN_VERSION_base_4_7_0 0 -#ifdef MIN_VERSION_base -#if MIN_VERSION_base(4,7,0) -#undef MIN_VERSION_base_4_7_0 -#define MIN_VERSION_base_4_7_0 1 -#endif -#endif - import Control.DeepSeq (NFData) import Data.Bits import qualified Data.List as List @@ -1228,7 +1208,7 @@ tip kx bm = Tip kx bm ----------------------------------------------------------------------} suffixBitMask :: Int -#if MIN_VERSION_base_4_7_0 +#if MIN_VERSION_base(4,7,0) suffixBitMask = finiteBitSize (undefined::Word) - 1 #else suffixBitMask = bitSize (undefined::Word) - 1 @@ -1479,7 +1459,7 @@ foldr'Bits prefix f z bm = let lb = lowestBitSet bm ----------------------------------------------------------------------} bitcount :: Int -> Word -> Int -#if MIN_VERSION_base_4_5_0 +#if MIN_VERSION_base(4,5,0) bitcount a x = a + popCount x #else bitcount a0 x0 = go a0 x0 From git at git.haskell.org Fri Jan 23 22:40:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:43 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Add simple mapWithIndex benchmark. (0f3ac0b) Message-ID: <20150123224043.D1CDF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/0f3ac0b3e48f49e5565b692f2abcb2219895d145 >--------------------------------------------------------------- commit 0f3ac0b3e48f49e5565b692f2abcb2219895d145 Author: Milan Straka Date: Sun Dec 7 15:43:09 2014 +0100 Add simple mapWithIndex benchmark. >--------------------------------------------------------------- 0f3ac0b3e48f49e5565b692f2abcb2219895d145 benchmarks/Sequence.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index 58e1114..5ae2cd3 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -12,7 +12,8 @@ main = do let s10 = S.fromList [1..10] :: S.Seq Int s100 = S.fromList [1..100] :: S.Seq Int s1000 = S.fromList [1..1000] :: S.Seq Int - rnf [s10, s100, s1000] `seq` return () + s10000 = S.fromList [1..10000] :: S.Seq Int + rnf [s10, s100, s1000, s10000] `seq` return () let g = mkStdGen 1 let rlist n = map (`mod` (n+1)) (take 10000 (randoms g)) :: [Int] r10 = rlist 10 @@ -35,6 +36,11 @@ main = do , bench "nf100" $ nf (\size -> S.fromFunction size id) 100 , bench "nf10000" $ nf (\size -> S.fromFunction size id) 10000 ] + , bgroup "mapWithIndex" + [ bench "ix10000/5000" $ nf (S.mapWithIndex (+)) s10000 + , bench "nf100" $ nf (S.mapWithIndex (+)) s100 + , bench "nf10000" $ nf (S.mapWithIndex (+)) s10000 + ] ] -- splitAt+append: repeatedly cut the sequence at a random point From git at git.haskell.org Fri Jan 23 22:40:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:45 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #57 from hvr/pr-foldable (daf640e) Message-ID: <20150123224045.7E5033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/daf640ec6c0c189a6c570a1dff4e958e2fa8d697 >--------------------------------------------------------------- commit daf640ec6c0c189a6c570a1dff4e958e2fa8d697 Merge: b9bd228 3582252 Author: Milan Straka Date: Sun Oct 19 10:24:41 2014 +0200 Merge pull request #57 from hvr/pr-foldable Define some new Foldable methods for containers >--------------------------------------------------------------- daf640ec6c0c189a6c570a1dff4e958e2fa8d697 Data/IntMap/Base.hs | 15 +++++++++++++++ Data/IntSet/Base.hs | 24 ++---------------------- Data/Map/Base.hs | 15 +++++++++++++++ Data/Sequence.hs | 7 +++++++ Data/Set/Base.hs | 20 ++++++++++++++++++++ Data/Tree.hs | 7 +++++++ 6 files changed, 66 insertions(+), 22 deletions(-) From git at git.haskell.org Fri Jan 23 22:40:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:45 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Direct implementation of fromFunction. (ce7f531) Message-ID: <20150123224045.D94B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/ce7f531605b5f2bb350f36c51a74d9ebd84ff8b6 >--------------------------------------------------------------- commit ce7f531605b5f2bb350f36c51a74d9ebd84ff8b6 Author: Milan Straka Date: Sun Dec 7 16:16:59 2014 +0100 Direct implementation of fromFunction. We avoid using Four Digit, so that elements can be added to the new Seq without forcing a large rebuild. >--------------------------------------------------------------- ce7f531605b5f2bb350f36c51a74d9ebd84ff8b6 Data/Sequence.hs | 23 ++++++++++++++++++++++- 1 file changed, 22 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index f7d551c..4f7eb86 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1429,7 +1429,28 @@ mapWithIndex# f (Seq xs) = Seq $ mapWithIndexTree# (\s (Elem a) -> Elem (f s a)) -- | /O(n)/. Convert a given sequence length and a function representing that -- sequence into a sequence. fromFunction :: Int -> (Int -> a) -> Seq a -fromFunction len f = mapWithIndex (\i _ -> f i) (replicate len ()) +fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with negative len" + | len == 0 = empty + | otherwise = Seq $ create (Elem . f) 1 0 len + where + create :: (Int -> a) -> Int -> Int -> Int -> FingerTree a + create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = case trees of + 1 -> Single $ b i + 2 -> Deep (2*s) (One (b i)) Empty (One (b (i+s))) + 3 -> Deep (3*s) (Two (b i) (b (i+s))) Empty (One (b (i+2*s))) + 4 -> Deep (4*s) (Two (b i) (b (i+s))) Empty (Two (b (i+2*s)) (b (i+3*s))) + 5 -> Deep (5*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Two (b (i+3*s)) (b (i+4*s))) + 6 -> Deep (5*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Three (b (i+3*s)) (b (i+4*s)) (b (i+5*s))) + _ -> case trees `quotRem` 3 of + (trees',1) -> Deep (trees*s) (Two (b i) (b (i+s))) + (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+2*s) (trees'-1)) + (Two (b (i+(2+3*(trees'-1))*s)) (b (i+(3+3*(trees'-1))*s))) + (trees',2) -> Deep (trees*s) (Three (b i) (b (i+s)) (b (i+2*s))) + (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+3*s) (trees'-1)) + (Two (b (i+(3+3*(trees'-1))*s)) (b (i+(4+3*(trees'-1))*s))) + (trees',0) -> Deep (trees*s) (Three (b i) (b (i+s)) (b (i+2*s))) + (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+3*s) (trees'-2)) + (Three (b (i+(3+3*(trees'-2))*s)) (b (i+(4+3*(trees'-2))*s)) (b (i+(5+3*(trees'-2))*s))) -- Splitting From git at git.haskell.org Fri Jan 23 22:40:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:47 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Provide default MIN_VERSION_base if not available. (0762786) Message-ID: <20150123224047.8AA643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/076278627b6b3fda9522a9ca971f2467947527d6 >--------------------------------------------------------------- commit 076278627b6b3fda9522a9ca971f2467947527d6 Author: Milan Straka Date: Sun Oct 19 10:43:09 2014 +0200 Provide default MIN_VERSION_base if not available. After #56, we use MIN_VERSION_base in many places. We now provide trivial MIN_VERSION_base if not available to allow compiling without cabal. >--------------------------------------------------------------- 076278627b6b3fda9522a9ca971f2467947527d6 Data/IntMap/Base.hs | 8 ++++++++ Data/IntSet/Base.hs | 8 ++++++++ Data/Map/Base.hs | 8 ++++++++ Data/Sequence.hs | 8 ++++++++ Data/Set/Base.hs | 8 ++++++++ Data/Tree.hs | 8 ++++++++ 6 files changed, 48 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 0de3e5b..8f2e32f 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -247,6 +247,14 @@ import Text.Read -- want the compilers to be compiled by as many compilers as possible. #define STRICT_1_OF_2(fn) fn arg _ | arg `seq` False = undefined +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + -- A "Nat" is a natural machine word (an unsigned Int) type Nat = Word diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index c8e70f6..b6f8014 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -202,6 +202,14 @@ import GHC.Prim (indexInt8OffAddr#) #define STRICT_1_OF_3(fn) fn arg _ _ | arg `seq` False = undefined #define STRICT_2_OF_3(fn) fn _ arg _ | arg `seq` False = undefined +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + infixl 9 \\{-This comment teaches CPP correct behaviour -} -- A "Nat" is a natural machine word (an unsigned Int) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 72934e9..edcfdb7 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -299,6 +299,14 @@ import Data.Data #define STRICT_1_OF_4(fn) fn arg _ _ _ | arg `seq` False = undefined #define STRICT_2_OF_4(fn) fn _ arg _ _ | arg `seq` False = undefined +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + {-------------------------------------------------------------------- Operators --------------------------------------------------------------------} diff --git a/Data/Sequence.hs b/Data/Sequence.hs index f1385f5..a2b4844 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -160,6 +160,14 @@ import Text.Read (Lexeme(Ident), lexP, parens, prec, import Data.Data #endif +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + infixr 5 `consTree` infixl 5 `snocTree` diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 9260aeb..e676a6f 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -214,6 +214,14 @@ import Data.Data #define STRICT_1_OF_3(fn) fn arg _ _ | arg `seq` False = undefined #define STRICT_2_OF_3(fn) fn _ arg _ | arg `seq` False = undefined +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + {-------------------------------------------------------------------- Operators --------------------------------------------------------------------} diff --git a/Data/Tree.hs b/Data/Tree.hs index 2f18c68..c880213 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -45,6 +45,14 @@ import Control.DeepSeq (NFData(rnf)) import Data.Data (Data) #endif +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + + -- | Multi-way trees, also known as /rose trees/. data Tree a = Node { rootLabel :: a, -- ^ label value From git at git.haskell.org Fri Jan 23 22:40:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:47 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6,develop-0.6-questionable,master: Nix the Splittable class; add fromFunction (41cc152) Message-ID: <20150123224047.E4A2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/41cc1523f99cecfd93efed16abab28eebd873abb >--------------------------------------------------------------- commit 41cc1523f99cecfd93efed16abab28eebd873abb Author: David Feuer Date: Sat Dec 6 00:23:44 2014 -0500 Nix the Splittable class; add fromFunction Write mapWithIndex using a hand-unboxed mapWithIndex#. Make `split` strict, and add an internal strict `splitAt'`. This helps `zipWith` a little. >--------------------------------------------------------------- 41cc1523f99cecfd93efed16abab28eebd873abb Data/Sequence.hs | 249 +++++++++++++++++++++++++++++++++++++------------------ 1 file changed, 167 insertions(+), 82 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 41cc1523f99cecfd93efed16abab28eebd873abb From git at git.haskell.org Fri Jan 23 22:40:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:49 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Remove RoleAnnotations extension from containers.cabal. (1d555a4) Message-ID: <20150123224049.9224B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/1d555a4d7d2b902808d73c2fad4314672241e81d >--------------------------------------------------------------- commit 1d555a4d7d2b902808d73c2fad4314672241e81d Author: Milan Straka Date: Sun Oct 19 10:46:13 2014 +0200 Remove RoleAnnotations extension from containers.cabal. We switch the language extensions in specific files. We only provide extensions for GHC pre 7.0, as it cannot enable extensions conditionally using CPP. >--------------------------------------------------------------- 1d555a4d7d2b902808d73c2fad4314672241e81d containers.cabal | 2 -- 1 file changed, 2 deletions(-) diff --git a/containers.cabal b/containers.cabal index dcf36fd..815882e 100644 --- a/containers.cabal +++ b/containers.cabal @@ -64,8 +64,6 @@ Library if impl(ghc<7.0) extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types - if impl(ghc >= 7.8) - extensions: RoleAnnotations ------------------- -- T E S T I N G -- From git at git.haskell.org Fri Jan 23 22:40:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:49 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Simplify zipWith3 and zipWith4 to reduce code size (58f3597) Message-ID: <20150123224049.EDAAD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/58f359787438f18dc7fbfe25f115654bd28ac94b >--------------------------------------------------------------- commit 58f359787438f18dc7fbfe25f115654bd28ac94b Author: David Feuer Date: Wed Dec 10 18:33:27 2014 -0500 Simplify zipWith3 and zipWith4 to reduce code size The performance impact isn't worth the code blowup. Also, fix a bug in `fromFunction`. >--------------------------------------------------------------- 58f359787438f18dc7fbfe25f115654bd28ac94b Data/Sequence.hs | 17 +++++++++++------ 1 file changed, 11 insertions(+), 6 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 29a19b3..62d76b3 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1382,7 +1382,7 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg 3 -> Deep (3*s) (Two (b i) (b (i+s))) Empty (One (b (i+2*s))) 4 -> Deep (4*s) (Two (b i) (b (i+s))) Empty (Two (b (i+2*s)) (b (i+3*s))) 5 -> Deep (5*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Two (b (i+3*s)) (b (i+4*s))) - 6 -> Deep (5*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Three (b (i+3*s)) (b (i+4*s)) (b (i+5*s))) + 6 -> Deep (6*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Three (b (i+3*s)) (b (i+4*s)) (b (i+5*s))) _ -> case trees `quotRem` 3 of (trees',1) -> Deep (trees*s) (Two (b i) (b (i+s))) (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+2*s) (trees'-1)) @@ -1937,12 +1937,16 @@ zip = zipWith (,) -- For example, @zipWith (+)@ is applied to two sequences to take the -- sequence of corresponding sums. zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c -zipWith f s1 s2 = splitMap splitAt' (\s a -> f a (getSingleton s)) s2' s1' +zipWith f s1 s2 = zipWith' f s1' s2' where minLen = min (length s1) (length s2) s1' = take minLen s1 s2' = take minLen s2 +-- | A version of zipWith that assumes the sequences have the same length. +zipWith' :: (a -> b -> c) -> Seq a -> Seq b -> Seq c +zipWith' f s1 s2 = splitMap splitAt' (\s a -> f a (getSingleton s)) s2 s1 + -- | /O(min(n1,n2,n3))/. 'zip3' takes three sequences and returns a -- sequence of triples, analogous to 'zip'. zip3 :: Seq a -> Seq b -> Seq c -> Seq (a,b,c) @@ -1952,14 +1956,16 @@ zip3 = zipWith3 (,,) -- three elements, as well as three sequences and returns a sequence of -- their point-wise combinations, analogous to 'zipWith'. zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d -zipWith3 f s1 s2 s3 = splitMap (\i (s,t) -> case (splitAt' i s, splitAt' i t) of ((s', s''), (t', t'')) -> ((s',t'),(s'',t''))) - (\(b,c) a -> f a (getSingleton b) (getSingleton c)) (s2',s3') s1' +zipWith3 f s1 s2 s3 = zipWith' ($) (zipWith' f s1' s2') s3' where minLen = minimum [length s1, length s2, length s3] s1' = take minLen s1 s2' = take minLen s2 s3' = take minLen s3 +zipWith3' :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d +zipWith3' f s1 s2 s3 = zipWith' ($) (zipWith' f s1 s2) s3 + -- | /O(min(n1,n2,n3,n4))/. 'zip4' takes four sequences and returns a -- sequence of quadruples, analogous to 'zip'. zip4 :: Seq a -> Seq b -> Seq c -> Seq d -> Seq (a,b,c,d) @@ -1969,8 +1975,7 @@ zip4 = zipWith4 (,,,) -- four elements, as well as four sequences and returns a sequence of -- their point-wise combinations, analogous to 'zipWith'. zipWith4 :: (a -> b -> c -> d -> e) -> Seq a -> Seq b -> Seq c -> Seq d -> Seq e -zipWith4 f s1 s2 s3 s4 = splitMap (\i (s,t,u) -> case (splitAt' i s, splitAt' i t, splitAt' i u) of ((s',s''),(t',t''),(u',u'')) -> ((s',t',u'),(s'',t'',u''))) - (\(b, c, d) a -> f a (getSingleton b) (getSingleton c) (getSingleton d)) (s2',s3',s4') s1' +zipWith4 f s1 s2 s3 s4 = zipWith' ($) (zipWith3' f s1' s2' s3') s4' where minLen = minimum [length s1, length s2, length s3, length s4] s1' = take minLen s1 From git at git.haskell.org Fri Jan 23 22:40:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:51 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Make Foldable.fold be INLINABLE without an argument. (398e466) Message-ID: <20150123224051.9B2F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/398e46672e498f83f28733f3a7a188651e9576b8 >--------------------------------------------------------------- commit 398e46672e498f83f28733f3a7a188651e9576b8 Author: Milan Straka Date: Sun Oct 19 14:07:13 2014 +0200 Make Foldable.fold be INLINABLE without an argument. >--------------------------------------------------------------- 398e46672e498f83f28733f3a7a188651e9576b8 Data/IntMap/Base.hs | 2 +- Data/Map/Base.hs | 2 +- Data/Set/Base.hs | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 8f2e32f..c1b2f4d 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -313,7 +313,7 @@ instance Monoid (IntMap a) where mconcat = unions instance Foldable.Foldable IntMap where - fold t = go t + fold = go where go Nil = mempty go (Tip _ v) = v go (Bin _ _ l r) = go l `mappend` go r diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index edcfdb7..781ac3a 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -2647,7 +2647,7 @@ instance Traversable (Map k) where {-# INLINE traverse #-} instance Foldable.Foldable (Map k) where - fold t = go t + fold = go where go Tip = mempty go (Bin 1 _ v _ _) = v go (Bin _ _ v l r) = go l `mappend` (v `mappend` go r) diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index e676a6f..67ade4e 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -255,7 +255,7 @@ instance Ord a => Monoid (Set a) where mconcat = unions instance Foldable.Foldable Set where - fold t = go t + fold = go where go Tip = mempty go (Bin 1 k _ _) = k go (Bin _ k l r) = go l `mappend` (k `mappend` go r) From git at git.haskell.org Fri Jan 23 22:40:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:52 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Revert the fromFunction shallowing (d8c9008) Message-ID: <20150123224052.0162B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/d8c90085755397b0180a349385fdd1b1820ae1aa >--------------------------------------------------------------- commit d8c90085755397b0180a349385fdd1b1820ae1aa Author: David Feuer Date: Thu Dec 11 21:21:38 2014 -0500 Revert the fromFunction shallowing I don't actually know whether we want it shallower or "safer". Make `fromFunction` easier to read. >--------------------------------------------------------------- d8c90085755397b0180a349385fdd1b1820ae1aa Data/Sequence.hs | 42 +++++++++++++++++++++++------------------- 1 file changed, 23 insertions(+), 19 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 62d76b3..f3fbbe7 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1374,25 +1374,29 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg #else | otherwise = Seq $ create (Elem . f) 1 0 len #endif - where - create :: (Int -> a) -> Int -> Int -> Int -> FingerTree a - create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = i `seq` s `seq` case trees of - 1 -> Single $ b i - 2 -> Deep (2*s) (One (b i)) Empty (One (b (i+s))) - 3 -> Deep (3*s) (Two (b i) (b (i+s))) Empty (One (b (i+2*s))) - 4 -> Deep (4*s) (Two (b i) (b (i+s))) Empty (Two (b (i+2*s)) (b (i+3*s))) - 5 -> Deep (5*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Two (b (i+3*s)) (b (i+4*s))) - 6 -> Deep (6*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Three (b (i+3*s)) (b (i+4*s)) (b (i+5*s))) - _ -> case trees `quotRem` 3 of - (trees',1) -> Deep (trees*s) (Two (b i) (b (i+s))) - (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+2*s) (trees'-1)) - (Two (b (i+(2+3*(trees'-1))*s)) (b (i+(3+3*(trees'-1))*s))) - (trees',2) -> Deep (trees*s) (Three (b i) (b (i+s)) (b (i+2*s))) - (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+3*s) (trees'-1)) - (Two (b (i+(3+3*(trees'-1))*s)) (b (i+(4+3*(trees'-1))*s))) - (trees',0) -> Deep (trees*s) (Three (b i) (b (i+s)) (b (i+2*s))) - (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+3*s) (trees'-2)) - (Three (b (i+(3+3*(trees'-2))*s)) (b (i+(4+3*(trees'-2))*s)) (b (i+(5+3*(trees'-2))*s))) + where + create :: (Int -> a) -> Int -> Int -> Int -> FingerTree a + create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = i `seq` s `seq` case trees of + 1 -> Single $ b i + 2 -> Deep (2*s) (One (b i)) Empty (One (b (i+s))) + 3 -> Deep (3*s) (createTwo b s i) Empty (One (b (i+2*s))) + 4 -> Deep (4*s) (createTwo b s i) Empty (createTwo b s (i+2*s)) + 5 -> Deep (5*s) (createThree b s i) Empty (createTwo b s (i+3*s)) + 6 -> Deep (6*s) (createThree b s i) Empty (createThree b s (i+3*s)) + _ -> case trees `quotRem` 3 of + (trees', 1) -> Deep (trees*s) (createTwo b s i) + (create mb (3*s) (i+2*s) (trees'-1)) + (createTwo b s (i+(2+3*(trees'-1))*s)) + (trees', 2) -> Deep (trees*s) (createThree b s i) + (create mb (3*s) (i+3*s) (trees'-1)) + (createTwo b s (i+(3+3*(trees'-1))*s)) + (trees', 0) -> Deep (trees*s) (createThree b s i) + (create mb (3*s) (i+3*s) (trees'-2)) + (createThree b s (i+(3+3*(trees'-2))*s)) + where + createTwo b s i = Two (b i) (b (i + s)) + createThree b s i = Three (b i) (b (i + s)) (b (i + s + s)) + mb j = Node3 (3*s) (b j) (b (j + s)) (b (j + 2*s)) -- Splitting From git at git.haskell.org Fri Jan 23 22:40:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:53 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add Foldable.{elem, maximum, minimum, sum, product} specializations. (530fc76) Message-ID: <20150123224053.A50F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/530fc76bdd17089fcaaa655d66156abbc2092c2c >--------------------------------------------------------------- commit 530fc76bdd17089fcaaa655d66156abbc2092c2c Author: Milan Straka Date: Sun Oct 19 14:07:42 2014 +0200 Add Foldable.{elem,maximum,minimum,sum,product} specializations. Following #56, add specializations for other base-4.8 Foldable methods, using strict folds and shortcircuiting. The Set.elem uses only Eq a, so it runs in linear time. >--------------------------------------------------------------- 530fc76bdd17089fcaaa655d66156abbc2092c2c Data/IntMap/Base.hs | 30 ++++++++++++++++++++++++++++++ Data/Map/Base.hs | 25 +++++++++++++++++++++++++ Data/Set/Base.hs | 9 +++++++++ 3 files changed, 64 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index c1b2f4d..007e41e 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -341,6 +341,36 @@ instance Foldable.Foldable IntMap where {-# INLINE null #-} toList = elems -- NB: Foldable.toList /= IntMap.toList {-# INLINE toList #-} + elem = go + where STRICT_1_OF_2(go) + go _ Nil = False + go x (Tip _ y) = x == y + go x (Bin _ _ l r) = go x l || go x r + {-# INLINABLE elem #-} + maximum = start + where start Nil = error "IntMap.Foldable.maximum: called with empty map" + start (Tip _ y) = y + start (Bin _ _ l r) = go (start l) r + + STRICT_1_OF_2(go) + go m Nil = m + go m (Tip _ y) = max m y + go m (Bin _ _ l r) = go (go m l) r + {-# INLINABLE maximum #-} + minimum = start + where start Nil = error "IntMap.Foldable.minimum: called with empty map" + start (Tip _ y) = y + start (Bin _ _ l r) = go (start l) r + + STRICT_1_OF_2(go) + go m Nil = m + go m (Tip _ y) = min m y + go m (Bin _ _ l r) = go (go m l) r + {-# INLINABLE minimum #-} + sum = foldl' (+) 0 + {-# INLINABLE sum #-} + product = foldl' (*) 1 + {-# INLINABLE product #-} #endif instance Traversable IntMap where diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 781ac3a..de074f4 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -2675,6 +2675,31 @@ instance Foldable.Foldable (Map k) where {-# INLINE null #-} toList = elems -- NB: Foldable.toList /= Map.toList {-# INLINE toList #-} + elem = go + where STRICT_1_OF_2(go) + go _ Tip = False + go x (Bin _ _ v l r) = x == v || go x l || go x r + {-# INLINABLE elem #-} + maximum = start + where start Tip = error "Map.Foldable.maximum: called with empty map" + start (Bin _ _ v l r) = go (go v l) r + + STRICT_1_OF_2(go) + go m Tip = m + go m (Bin _ _ v l r) = go (go (max m v) l) r + {-# INLINABLE maximum #-} + minimum = start + where start Tip = error "Map.Foldable.minumum: called with empty map" + start (Bin _ _ v l r) = go (go v l) r + + STRICT_1_OF_2(go) + go m Tip = m + go m (Bin _ _ v l r) = go (go (min m v) l) r + {-# INLINABLE minimum #-} + sum = foldl' (+) 0 + {-# INLINABLE sum #-} + product = foldl' (*) 1 + {-# INLINABLE product #-} #endif instance (NFData k, NFData a) => NFData (Map k a) where diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 67ade4e..7e792f4 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -283,10 +283,19 @@ instance Foldable.Foldable Set where {-# INLINE null #-} toList = toList {-# INLINE toList #-} + elem = go + where STRICT_1_OF_2(go) + go _ Tip = False + go x (Bin _ y l r) = x == y || go x l || go x r + {-# INLINABLE elem #-} minimum = findMin {-# INLINE minimum #-} maximum = findMax {-# INLINE maximum #-} + sum = foldl' (+) 0 + {-# INLINABLE sum #-} + product = foldl' (*) 1 + {-# INLINABLE product #-} #endif From git at git.haskell.org Fri Jan 23 22:40:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:54 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Rename strictness tests to match other test names. (7e42d81) Message-ID: <20150123224054.079F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/7e42d81350aac6db1aa52180572a117e67b168b3 >--------------------------------------------------------------- commit 7e42d81350aac6db1aa52180572a117e67b168b3 Author: Milan Straka Date: Sun Dec 14 15:56:15 2014 +0100 Rename strictness tests to match other test names. >--------------------------------------------------------------- 7e42d81350aac6db1aa52180572a117e67b168b3 containers.cabal | 4 ++-- tests/{IntMapStrictness.hs => intmap-strictness.hs} | 0 tests/{MapStrictness.hs => map-strictness.hs} | 0 3 files changed, 2 insertions(+), 2 deletions(-) diff --git a/containers.cabal b/containers.cabal index 050257c..ae7e247 100644 --- a/containers.cabal +++ b/containers.cabal @@ -211,7 +211,7 @@ Test-suite seq-properties test-suite map-strictness-properties hs-source-dirs: tests, . - main-is: MapStrictness.hs + main-is: map-strictness.hs type: exitcode-stdio-1.0 build-depends: @@ -228,7 +228,7 @@ test-suite map-strictness-properties test-suite intmap-strictness-properties hs-source-dirs: tests, . - main-is: IntMapStrictness.hs + main-is: intmap-strictness.hs type: exitcode-stdio-1.0 build-depends: diff --git a/tests/IntMapStrictness.hs b/tests/intmap-strictness.hs similarity index 100% rename from tests/IntMapStrictness.hs rename to tests/intmap-strictness.hs diff --git a/tests/MapStrictness.hs b/tests/map-strictness.hs similarity index 100% rename from tests/MapStrictness.hs rename to tests/map-strictness.hs From git at git.haskell.org Fri Jan 23 22:40:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:55 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Force prefix and suffix before middle (7dfdc33) Message-ID: <20150123224055.ADAE83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/7dfdc33f8cc740036cee5a5e94c5603722d6fd02 >--------------------------------------------------------------- commit 7dfdc33f8cc740036cee5a5e94c5603722d6fd02 Author: treeowl Date: Sat Nov 8 22:08:19 2014 -0500 Force prefix and suffix before middle This should be slightly more efficient. Probably very slightly, but there doesn't seem to be a good reason not to. >--------------------------------------------------------------- 7dfdc33f8cc740036cee5a5e94c5603722d6fd02 Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index a2b4844..1952b1c 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -346,7 +346,7 @@ instance Traversable FingerTree where instance NFData a => NFData (FingerTree a) where rnf (Empty) = () rnf (Single x) = rnf x - rnf (Deep _ pr m sf) = rnf pr `seq` rnf m `seq` rnf sf + rnf (Deep _ pr m sf) = rnf pr `seq` rnf sf `seq` rnf m {-# INLINE deep #-} deep :: Sized a => Digit a -> FingerTree (Node a) -> Digit a -> FingerTree a From git at git.haskell.org Fri Jan 23 22:40:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:56 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Use pre-evaluated sequences in benchmarks. (999851e) Message-ID: <20150123224056.0EF5E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/999851e33acde2db08b06cf8d0331f37bbeb3c0b >--------------------------------------------------------------- commit 999851e33acde2db08b06cf8d0331f37bbeb3c0b Author: Milan Straka Date: Sun Dec 14 16:26:42 2014 +0100 Use pre-evaluated sequences in benchmarks. >--------------------------------------------------------------- 999851e33acde2db08b06cf8d0331f37bbeb3c0b benchmarks/Sequence.hs | 17 ++++++++++++----- 1 file changed, 12 insertions(+), 5 deletions(-) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index ccaca6c..8fd1fcf 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -12,13 +12,20 @@ main = do let s10 = S.fromList [1..10] :: S.Seq Int s100 = S.fromList [1..100] :: S.Seq Int s1000 = S.fromList [1..1000] :: S.Seq Int - rnf [s10, s100, s1000] `seq` return () + s10000 = S.fromList [1..10000] :: S.Seq Int + rnf [s10, s100, s1000, s10000] `seq` return () let g = mkStdGen 1 let rlist n = map (`mod` (n+1)) (take 10000 (randoms g)) :: [Int] r10 = rlist 10 r100 = rlist 100 r1000 = rlist 1000 - rnf [r10, r100, r1000] `seq` return () + r10000 = rlist 10000 + rnf [r10, r100, r1000, r10000] `seq` return () + let u10 = S.replicate 10 () :: S.Seq () + u100 = S.replicate 100 () :: S.Seq () + u1000 = S.replicate 1000 () :: S.Seq () + u10000 = S.replicate 10000 () :: S.Seq () + rnf [u10, u100, u1000, u10000] `seq` return () defaultMain [ bgroup "splitAt/append" [ bench "10" $ nf (shuffle r10) s10 @@ -26,9 +33,9 @@ main = do , bench "1000" $ nf (shuffle r1000) s1000 ] , bgroup "zip" - [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (S.replicate 10000 (), S.fromList [1..10000::Int]) - , bench "nf150" $ nf (uncurry S.zip) (S.fromList [1..150::Int], S.replicate 150 ()) - , bench "nf10000" $ nf (uncurry S.zip) (S.fromList [1..10000::Int], S.replicate 10000 ()) + [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (s10000, u10000) + , bench "nf100" $ nf (uncurry S.zip) (s100, u100) + , bench "nf10000" $ nf (uncurry S.zip) (s10000, u10000) ] ] -- splitAt+append: repeatedly cut the sequence at a random point From git at git.haskell.org Fri Jan 23 22:40:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:57 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #61 from treeowl/master (f9c23af) Message-ID: <20150123224057.B4E7A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/f9c23af0c7396aaf457ce9916392c7f949b60384 >--------------------------------------------------------------- commit f9c23af0c7396aaf457ce9916392c7f949b60384 Merge: 530fc76 7dfdc33 Author: Milan Straka Date: Sun Nov 9 07:11:13 2014 +0100 Merge pull request #61 from treeowl/master Force prefix and suffix before middle >--------------------------------------------------------------- f9c23af0c7396aaf457ce9916392c7f949b60384 Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:40:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:58 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Update URL of the fingertree paper. (7ffc123) Message-ID: <20150123224058.181AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/7ffc123000d82a676a23e0ce5e916a871598610f >--------------------------------------------------------------- commit 7ffc123000d82a676a23e0ce5e916a871598610f Author: Milan Straka Date: Sun Dec 14 16:40:11 2014 +0100 Update URL of the fingertree paper. >--------------------------------------------------------------- 7ffc123000d82a676a23e0ce5e916a871598610f Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index f3fbbe7..9f3f543 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -40,7 +40,7 @@ -- * Ralf Hinze and Ross Paterson, -- \"Finger trees: a simple general-purpose data structure\", -- /Journal of Functional Programming/ 16:2 (2006) pp 197-217. --- +-- -- -- /Note/: Many of these operations have the same names as similar -- operations on lists in the "Prelude". The ambiguity may be resolved From git at git.haskell.org Fri Jan 23 22:40:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:40:59 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. (245ef13) Message-ID: <20150123224059.BDD983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/245ef135eb8701fcd139770e564f25e774d26422 >--------------------------------------------------------------- commit 245ef135eb8701fcd139770e564f25e774d26422 Author: David Terei Date: Wed Nov 12 18:19:51 2014 -0800 Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. >--------------------------------------------------------------- 245ef135eb8701fcd139770e564f25e774d26422 Data/IntMap.hs | 2 +- Data/IntMap/Lazy.hs | 2 +- Data/IntMap/Strict.hs | 4 +++- Data/Utils/StrictFold.hs | 2 +- Data/Utils/StrictPair.hs | 2 +- 5 files changed, 7 insertions(+), 5 deletions(-) diff --git a/Data/IntMap.hs b/Data/IntMap.hs index 29ca3f5..52b05c2 100644 --- a/Data/IntMap.hs +++ b/Data/IntMap.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif ----------------------------------------------------------------------------- -- | diff --git a/Data/IntMap/Lazy.hs b/Data/IntMap/Lazy.hs index ab89e1a..62bf835 100644 --- a/Data/IntMap/Lazy.hs +++ b/Data/IntMap/Lazy.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif ----------------------------------------------------------------------------- -- | diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs index 3a7dde8..f1c363c 100644 --- a/Data/IntMap/Strict.hs +++ b/Data/IntMap/Strict.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} -#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 +#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/Data/Utils/StrictFold.hs b/Data/Utils/StrictFold.hs index 953c9f1..b080e8a 100644 --- a/Data/Utils/StrictFold.hs +++ b/Data/Utils/StrictFold.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif module Data.Utils.StrictFold (foldlStrict) where diff --git a/Data/Utils/StrictPair.hs b/Data/Utils/StrictPair.hs index 6ae7ded..0c01ca4 100644 --- a/Data/Utils/StrictPair.hs +++ b/Data/Utils/StrictPair.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif module Data.Utils.StrictPair (StrictPair(..), toPair) where From git at git.haskell.org Fri Jan 23 22:41:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:00 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Add test for fromFunction. (61eeeec) Message-ID: <20150123224100.1E8173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/61eeeec856e39108ba3d5cb4251b249acc782305 >--------------------------------------------------------------- commit 61eeeec856e39108ba3d5cb4251b249acc782305 Author: Milan Straka Date: Sun Dec 14 16:49:49 2014 +0100 Add test for fromFunction. >--------------------------------------------------------------- 61eeeec856e39108ba3d5cb4251b249acc782305 tests/seq-properties.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index 74b2e9c..14d5a5f 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -36,6 +36,7 @@ main = defaultMain , testProperty "(|>)" prop_snoc , testProperty "(><)" prop_append , testProperty "fromList" prop_fromList + , testProperty "fromFunction" prop_fromFunction , testProperty "replicate" prop_replicate , testProperty "replicateA" prop_replicateA , testProperty "replicateM" prop_replicateM @@ -270,6 +271,10 @@ prop_fromList :: [A] -> Bool prop_fromList xs = toList' (fromList xs) ~= xs +prop_fromFunction :: [A] -> Bool +prop_fromFunction xs = + toList' (fromFunction (Prelude.length xs) (xs!!)) ~= xs + -- ** Repetition prop_replicate :: NonNegative Int -> A -> Bool From git at git.haskell.org Fri Jan 23 22:41:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:01 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add support for `deepseq-1.4` (667cf94) Message-ID: <20150123224101.C50BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/667cf94c6826738429485b806354d1e92136ba56 >--------------------------------------------------------------- commit 667cf94c6826738429485b806354d1e92136ba56 Author: Herbert Valerio Riedel Date: Fri Nov 14 16:09:27 2014 +0100 Add support for `deepseq-1.4` This change avoids relying on `rnf`'s default method implementation which has changed in `deepseq-1.4.0.0` >--------------------------------------------------------------- 667cf94c6826738429485b806354d1e92136ba56 Data/IntSet/Base.hs | 4 ++-- containers.cabal | 22 +++++++++++----------- 2 files changed, 13 insertions(+), 13 deletions(-) diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index b6f8014..6333eea 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -162,7 +162,7 @@ module Data.IntSet.Base ( , bitmapOf ) where -import Control.DeepSeq (NFData) +import Control.DeepSeq (NFData(rnf)) import Data.Bits import qualified Data.List as List import Data.Maybe (fromMaybe) @@ -1099,7 +1099,7 @@ INSTANCE_TYPEABLE0(IntSet,intSetTc,"IntSet") -- The IntSet constructors consist only of strict fields of Ints and -- IntSets, thus the default NFData instance which evaluates to whnf -- should suffice -instance NFData IntSet +instance NFData IntSet where rnf x = seq x () {-------------------------------------------------------------------- Debugging diff --git a/containers.cabal b/containers.cabal index 815882e..050257c 100644 --- a/containers.cabal +++ b/containers.cabal @@ -31,7 +31,7 @@ source-repository head location: http://github.com/haskell/containers.git Library - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4 + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5 if impl(ghc>=6.10) build-depends: ghc-prim @@ -83,7 +83,7 @@ Test-suite map-lazy-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -100,7 +100,7 @@ Test-suite map-strict-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING -DSTRICT - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -117,7 +117,7 @@ Test-suite set-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -134,7 +134,7 @@ Test-suite intmap-lazy-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -151,7 +151,7 @@ Test-suite intmap-strict-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING -DSTRICT - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -168,7 +168,7 @@ Test-suite intset-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -185,7 +185,7 @@ Test-suite deprecated-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -200,7 +200,7 @@ Test-suite seq-properties type: exitcode-stdio-1.0 cpp-options: -DTESTING - build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.4, ghc-prim + build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types @@ -218,7 +218,7 @@ test-suite map-strictness-properties array, base >= 4.2 && < 5, ChasingBottoms, - deepseq >= 1.2 && < 1.4, + deepseq >= 1.2 && < 1.5, QuickCheck >= 2.4.0.1, ghc-prim, test-framework >= 0.3.3, @@ -235,7 +235,7 @@ test-suite intmap-strictness-properties array, base >= 4.2 && < 5, ChasingBottoms, - deepseq >= 1.2 && < 1.4, + deepseq >= 1.2 && < 1.5, QuickCheck >= 2.4.0.1, ghc-prim, test-framework >= 0.3.3, From git at git.haskell.org Fri Jan 23 22:41:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:02 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Fix warnings. (610ebfb) Message-ID: <20150123224102.27B653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/610ebfbe4eecfb04886ed87691aeb65869ee0445 >--------------------------------------------------------------- commit 610ebfbe4eecfb04886ed87691aeb65869ee0445 Author: Milan Straka Date: Mon Dec 15 07:41:55 2014 +0100 Fix warnings. >--------------------------------------------------------------- 610ebfbe4eecfb04886ed87691aeb65869ee0445 Data/Sequence.hs | 48 ++++++++++++++++++++++-------------------------- 1 file changed, 22 insertions(+), 26 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 9f3f543..d85cab6 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -164,9 +164,9 @@ import Data.Functor (Functor(..)) import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr', toList)) #else #if MIN_VERSION_base(4,6,0) -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr'), toList) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl'), toList) #else -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', foldr', toList) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', toList) #endif #endif import Data.Traversable @@ -180,6 +180,7 @@ import Data.Data #endif #if __GLASGOW_HASKELL__ >= 708 import Data.Coerce +import qualified GHC.Exts #define COERCE coerce #else #ifdef __GLASGOW_HASKELL__ @@ -192,9 +193,6 @@ import qualified Unsafe.Coerce #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity(..)) #endif -#ifdef __GLASGOW_HASKELL__ -import qualified GHC.Exts -#endif infixr 5 `consTree` infixl 5 `snocTree` @@ -246,6 +244,8 @@ instance Foldable Seq where {-# INLINE length #-} null = null {-# INLINE null #-} + toList = toList + {-# INLINE toList #-} #endif instance Traversable Seq where @@ -611,10 +611,6 @@ instance Applicative (State s) where execState :: State s a -> s -> a execState m x = snd (runState m x) --- | A helper method: a strict version of mapAccumL. -mapAccumL' :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) -mapAccumL' f s t = runState (traverse (State . flip f) t) s - -- | 'applicativeTree' takes an Applicative-wrapped construction of a -- piece of a FingerTree, assumed to always have the same size (which -- is put in the second argument), and replicates it as many times as @@ -1305,12 +1301,12 @@ adjustDigit f i (Four a b c d) -- function that also depends on the element's index, and applies it to every -- element in the sequence. mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b -mapWithIndex f (Seq xs) = Seq $ mapWithIndexTree (\s (Elem a) -> Elem (f s a)) 0 xs +mapWithIndex f' (Seq xs') = Seq $ mapWithIndexTree (\s (Elem a) -> Elem (f' s a)) 0 xs' where {-# SPECIALIZE mapWithIndexTree :: (Int -> Elem y -> b) -> Int -> FingerTree (Elem y) -> FingerTree b #-} {-# SPECIALIZE mapWithIndexTree :: (Int -> Node y -> b) -> Int -> FingerTree (Node y) -> FingerTree b #-} mapWithIndexTree :: Sized a => (Int -> a -> b) -> Int -> FingerTree a -> FingerTree b - mapWithIndexTree _f s Empty = s `seq` Empty + mapWithIndexTree _ s Empty = s `seq` Empty mapWithIndexTree f s (Single xs) = Single $ f s xs mapWithIndexTree f s (Deep n pr m sf) = sPspr `seq` sPsprm `seq` Deep n @@ -1379,23 +1375,23 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = i `seq` s `seq` case trees of 1 -> Single $ b i 2 -> Deep (2*s) (One (b i)) Empty (One (b (i+s))) - 3 -> Deep (3*s) (createTwo b s i) Empty (One (b (i+2*s))) - 4 -> Deep (4*s) (createTwo b s i) Empty (createTwo b s (i+2*s)) - 5 -> Deep (5*s) (createThree b s i) Empty (createTwo b s (i+3*s)) - 6 -> Deep (6*s) (createThree b s i) Empty (createThree b s (i+3*s)) + 3 -> Deep (3*s) (createTwo i) Empty (One (b (i+2*s))) + 4 -> Deep (4*s) (createTwo i) Empty (createTwo (i+2*s)) + 5 -> Deep (5*s) (createThree i) Empty (createTwo (i+3*s)) + 6 -> Deep (6*s) (createThree i) Empty (createThree (i+3*s)) _ -> case trees `quotRem` 3 of - (trees', 1) -> Deep (trees*s) (createTwo b s i) + (trees', 1) -> Deep (trees*s) (createTwo i) (create mb (3*s) (i+2*s) (trees'-1)) - (createTwo b s (i+(2+3*(trees'-1))*s)) - (trees', 2) -> Deep (trees*s) (createThree b s i) + (createTwo (i+(2+3*(trees'-1))*s)) + (trees', 2) -> Deep (trees*s) (createThree i) (create mb (3*s) (i+3*s) (trees'-1)) - (createTwo b s (i+(3+3*(trees'-1))*s)) - (trees', 0) -> Deep (trees*s) (createThree b s i) + (createTwo (i+(3+3*(trees'-1))*s)) + (trees', _) -> Deep (trees*s) (createThree i) (create mb (3*s) (i+3*s) (trees'-2)) - (createThree b s (i+(3+3*(trees'-2))*s)) + (createThree (i+(3+3*(trees'-2))*s)) where - createTwo b s i = Two (b i) (b (i + s)) - createThree b s i = Three (b i) (b (i + s)) (b (i + s + s)) + createTwo j = Two (b j) (b (j + s)) + createThree j = Three (b j) (b (j + s)) (b (j + 2*s)) mb j = Node3 (3*s) (b j) (b (j + s)) (b (j + 2*s)) -- Splitting @@ -1884,8 +1880,8 @@ splitMap splt' = go {-# SPECIALIZE splitMapTree :: (Int -> s -> (s,s)) -> (s -> Elem y -> b) -> s -> FingerTree (Elem y) -> FingerTree b #-} {-# SPECIALIZE splitMapTree :: (Int -> s -> (s,s)) -> (s -> Node y -> b) -> s -> FingerTree (Node y) -> FingerTree b #-} splitMapTree :: Sized a => (Int -> s -> (s,s)) -> (s -> a -> b) -> s -> FingerTree a -> FingerTree b - splitMapTree splt _f _s Empty = Empty - splitMapTree splt f s (Single xs) = Single $ f s xs + splitMapTree _ _ _ Empty = Empty + splitMapTree _ f s (Single xs) = Single $ f s xs splitMapTree splt f s (Deep n pr m sf) = Deep n (splitMapDigit splt f prs pr) (splitMapTree splt (splitMapNode splt f) ms m) (splitMapDigit splt f sfs sf) where (prs, r) = splt (size pr) s @@ -1894,7 +1890,7 @@ splitMap splt' = go {-# SPECIALIZE splitMapDigit :: (Int -> s -> (s,s)) -> (s -> Elem y -> b) -> s -> Digit (Elem y) -> Digit b #-} {-# SPECIALIZE splitMapDigit :: (Int -> s -> (s,s)) -> (s -> Node y -> b) -> s -> Digit (Node y) -> Digit b #-} splitMapDigit :: Sized a => (Int -> s -> (s,s)) -> (s -> a -> b) -> s -> Digit a -> Digit b - splitMapDigit splt f s (One a) = One (f s a) + splitMapDigit _ f s (One a) = One (f s a) splitMapDigit splt f s (Two a b) = Two (f first a) (f second b) where (first, second) = splt (size a) s From git at git.haskell.org Fri Jan 23 22:41:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:03 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #65 from dterei/safe710fixes (09ae752) Message-ID: <20150123224103.CE2CD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/09ae752eeffd06e24ffb4abeabcd6511dea0e68e >--------------------------------------------------------------- commit 09ae752eeffd06e24ffb4abeabcd6511dea0e68e Merge: f9c23af 245ef13 Author: Milan Straka Date: Fri Nov 14 16:15:41 2014 +0100 Merge pull request #65 from dterei/safe710fixes Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. >--------------------------------------------------------------- 09ae752eeffd06e24ffb4abeabcd6511dea0e68e Data/IntMap.hs | 2 +- Data/IntMap/Lazy.hs | 2 +- Data/IntMap/Strict.hs | 4 +++- Data/Utils/StrictFold.hs | 2 +- Data/Utils/StrictPair.hs | 2 +- 5 files changed, 7 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Jan 23 22:41:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:04 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Make sure the helper functions are inlined. (3e60f3a) Message-ID: <20150123224104.2F68F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/3e60f3aa337ddf670a3f20586353c539f6b49eb4 >--------------------------------------------------------------- commit 3e60f3aa337ddf670a3f20586353c539f6b49eb4 Author: Milan Straka Date: Mon Dec 15 08:15:42 2014 +0100 Make sure the helper functions are inlined. >--------------------------------------------------------------- 3e60f3aa337ddf670a3f20586353c539f6b49eb4 Data/Sequence.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index d85cab6..fa80b3f 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1391,8 +1391,11 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg (createThree (i+(3+3*(trees'-2))*s)) where createTwo j = Two (b j) (b (j + s)) + {-# INLINE createTwo #-} createThree j = Three (b j) (b (j + s)) (b (j + 2*s)) + {-# INLINE createThree #-} mb j = Node3 (3*s) (b j) (b (j + s)) (b (j + 2*s)) + {-# INLINE mb #-} -- Splitting From git at git.haskell.org Fri Jan 23 22:41:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:05 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #67 from hvr/pr-deepseq-14 (c802c36) Message-ID: <20150123224105.D6D223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c802c36dbed4b800d8c2131181f5af3db837aded >--------------------------------------------------------------- commit c802c36dbed4b800d8c2131181f5af3db837aded Merge: 09ae752 667cf94 Author: Milan Straka Date: Fri Nov 14 16:27:16 2014 +0100 Merge pull request #67 from hvr/pr-deepseq-14 Add support for `deepseq-1.4` >--------------------------------------------------------------- c802c36dbed4b800d8c2131181f5af3db837aded Data/IntSet/Base.hs | 4 ++-- containers.cabal | 22 +++++++++++----------- 2 files changed, 13 insertions(+), 13 deletions(-) From git at git.haskell.org Fri Jan 23 22:41:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:06 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Move the closing parent to a separate line. (97599c0) Message-ID: <20150123224106.36AC43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/97599c082e5388551d2f8f767045b807194083fa >--------------------------------------------------------------- commit 97599c082e5388551d2f8f767045b807194083fa Author: Milan Straka Date: Mon Dec 15 08:24:34 2014 +0100 Move the closing parent to a separate line. >--------------------------------------------------------------- 97599c082e5388551d2f8f767045b807194083fa benchmarks/Sequence.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index 8fd1fcf..8bc2d74 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -36,7 +36,8 @@ main = do [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (s10000, u10000) , bench "nf100" $ nf (uncurry S.zip) (s100, u100) , bench "nf10000" $ nf (uncurry S.zip) (s10000, u10000) - ] ] + ] + ] -- splitAt+append: repeatedly cut the sequence at a random point -- and rejoin the pieces in the opposite order. From git at git.haskell.org Fri Jan 23 22:41:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:07 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Improve Foldable methods (c4884ad) Message-ID: <20150123224107.DF01F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c4884ad0d7310e62c48ebd23600d73230718ae45 >--------------------------------------------------------------- commit c4884ad0d7310e62c48ebd23600d73230718ae45 Author: David Feuer Date: Mon Nov 17 17:48:10 2014 -0500 Improve Foldable methods Define foldMap for Seq directly, instead of relying on the default based on foldr. Define length and null for ViewR directly, instead of relying on (inappropriate) defaults. >--------------------------------------------------------------- c4884ad0d7310e62c48ebd23600d73230718ae45 Data/Sequence.hs | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 1952b1c..0c2be04 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -149,7 +149,7 @@ import Control.DeepSeq (NFData(rnf)) import Control.Monad (MonadPlus(..), ap) import Data.Monoid (Monoid(..)) import Data.Functor (Functor(..)) -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1), foldl', toList) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', foldr', toList) import Data.Traversable import Data.Typeable @@ -188,6 +188,7 @@ instance Functor Seq where #endif instance Foldable Seq where + foldMap f (Seq xs) = foldMap (foldMap f) xs foldr f z (Seq xs) = foldr (flip (foldr f)) z xs foldl f z (Seq xs) = foldl (foldl f) z xs @@ -310,6 +311,11 @@ instance Sized a => Sized (FingerTree a) where size (Deep v _ _ _) = v instance Foldable FingerTree where + foldMap _ Empty = mempty + foldMap f (Single x) = f x + foldMap f (Deep _ pr m sf) = + foldMap f pr `mappend` (foldMap (foldMap f) m `mappend` foldMap f sf) + foldr _ z Empty = z foldr f z (Single x) = x `f` z foldr f z (Deep _ pr m sf) = @@ -388,6 +394,11 @@ data Digit a #endif instance Foldable Digit where + foldMap f (One a) = f a + foldMap f (Two a b) = f a `mappend` f b + foldMap f (Three a b c) = f a `mappend` (f b `mappend` f c) + foldMap f (Four a b c d) = f a `mappend` (f b `mappend` (f c `mappend` f d)) + foldr f z (One a) = a `f` z foldr f z (Two a b) = a `f` (b `f` z) foldr f z (Three a b c) = a `f` (b `f` (c `f` z)) @@ -458,6 +469,9 @@ data Node a #endif instance Foldable Node where + foldMap f (Node2 _ a b) = f a `mappend` f b + foldMap f (Node3 _ a b c) = f a `mappend` (f b `mappend` f c) + foldr f z (Node2 _ a b) = a `f` (b `f` z) foldr f z (Node3 _ a b c) = a `f` (b `f` (c `f` z)) @@ -508,6 +522,7 @@ instance Functor Elem where fmap f (Elem x) = Elem (f x) instance Foldable Elem where + foldMap f (Elem x) = f x foldr f z (Elem x) = f x z foldl f z (Elem x) = f z x @@ -1009,6 +1024,9 @@ instance Functor ViewR where fmap f (xs :> x) = fmap f xs :> f x instance Foldable ViewR where + foldMap _ EmptyR = mempty + foldMap f (xs :> x) = foldMap f xs `mappend` f x + foldr _ z EmptyR = z foldr f z (xs :> x) = foldr f (f x z) xs @@ -1017,6 +1035,14 @@ instance Foldable ViewR where foldr1 _ EmptyR = error "foldr1: empty view" foldr1 f (xs :> x) = foldr f x xs +#if MIN_VERSION_base(4,8,0) + -- The default definitions are sensible for ViewL, but not so much for + -- ViewR. + null EmptyR = True + null (_ :> _) = False + + length = foldr' (\_ k -> k+1) 0 +#endif instance Traversable ViewR where traverse _ EmptyR = pure EmptyR From git at git.haskell.org Fri Jan 23 22:41:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:08 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Remove unsafeCoerce, use only coerce on GHC 7.8 and later. (b38f240) Message-ID: <20150123224108.403013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/b38f240ab4bec53c5f5800cc1b621a00b4604b2d >--------------------------------------------------------------- commit b38f240ab4bec53c5f5800cc1b621a00b4604b2d Author: Milan Straka Date: Mon Dec 15 09:02:37 2014 +0100 Remove unsafeCoerce, use only coerce on GHC 7.8 and later. Also, move the conditional compilation to a local where definition. On my GHC 7.6.3, there is no heap allocation in the cmm in fromFunction for the (Elem . f) closure, so there is no penalty of not using `coerce`. Nevertheless, GHC 7.8.3 and GHC-head (15 Dec 2014) do heap-allocate trivial closure for (Elem . f), so `coerce` helps. Back to GHC 7.6.3, I found that the following does not allocate in GHC 7.6.3: newtype Elem a = Elem a elemMap :: Int -> (Int -> b) -> [Elem b] elemMap s f = go (Elem . f) 0 where go :: (Int -> b) -> Int -> [b] go f i | i >= s = [] | otherwise = f i : go f (i+1) Nevertheless, the following does heap-allocate trivial closure for f: newtype Elem a = Elem a elemMap :: [Int] -> (Int -> b) -> [Elem b] elemMap xs f = go (Elem . f) xs where go :: (Int -> b) -> [Int] -> [b] go f [] = [] go f (x:xs) = f x : go f xs I am not sure what the difference is, but the current fromFunction does not allocate too (on 7.6.3). >--------------------------------------------------------------- b38f240ab4bec53c5f5800cc1b621a00b4604b2d Data/Sequence.hs | 21 +++++++++------------ 1 file changed, 9 insertions(+), 12 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index fa80b3f..4c281fc 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -181,14 +181,7 @@ import Data.Data #if __GLASGOW_HASKELL__ >= 708 import Data.Coerce import qualified GHC.Exts -#define COERCE coerce #else -#ifdef __GLASGOW_HASKELL__ -import qualified Unsafe.Coerce --- Note that by compiling this file with GHC 7.8 or later, we prove that --- it is safe to use COERCE with earlier GHC versions. -#define COERCE Unsafe.Coerce.unsafeCoerce -#endif #endif #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity(..)) @@ -1365,11 +1358,7 @@ mapWithIndex f' (Seq xs') = Seq $ mapWithIndexTree (\s (Elem a) -> Elem (f' s a) fromFunction :: Int -> (Int -> a) -> Seq a fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with negative len" | len == 0 = empty -#ifdef __GLASGOW_HASKELL__ - | otherwise = Seq $ create (COERCE f) 1 0 len -#else - | otherwise = Seq $ create (Elem . f) 1 0 len -#endif + | otherwise = Seq $ create (lift_elem f) 1 0 len where create :: (Int -> a) -> Int -> Int -> Int -> FingerTree a create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = i `seq` s `seq` case trees of @@ -1397,6 +1386,14 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg mb j = Node3 (3*s) (b j) (b (j + s)) (b (j + 2*s)) {-# INLINE mb #-} + lift_elem :: (Int -> a) -> (Int -> Elem a) +#if __GLASGOW_HASKELL__ >= 708 + lift_elem g = coerce g +#else + lift_elem g = Elem . g +#endif + {-# INLINE lift_elem #-} + -- Splitting -- | /O(log(min(i,n-i)))/. The first @i@ elements of a sequence. From git at git.haskell.org Fri Jan 23 22:41:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:09 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #68 from treeowl/foldmapseq (94fa013) Message-ID: <20150123224109.E5D913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/94fa01318f3a575eb3045956415827b582ac9fb8 >--------------------------------------------------------------- commit 94fa01318f3a575eb3045956415827b582ac9fb8 Merge: c802c36 c4884ad Author: Milan Straka Date: Tue Nov 18 10:31:01 2014 +0100 Merge pull request #68 from treeowl/foldmapseq Improve Foldable methods >--------------------------------------------------------------- 94fa01318f3a575eb3045956415827b582ac9fb8 Data/Sequence.hs | 28 +++++++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:41:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:10 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Add simple fromFunction benchmarks. (a556ef2) Message-ID: <20150123224110.464233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/a556ef225952c27731a00b24b6417b6a057507ce >--------------------------------------------------------------- commit a556ef225952c27731a00b24b6417b6a057507ce Author: Milan Straka Date: Mon Dec 15 14:47:20 2014 +0100 Add simple fromFunction benchmarks. >--------------------------------------------------------------- a556ef225952c27731a00b24b6417b6a057507ce benchmarks/Sequence.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index 8bc2d74..b6b82fa 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -37,6 +37,13 @@ main = do , bench "nf100" $ nf (uncurry S.zip) (s100, u100) , bench "nf10000" $ nf (uncurry S.zip) (s10000, u10000) ] + , bgroup "fromFunction" + [ bench "ix10000/5000" $ nf (\s -> S.fromFunction s (+1) `S.index` (s `div` 2)) 10000 + , bench "nf10" $ nf (\s -> S.fromFunction s (+1)) 10 + , bench "nf100" $ nf (\s -> S.fromFunction s (+1)) 100 + , bench "nf1000" $ nf (\s -> S.fromFunction s (+1)) 1000 + , bench "nf10000" $ nf (\s -> S.fromFunction s (+1)) 10000 + ] ] -- splitAt+append: repeatedly cut the sequence at a random point From git at git.haskell.org Fri Jan 23 22:41:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:12 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Implement fmap/coerce rules (ad24ce6) Message-ID: <20150123224112.010B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/ad24ce6e10d2a0168dcb4d68765b4a25ae22ad88 >--------------------------------------------------------------- commit ad24ce6e10d2a0168dcb4d68765b4a25ae22ad88 Author: David Feuer Date: Thu Nov 13 00:16:28 2014 -0500 Implement fmap/coerce rules Implement fmap/coerce rules for Map, Sequence, and Tree. One concern: unfortunately, implementing the RULES forces the LANGUAGE to be turned from Safe to Trustworthy. This is rather sad. An alternative would be to do this in another module, but orphan rules are not so lovely either. >--------------------------------------------------------------- ad24ce6e10d2a0168dcb4d68765b4a25ae22ad88 Data/Map/Base.hs | 24 +++++++++++++++++------- Data/Map/Strict.hs | 19 ++++++++++++++++++- Data/Sequence.hs | 27 ++++++++++++++++++++------- Data/Tree.hs | 29 ++++++++++++++++++++++------- tests-ghc/all.T | 3 +++ tests-ghc/mapcoercemap.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoercemap.stdout | 3 +++ tests-ghc/mapcoerceseq.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoerceseq.stdout | 3 +++ tests-ghc/mapcoercesmap.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoercesmap.stdout | 3 +++ 11 files changed, 164 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ad24ce6e10d2a0168dcb4d68765b4a25ae22ad88 From git at git.haskell.org Fri Jan 23 22:41:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:12 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Use a top-down version of fromList (51a1f7c) Message-ID: <20150123224112.4E53F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/51a1f7c6670058ed4feefd1ef86170ddef173e63 >--------------------------------------------------------------- commit 51a1f7c6670058ed4feefd1ef86170ddef173e63 Author: David Feuer Date: Tue Dec 9 14:56:53 2014 -0500 Use a top-down version of fromList Ross Paterson came up with a version of fromList that avoids the tree rebuilding inherent in the `(|>)`-based approach. This version is somewhat strictified and rearranged. It reduces allocation substantially over the old version. Mutator time goes down too, but for some reason GC time rises to match it. >--------------------------------------------------------------- 51a1f7c6670058ed4feefd1ef86170ddef173e63 Data/Sequence.hs | 25 ++++++++++++++++++++++++- 1 file changed, 24 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 4c281fc..651dd5e 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1752,11 +1752,34 @@ findIndicesR p xs = foldlWithIndex g [] xs -- Lists ------------------------------------------------------------------------ +-- The implementation below, by Ross Paterson, avoids the rebuilding +-- the previous (|>)-based implementation suffered from. + -- | /O(n)/. Create a sequence from a finite list of elements. -- There is a function 'toList' in the opposite direction for all -- instances of the 'Foldable' class, including 'Seq'. fromList :: [a] -> Seq a -fromList = Data.List.foldl' (|>) empty +fromList xs = Seq $ mkTree 1 $ Data.List.map Elem xs + where + {-# SPECIALIZE mkTree :: Int -> [Elem a] -> FingerTree (Elem a) #-} + {-# SPECIALIZE mkTree :: Int -> [Node a] -> FingerTree (Node a) #-} + mkTree :: (Sized a) => Int -> [a] -> FingerTree a + mkTree s [] = s `seq` Empty + mkTree s [x1] = s `seq` Single x1 + mkTree s [x1, x2] = Deep (2*s) (One x1) Empty (One x2) + mkTree s [x1, x2, x3] = Deep (3*s) (One x1) Empty (Two x2 x3) + mkTree s (x1:x2:x3:xs) = s `seq` case getNodes (3*s) xs of + (ns, sf) -> m `seq` deep' (Three x1 x2 x3) m sf + where m = mkTree (3*s) ns + + deep' pr@(Three x1 _ _) m sf = Deep (3*size x1 + size m + size sf) pr m sf + + getNodes :: Int -> [a] -> ([Node a], Digit a) + getNodes s [x1] = s `seq` ([], One x1) + getNodes s [x1, x2] = s `seq` ([], Two x1 x2) + getNodes s [x1, x2, x3] = s `seq` ([], Three x1 x2 x3) + getNodes s (x1:x2:x3:xs) = s `seq` (Node3 s x1 x2 x3:ns, d) + where (ns, d) = getNodes s xs #if __GLASGOW_HASKELL__ >= 708 instance GHC.Exts.IsList (Seq a) where From git at git.haskell.org Fri Jan 23 22:41:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:14 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #66 from treeowl/seqfmapcoerce (e083f68) Message-ID: <20150123224114.0B6A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/e083f683d833d6ffd98b7b91f27c1e10a2cded97 >--------------------------------------------------------------- commit e083f683d833d6ffd98b7b91f27c1e10a2cded97 Merge: 94fa013 ad24ce6 Author: Milan Straka Date: Tue Nov 18 14:50:46 2014 +0100 Merge pull request #66 from treeowl/seqfmapcoerce Implement fmap/coerce rules >--------------------------------------------------------------- e083f683d833d6ffd98b7b91f27c1e10a2cded97 Data/Map/Base.hs | 24 +++++++++++++++++------- Data/Map/Strict.hs | 19 ++++++++++++++++++- Data/Sequence.hs | 27 ++++++++++++++++++++------- Data/Tree.hs | 29 ++++++++++++++++++++++------- tests-ghc/all.T | 3 +++ tests-ghc/mapcoercemap.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoercemap.stdout | 3 +++ tests-ghc/mapcoerceseq.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoerceseq.stdout | 3 +++ tests-ghc/mapcoercesmap.hs | 25 +++++++++++++++++++++++++ tests-ghc/mapcoercesmap.stdout | 3 +++ 11 files changed, 164 insertions(+), 22 deletions(-) diff --cc Data/Sequence.hs index 0c2be04,0bef765..1c4e143 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@@ -187,8 -189,18 +189,19 @@@ instance Functor Seq wher x <$ s = replicate (length s) x #endif + fmapSeq :: (a -> b) -> Seq a -> Seq b + fmapSeq f (Seq xs) = Seq (fmap (fmap f) xs) + #if MIN_VERSION_base(4,8,0) + -- Safe coercions were introduced in 4.7.0, but I am not sure if they played + -- well enough with RULES to do what we want. + {-# NOINLINE [1] fmapSeq #-} + {-# RULES + "fmapSeq/coerce" fmapSeq coerce = coerce + #-} + #endif + instance Foldable Seq where + foldMap f (Seq xs) = foldMap (foldMap f) xs foldr f z (Seq xs) = foldr (flip (foldr f)) z xs foldl f z (Seq xs) = foldl (foldl f) z xs From git at git.haskell.org Fri Jan 23 22:41:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:14 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Remove trailing whitespace. (a1d613b) Message-ID: <20150123224114.56DFA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/a1d613b50c2e0e15e01159ab2fa1b377a49e2a38 >--------------------------------------------------------------- commit a1d613b50c2e0e15e01159ab2fa1b377a49e2a38 Author: Milan Straka Date: Mon Dec 15 17:30:58 2014 +0100 Remove trailing whitespace. >--------------------------------------------------------------- a1d613b50c2e0e15e01159ab2fa1b377a49e2a38 Data/Sequence.hs | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Fri Jan 23 22:41:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:16 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add fmap/fmap rules (352c73d) Message-ID: <20150123224116.183913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/352c73dca04572fc843417518b9f5dd684c1792c >--------------------------------------------------------------- commit 352c73dca04572fc843417518b9f5dd684c1792c Author: David Feuer Date: Tue Nov 18 09:41:29 2014 -0500 Add fmap/fmap rules Specifically, fuse map, mapWithIndex, mapWithKey, etc., with each other. >--------------------------------------------------------------- 352c73dca04572fc843417518b9f5dd684c1792c Data/IntMap/Base.hs | 19 +++++++++++++++++++ Data/IntMap/Strict.hs | 19 +++++++++++++++++++ Data/Map/Base.hs | 19 ++++++++++++++++++- Data/Map/Strict.hs | 24 +++++++++++++++++++++--- Data/Sequence.hs | 19 ++++++++++++++++++- 5 files changed, 95 insertions(+), 5 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 007e41e..3832e1c 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -1301,6 +1301,13 @@ map f t Tip k x -> Tip k (f x) Nil -> Nil +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] map #-} +{-# RULES +"map/map" forall f g xs . map f (map g xs) = map (f . g) xs + #-} +#endif + -- | /O(n)/. Map a function over all values in the map. -- -- > let f key x = (show key) ++ ":" ++ x @@ -1313,6 +1320,18 @@ mapWithKey f t Tip k x -> Tip k (f k x) Nil -> Nil +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] mapWithKey #-} +{-# RULES +"mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) = + mapWithKey (\k a -> f k (g k a)) xs +"mapWithKey/map" forall f g xs . mapWithKey f (map g xs) = + mapWithKey (\k a -> f k (g a)) xs +"map/mapWithKey" forall f g xs . map f (mapWithKey g xs) = + mapWithKey (\k a -> f (g k a)) xs + #-} +#endif + -- | /O(n)/. -- @'traverseWithKey' f s == 'fromList' <$> 'traverse' (\(k, v) -> (,) k <$> f k v) ('toList' m)@ -- That is, behaves exactly like a regular 'traverse' except that the traversing diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs index f1c363c..af44b2a 100644 --- a/Data/IntMap/Strict.hs +++ b/Data/IntMap/Strict.hs @@ -718,6 +718,13 @@ map f t Tip k x -> Tip k $! f x Nil -> Nil +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] map #-} +{-# RULES +"map/map" forall f g xs . map f (map g xs) = map (f . g) xs + #-} +#endif + -- | /O(n)/. Map a function over all values in the map. -- -- > let f key x = (show key) ++ ":" ++ x @@ -730,6 +737,18 @@ mapWithKey f t Tip k x -> Tip k $! f k x Nil -> Nil +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] mapWithKey #-} +{-# RULES +"mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) = + mapWithKey (\k a -> f k (g k a)) xs +"mapWithKey/map" forall f g xs . mapWithKey f (map g xs) = + mapWithKey (\k a -> f k (g a)) xs +"map/mapWithKey" forall f g xs . map f (mapWithKey g xs) = + mapWithKey (\k a -> f (g k a)) xs + #-} +#endif + -- | /O(n)/. The function @'mapAccum'@ threads an accumulating -- argument through the map in ascending order of keys. -- diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 89b851e..3911125 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -1662,10 +1662,15 @@ mapEitherWithKey f0 t0 = toPair $ go f0 t0 map :: (a -> b) -> Map k a -> Map k b map _ Tip = Tip map f (Bin sx kx x l r) = Bin sx kx (f x) (map f l) (map f r) +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] map #-} +{-# RULES +"map/map" forall f g xs . map f (map g xs) = map (f . g) xs + #-} +#endif #if MIN_VERSION_base(4,8,0) -- Safe coercions were introduced in 4.7.0, but I am not sure if they played -- well enough with RULES to do what we want. -{-# NOINLINE [1] map #-} {-# RULES "map/coerce" map coerce = coerce #-} @@ -1680,6 +1685,18 @@ mapWithKey :: (k -> a -> b) -> Map k a -> Map k b mapWithKey _ Tip = Tip mapWithKey f (Bin sx kx x l r) = Bin sx kx (f kx x) (mapWithKey f l) (mapWithKey f r) +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] mapWithKey #-} +{-# RULES +"mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) = + mapWithKey (\k a -> f k (g k a)) xs +"mapWithKey/map" forall f g xs . mapWithKey f (map g xs) = + mapWithKey (\k a -> f k (g a)) xs +"map/mapWithKey" forall f g xs . map f (mapWithKey g xs) = + mapWithKey (\k a -> f (g k a)) xs + #-} +#endif + -- | /O(n)/. -- @'traverseWithKey' f s == 'fromList' <$> 'traverse' (\(k, v) -> (,) k <$> f k v) ('toList' m)@ -- That is, behaves exactly like a regular 'traverse' except that the traversing diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs index 8c7ea0f..6255e91 100644 --- a/Data/Map/Strict.hs +++ b/Data/Map/Strict.hs @@ -935,10 +935,15 @@ mapEitherWithKey f0 t0 = toPair $ go f0 t0 map :: (a -> b) -> Map k a -> Map k b map _ Tip = Tip map f (Bin sx kx x l r) = let x' = f x in x' `seq` Bin sx kx x' (map f l) (map f r) +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] map #-} +{-# RULES +"map/map" forall f g xs . map f (map g xs) = map (f . g) xs + #-} +#endif #if MIN_VERSION_base(4,8,0) -- Safe coercions were introduced in 4.7.0, but I am not sure if they played -- well enough with RULES to do what we want. -{-# NOINLINE [1] map #-} {-# RULES "mapSeq/coerce" map coerce = coerce #-} @@ -951,8 +956,21 @@ map f (Bin sx kx x l r) = let x' = f x in x' `seq` Bin sx kx x' (map f l) (map f mapWithKey :: (k -> a -> b) -> Map k a -> Map k b mapWithKey _ Tip = Tip -mapWithKey f (Bin sx kx x l r) = let x' = f kx x - in x' `seq` Bin sx kx x' (mapWithKey f l) (mapWithKey f r) +mapWithKey f (Bin sx kx x l r) = + let x' = f kx x + in x' `seq` Bin sx kx x' (mapWithKey f l) (mapWithKey f r) + +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] mapWithKey #-} +{-# RULES +"mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) = + mapWithKey (\k a -> f k (g k a)) xs +"mapWithKey/map" forall f g xs . mapWithKey f (map g xs) = + mapWithKey (\k a -> f k (g a)) xs +"map/mapWithKey" forall f g xs . map f (mapWithKey g xs) = + mapWithKey (\k a -> f (g k a)) xs + #-} +#endif -- | /O(n)/. The function 'mapAccum' threads an accumulating -- argument through the map in ascending order of keys. diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 1c4e143..fe59172 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -191,10 +191,15 @@ instance Functor Seq where fmapSeq :: (a -> b) -> Seq a -> Seq b fmapSeq f (Seq xs) = Seq (fmap (fmap f) xs) +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] fmapSeq #-} +{-# RULES +"fmapSeq/fmapSeq" forall f g xs . fmapSeq f (fmapSeq g xs) = fmapSeq (f . g) xs + #-} +#endif #if MIN_VERSION_base(4,8,0) -- Safe coercions were introduced in 4.7.0, but I am not sure if they played -- well enough with RULES to do what we want. -{-# NOINLINE [1] fmapSeq #-} {-# RULES "fmapSeq/coerce" fmapSeq coerce = coerce #-} @@ -1265,6 +1270,18 @@ adjustDigit f i (Four a b c d) mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b mapWithIndex f xs = snd (mapAccumL' (\ i x -> (i + 1, f i x)) 0 xs) +#ifdef __GLASGOW_HASKELL__ +{-# NOINLINE [1] mapWithIndex #-} +{-# RULES +"mapWithIndex/mapWithIndex" forall f g xs . mapWithIndex f (mapWithIndex g xs) = + mapWithIndex (\k a -> f k (g k a)) xs +"mapWithIndex/fmapSeq" forall f g xs . mapWithIndex f (fmapSeq g xs) = + mapWithIndex (\k a -> f k (g a)) xs +"fmapSeq/mapWithIndex" forall f g xs . fmapSeq f (mapWithIndex g xs) = + mapWithIndex (\k a -> f (g k a)) xs + #-} +#endif + -- Splitting -- | /O(log(min(i,n-i)))/. The first @i@ elements of a sequence. From git at git.haskell.org Fri Jan 23 22:41:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:16 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Use coerce for [a]->[Elem a] convertion in fromList. (9b37d5a) Message-ID: <20150123224116.5F64F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/9b37d5a262e8070abce1f51d4913d9312a630acd >--------------------------------------------------------------- commit 9b37d5a262e8070abce1f51d4913d9312a630acd Author: Milan Straka Date: Mon Dec 15 17:37:18 2014 +0100 Use coerce for [a]->[Elem a] convertion in fromList. >--------------------------------------------------------------- 9b37d5a262e8070abce1f51d4913d9312a630acd Data/Sequence.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 1b6dea2..71ded95 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1759,7 +1759,7 @@ findIndicesR p xs = foldlWithIndex g [] xs -- There is a function 'toList' in the opposite direction for all -- instances of the 'Foldable' class, including 'Seq'. fromList :: [a] -> Seq a -fromList xs = Seq $ mkTree 1 $ Data.List.map Elem xs +fromList xs = Seq $ mkTree 1 $ map_elem xs where {-# SPECIALIZE mkTree :: Int -> [Elem a] -> FingerTree (Elem a) #-} {-# SPECIALIZE mkTree :: Int -> [Node a] -> FingerTree (Node a) #-} @@ -1781,6 +1781,14 @@ fromList xs = Seq $ mkTree 1 $ Data.List.map Elem xs getNodes s (x1:x2:x3:xs) = s `seq` (Node3 s x1 x2 x3:ns, d) where (ns, d) = getNodes s xs + map_elem :: [a] -> [Elem a] +#if __GLASGOW_HASKELL__ >= 708 + map_elem xs = coerce xs +#else + map_elem xs = Data.List.map Elem xs +#endif + {-# INLINE map_elem #-} + #if __GLASGOW_HASKELL__ >= 708 instance GHC.Exts.IsList (Seq a) where type Item (Seq a) = a From git at git.haskell.org Fri Jan 23 22:41:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:18 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #69 from treeowl/fmapfmap (b2c1c79) Message-ID: <20150123224118.24AE03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/b2c1c79893c4b112d98f82dccb006b7453dc4f21 >--------------------------------------------------------------- commit b2c1c79893c4b112d98f82dccb006b7453dc4f21 Merge: e083f68 352c73d Author: Milan Straka Date: Tue Nov 18 16:44:20 2014 +0100 Merge pull request #69 from treeowl/fmapfmap Add fmap/fmap rules >--------------------------------------------------------------- b2c1c79893c4b112d98f82dccb006b7453dc4f21 Data/IntMap/Base.hs | 19 +++++++++++++++++++ Data/IntMap/Strict.hs | 19 +++++++++++++++++++ Data/Map/Base.hs | 19 ++++++++++++++++++- Data/Map/Strict.hs | 24 +++++++++++++++++++++--- Data/Sequence.hs | 19 ++++++++++++++++++- 5 files changed, 95 insertions(+), 5 deletions(-) From git at git.haskell.org Fri Jan 23 22:41:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:18 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Comment various conditional imports. (9df67f5) Message-ID: <20150123224118.66C3C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/9df67f5121ef14c865b4fae9db96aebf083dfb6c >--------------------------------------------------------------- commit 9df67f5121ef14c865b4fae9db96aebf083dfb6c Author: Milan Straka Date: Mon Dec 15 17:57:20 2014 +0100 Comment various conditional imports. >--------------------------------------------------------------- 9df67f5121ef14c865b4fae9db96aebf083dfb6c Data/Sequence.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 71ded95..2e8f84c 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -172,17 +172,22 @@ import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', t import Data.Traversable import Data.Typeable +-- GHC specific stuff #ifdef __GLASGOW_HASKELL__ import GHC.Exts (build) import Text.Read (Lexeme(Ident), lexP, parens, prec, readPrec, readListPrec, readListPrecDefault) import Data.Data #endif + +-- Coercion on GHC 7.8+ #if __GLASGOW_HASKELL__ >= 708 import Data.Coerce import qualified GHC.Exts #else #endif + +-- Identity functor on base 4.8 (GHC 7.10+) #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity(..)) #endif From git at git.haskell.org Fri Jan 23 22:41:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:20 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Implement map/coerce for IntMap (ee3eb5f) Message-ID: <20150123224120.2F31D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/ee3eb5f19dbbd193e7c8b991c861f8568c7106d9 >--------------------------------------------------------------- commit ee3eb5f19dbbd193e7c8b991c861f8568c7106d9 Author: David Feuer Date: Tue Nov 18 17:39:18 2014 -0500 Implement map/coerce for IntMap I realized what I was doing with MIN_VERSION was kind of silly. The easy/sane thing to do is really to use __GLASGOW_HASKELL__ for the coercion stuff. >--------------------------------------------------------------- ee3eb5f19dbbd193e7c8b991c861f8568c7106d9 Data/IntMap/Base.hs | 23 +++++++++++++++------- Data/IntMap/Strict.hs | 12 ++++++++--- tests-ghc/all.T | 2 ++ tests-ghc/{mapcoercemap.hs => mapcoerceintmap.hs} | 8 ++++---- ...{mapcoercemap.stdout => mapcoerceintmap.stdout} | 0 .../{mapcoercemap.hs => mapcoerceintmapstrict.hs} | 14 ++++++------- ...emap.stdout => mapcoerceintmapstrict.hs.stdout} | 0 7 files changed, 38 insertions(+), 21 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 3832e1c..d5fd75a 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -9,6 +9,13 @@ #if __GLASGOW_HASKELL__ >= 708 {-# LANGUAGE TypeFamilies #-} #endif +-- We use cabal-generated MIN_VERSION_base to adapt to changes of base. +-- Nevertheless, as a convenience, we also allow compiling without cabal by +-- defining trivial MIN_VERSION_base if needed. +#ifndef MIN_VERSION_base +#define MIN_VERSION_base(major1,major2,minor) 0 +#endif + ----------------------------------------------------------------------------- -- | -- Module : Data.IntMap.Base @@ -240,6 +247,9 @@ import qualified GHC.Exts as GHCExts #endif import Text.Read #endif +#if __GLASGOW_HASKELL__ >= 709 +import Data.Coerce +#endif -- Use macros to define strictness of functions. -- STRICT_x_OF_y denotes an y-ary function strict in the x-th parameter. @@ -247,13 +257,6 @@ import Text.Read -- want the compilers to be compiled by as many compilers as possible. #define STRICT_1_OF_2(fn) fn arg _ | arg `seq` False = undefined --- We use cabal-generated MIN_VERSION_base to adapt to changes of base. --- Nevertheless, as a convenience, we also allow compiling without cabal by --- defining trivial MIN_VERSION_base if needed. -#ifndef MIN_VERSION_base -#define MIN_VERSION_base(major1,major2,minor) 0 -#endif - -- A "Nat" is a natural machine word (an unsigned Int) type Nat = Word @@ -1307,6 +1310,12 @@ map f t "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} #endif +#if __GLASGOW_HASKELL__ >= 709 +-- Safe coercions were introduced in 7.8, but did not play well with RULES yet. +{-# RULES +"map/coerce" map coerce = coerce + #-} +#endif -- | /O(n)/. Map a function over all values in the map. -- diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs index af44b2a..d7f45f7 100644 --- a/Data/IntMap/Strict.hs +++ b/Data/IntMap/Strict.hs @@ -1,7 +1,5 @@ {-# LANGUAGE CPP #-} -#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 709 -{-# LANGUAGE Safe #-} -#elif !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 +#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- @@ -262,6 +260,9 @@ import qualified Data.IntSet.Base as IntSet import Data.Utils.BitUtil import Data.Utils.StrictFold import Data.Utils.StrictPair +#if __GLASGOW_HASKELL__ >= 709 +import Data.Coerce +#endif -- $strictness -- @@ -724,6 +725,11 @@ map f t "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} #endif +#if __GLASGOW_HASKELL__ >= 709 +{-# RULES +"map/coerce" map coerce = coerce + #-} +#endif -- | /O(n)/. Map a function over all values in the map. -- diff --git a/tests-ghc/all.T b/tests-ghc/all.T index 6a8a339..eba1dcc 100644 --- a/tests-ghc/all.T +++ b/tests-ghc/all.T @@ -8,3 +8,5 @@ test('sequence001', normal, compile_and_run, ['-package containers']) test('mapcoerceseq', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) test('mapcoercemap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) test('mapcoercesmap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) +test('mapcoerceintmap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) +test('mapcoerceintmapstrict', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) diff --git a/tests-ghc/mapcoercemap.hs b/tests-ghc/mapcoerceintmap.hs similarity index 76% copy from tests-ghc/mapcoercemap.hs copy to tests-ghc/mapcoerceintmap.hs index 6dd336d..ded48c7 100644 --- a/tests-ghc/mapcoercemap.hs +++ b/tests-ghc/mapcoerceintmap.hs @@ -2,15 +2,15 @@ import GHC.Exts hiding (fromList) import Unsafe.Coerce -import Data.Map +import Data.IntMap.Lazy newtype Age = Age Int -fooAge :: Map Int Int -> Map Int Age +fooAge :: IntMap Int -> IntMap Age fooAge = fmap Age -fooCoerce :: Map Int Int -> Map Int Age +fooCoerce :: IntMap Int -> IntMap Age fooCoerce = fmap coerce -fooUnsafeCoerce :: Map Int Int -> Map Int Age +fooUnsafeCoerce :: IntMap Int -> IntMap Age fooUnsafeCoerce = fmap unsafeCoerce same :: a -> b -> IO () diff --git a/tests-ghc/mapcoercemap.stdout b/tests-ghc/mapcoerceintmap.stdout similarity index 100% copy from tests-ghc/mapcoercemap.stdout copy to tests-ghc/mapcoerceintmap.stdout diff --git a/tests-ghc/mapcoercemap.hs b/tests-ghc/mapcoerceintmapstrict.hs similarity index 61% copy from tests-ghc/mapcoercemap.hs copy to tests-ghc/mapcoerceintmapstrict.hs index 6dd336d..2e97004 100644 --- a/tests-ghc/mapcoercemap.hs +++ b/tests-ghc/mapcoerceintmapstrict.hs @@ -2,16 +2,16 @@ import GHC.Exts hiding (fromList) import Unsafe.Coerce -import Data.Map +import Data.IntMap.Strict as IM newtype Age = Age Int -fooAge :: Map Int Int -> Map Int Age -fooAge = fmap Age -fooCoerce :: Map Int Int -> Map Int Age -fooCoerce = fmap coerce -fooUnsafeCoerce :: Map Int Int -> Map Int Age -fooUnsafeCoerce = fmap unsafeCoerce +fooAge :: IntMap Int -> IntMap Age +fooAge = IM.map Age +fooCoerce :: IntMap Int -> IntMap Age +fooCoerce = IM.map coerce +fooUnsafeCoerce :: IntMap Int -> IntMap Age +fooUnsafeCoerce = IM.map unsafeCoerce same :: a -> b -> IO () same x y = case reallyUnsafePtrEquality# (unsafeCoerce x) y of diff --git a/tests-ghc/mapcoercemap.stdout b/tests-ghc/mapcoerceintmapstrict.hs.stdout similarity index 100% copy from tests-ghc/mapcoercemap.stdout copy to tests-ghc/mapcoerceintmapstrict.hs.stdout From git at git.haskell.org Fri Jan 23 22:41:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:20 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Add Data.Sequence.fromArray. (52ba9e5) Message-ID: <20150123224120.726B23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/52ba9e5d9c85d4bd11236c1e43b4847a50a3b771 >--------------------------------------------------------------- commit 52ba9e5d9c85d4bd11236c1e43b4847a50a3b771 Author: Milan Straka Date: Mon Dec 15 17:58:46 2014 +0100 Add Data.Sequence.fromArray. Sugested by David Feuer in #88. The implementation on GHC uses GHC.Arr module and is considerably faster than on non-GHC compilers. >--------------------------------------------------------------- 52ba9e5d9c85d4bd11236c1e43b4847a50a3b771 Data/Sequence.hs | 19 +++++++++++++++++++ tests/seq-properties.hs | 6 ++++++ 2 files changed, 25 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 2e8f84c..690a9fe 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -62,6 +62,7 @@ module Data.Sequence ( (><), -- :: Seq a -> Seq a -> Seq a fromList, -- :: [a] -> Seq a fromFunction, -- :: Int -> (Int -> a) -> Seq a + fromArray, -- :: Ix i => Array i a -> Seq a -- ** Repetition replicate, -- :: Int -> a -> Seq a replicateA, -- :: Applicative f => Int -> f a -> f (Seq a) @@ -180,6 +181,13 @@ import Text.Read (Lexeme(Ident), lexP, parens, prec, import Data.Data #endif +-- Array stuff, with GHC.Arr on GHC +import Data.Array (Ix, Array) +import qualified Data.Array +#ifdef __GLASGOW_HASKELL__ +import qualified GHC.Arr +#endif + -- Coercion on GHC 7.8+ #if __GLASGOW_HASKELL__ >= 708 import Data.Coerce @@ -1399,6 +1407,17 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg #endif {-# INLINE lift_elem #-} +-- | /O(n)/. Create a sequence consisting of the elements of an 'Array'. +-- Note that the resulting sequence elements may be evaluated lazily (as on GHC), +-- so you must force the entire structure to be sure that the original array +-- can be garbage-collected. +fromArray :: Ix i => Array i a -> Seq a +#ifdef __GLASGOW_HASKELL__ +fromArray a = fromFunction (GHC.Arr.numElements a) (GHC.Arr.unsafeAt a) +#else +fromArray a = fromList2 (Data.Array.rangeSize (Data.Array.bounds a)) (Data.Array.elems a) +#endif + -- Splitting -- | /O(log(min(i,n-i)))/. The first @i@ elements of a sequence. diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index 14d5a5f..a64e66d 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -2,6 +2,7 @@ import Data.Sequence -- needs to be compiled with -DTESTING for use here import Control.Applicative (Applicative(..)) import Control.Arrow ((***)) +import Data.Array (listArray) import Data.Foldable (Foldable(..), toList, all, sum) import Data.Functor ((<$>), (<$)) import Data.Maybe @@ -37,6 +38,7 @@ main = defaultMain , testProperty "(><)" prop_append , testProperty "fromList" prop_fromList , testProperty "fromFunction" prop_fromFunction + , testProperty "fromArray" prop_fromArray , testProperty "replicate" prop_replicate , testProperty "replicateA" prop_replicateA , testProperty "replicateM" prop_replicateM @@ -275,6 +277,10 @@ prop_fromFunction :: [A] -> Bool prop_fromFunction xs = toList' (fromFunction (Prelude.length xs) (xs!!)) ~= xs +prop_fromArray :: [A] -> Bool +prop_fromArray xs = + toList' (fromArray (listArray (42, 42+Prelude.length xs-1) xs)) ~= xs + -- ** Repetition prop_replicate :: NonNegative Int -> A -> Bool From git at git.haskell.org Fri Jan 23 22:41:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:22 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Optimize *> and >> for Seq (22ef7de) Message-ID: <20150123224122.38C263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/22ef7de71a5de7f9447f3fdcf16fa8f786cb84c0 >--------------------------------------------------------------- commit 22ef7de71a5de7f9447f3fdcf16fa8f786cb84c0 Author: David Feuer Date: Wed Nov 19 15:14:01 2014 -0500 Optimize *> and >> for Seq Based on a discussion with Ross Paterson, use a multiplication- by-doubling algorithm to improve asymptotic time and space performance. >--------------------------------------------------------------- 22ef7de71a5de7f9447f3fdcf16fa8f786cb84c0 Data/Sequence.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 1c4e143..2cfa9c7 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -228,11 +228,13 @@ instance Monad Seq where return = singleton xs >>= f = foldl' add empty xs where add ys x = ys >< f x + (>>) = (*>) instance Applicative Seq where pure = singleton fs <*> xs = foldl' add empty fs where add ys f = ys >< fmap f xs + xs *> ys = replicateSeq (length xs) ys instance MonadPlus Seq where mzero = empty @@ -655,6 +657,19 @@ replicateM n x | n >= 0 = unwrapMonad (replicateA n (WrapMonad x)) | otherwise = error "replicateM takes a nonnegative integer argument" +-- | @'replicateSeq' n xs@ concatenates @n@ copies of @xs at . +replicateSeq :: Int -> Seq a -> Seq a +replicateSeq n xs + | n < 0 = error "replicateSeq takes a nonnegative integer argument" + | n == 0 = empty + | otherwise = go n xs + where + -- Invariant: k >= 1 + go 1 xs = xs + go k xs | even k = kxs + | otherwise = xs >< kxs + where kxs = go (k `quot` 2) $! (xs >< xs) + -- | /O(1)/. Add an element to the left end of a sequence. -- Mnemonic: a triangle with the single element at the pointy end. (<|) :: a -> Seq a -> Seq a From git at git.haskell.org Fri Jan 23 22:41:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:22 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6: Make types of the drawing functions more generic, i.e. Show s => Tree s instead of Tree String (7ab1c39) Message-ID: <20150123224122.78DBD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop-0.6 Link : http://git.haskell.org/packages/containers.git/commitdiff/7ab1c399726c5a4a562cff3f56017ff5852ac82e >--------------------------------------------------------------- commit 7ab1c399726c5a4a562cff3f56017ff5852ac82e Author: jonasc Date: Fri Aug 8 00:15:10 2014 +0200 Make types of the drawing functions more generic, i.e. Show s => Tree s instead of Tree String >--------------------------------------------------------------- 7ab1c399726c5a4a562cff3f56017ff5852ac82e Data/Tree.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/Data/Tree.hs b/Data/Tree.hs index 57a4324..1642c3b 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -113,15 +113,15 @@ instance NFData a => NFData (Tree a) where rnf (Node x ts) = rnf x `seq` rnf ts -- | Neat 2-dimensional drawing of a tree. -drawTree :: Tree String -> String +drawTree :: Show a => Tree a -> String drawTree = unlines . draw -- | Neat 2-dimensional drawing of a forest. -drawForest :: Forest String -> String +drawForest :: Show a => Forest a -> String drawForest = unlines . map drawTree -draw :: Tree String -> [String] -draw (Node x ts0) = x : drawSubTrees ts0 +draw :: Show a => Tree a -> [String] +draw (Node x ts0) = show x : drawSubTrees ts0 where drawSubTrees [] = [] drawSubTrees [t] = From git at git.haskell.org Fri Jan 23 22:41:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:24 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #71 from treeowl/fmapcoerceintmap (bcebc7a) Message-ID: <20150123224124.409333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/bcebc7af8d347d6229836847cd09ce6971dd6db4 >--------------------------------------------------------------- commit bcebc7af8d347d6229836847cd09ce6971dd6db4 Merge: b2c1c79 ee3eb5f Author: Milan Straka Date: Fri Nov 21 07:56:17 2014 +0100 Merge pull request #71 from treeowl/fmapcoerceintmap Implement map/coerce for IntMap >--------------------------------------------------------------- bcebc7af8d347d6229836847cd09ce6971dd6db4 Data/IntMap/Base.hs | 23 +++++++++++++++------- Data/IntMap/Strict.hs | 12 ++++++++--- tests-ghc/all.T | 2 ++ tests-ghc/{mapcoercemap.hs => mapcoerceintmap.hs} | 8 ++++---- ...{mapcoercemap.stdout => mapcoerceintmap.stdout} | 0 .../{mapcoercemap.hs => mapcoerceintmapstrict.hs} | 14 ++++++------- ...emap.stdout => mapcoerceintmapstrict.hs.stdout} | 0 7 files changed, 38 insertions(+), 21 deletions(-) From git at git.haskell.org Fri Jan 23 22:41:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:24 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6-questionable: Added fixity declarations for member, notMember, union, and intersection. (de85ae9) Message-ID: <20150123224124.858A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop-0.6-questionable Link : http://git.haskell.org/packages/containers.git/commitdiff/de85ae9eccb84284873d419c899743a85bd4e66a >--------------------------------------------------------------- commit de85ae9eccb84284873d419c899743a85bd4e66a Author: Peter Selinger Date: Fri Jul 4 10:31:20 2014 -0300 Added fixity declarations for member, notMember, union, and intersection. Milan Straka: It is quite unlikely that this ever gets merged, as it can cause build failures (it broke the testing suite for example) and offers in my opinion little benefit. >--------------------------------------------------------------- de85ae9eccb84284873d419c899743a85bd4e66a Data/IntMap/Base.hs | 8 ++++++++ Data/IntSet/Base.hs | 7 +++++++ Data/Map/Base.hs | 8 ++++++++ Data/Set/Base.hs | 8 ++++++++ 4 files changed, 31 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index d5fd75a..2a912d9 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -451,6 +451,8 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the key not a member of the map? -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -459,6 +461,8 @@ member k = k `seq` go notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m +infix 4 notMember + -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. -- See Note: Local 'go' functions and capturing] @@ -874,6 +878,8 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 +infixl 5 union + -- | /O(n+m)/. The union with a combining function. -- -- > unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")] @@ -937,6 +943,8 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 +infixl 5 intersection + -- | /O(n+m)/. The intersection with a combining function. -- -- > intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA" diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 6333eea..f2dfb90 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -321,10 +321,14 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -512,6 +516,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t +infixl 5 union {-------------------------------------------------------------------- Difference @@ -586,6 +591,8 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil +infixl 5 intersection + {-------------------------------------------------------------------- Subset --------------------------------------------------------------------} diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index e582e16..92ff096 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -466,6 +466,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -479,6 +481,8 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. find :: Ord k => k -> Map k a -> a @@ -1241,6 +1245,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b hedgeUnion _ _ t1 Tip = t1 @@ -1361,6 +1367,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 7e792f4..0c4f62b 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -356,6 +356,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool notMember a t = not $ member a t @@ -365,6 +367,8 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -616,6 +620,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 hedgeUnion blo bhi Tip (Bin _ x l r) = link x (filterGt blo l) (filterLt bhi r) @@ -674,6 +680,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip From git at git.haskell.org Fri Jan 23 22:41:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:26 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #72 from treeowl/then (dde7a53) Message-ID: <20150123224126.495253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/dde7a531b506096ae32b358c2dc83f3edac91ec2 >--------------------------------------------------------------- commit dde7a531b506096ae32b358c2dc83f3edac91ec2 Merge: bcebc7a 22ef7de Author: Milan Straka Date: Fri Nov 21 08:06:03 2014 +0100 Merge pull request #72 from treeowl/then Optimize *> and >> for Seq >--------------------------------------------------------------- dde7a531b506096ae32b358c2dc83f3edac91ec2 Data/Sequence.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) From git at git.haskell.org Fri Jan 23 22:41:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:26 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6-questionable: Fixed syntax of fixity declarations. (2bf686d) Message-ID: <20150123224126.90D113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop-0.6-questionable Link : http://git.haskell.org/packages/containers.git/commitdiff/2bf686d3dd0706eef416590100f8d1ebaa3eb80b >--------------------------------------------------------------- commit 2bf686d3dd0706eef416590100f8d1ebaa3eb80b Author: Peter Selinger Date: Fri Jul 4 10:47:35 2014 -0300 Fixed syntax of fixity declarations. >--------------------------------------------------------------- 2bf686d3dd0706eef416590100f8d1ebaa3eb80b Data/IntMap/Base.hs | 8 ++++---- Data/IntSet/Base.hs | 8 ++++---- Data/Map/Base.hs | 8 ++++---- Data/Set/Base.hs | 8 ++++---- 4 files changed, 16 insertions(+), 16 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 2a912d9..8afb60c 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -451,7 +451,7 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the key not a member of the map? -- @@ -461,7 +461,7 @@ infix 4 member notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 notMember +infix 4 `notMember` -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. @@ -878,7 +878,7 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 union +infixl 5 `union` -- | /O(n+m)/. The union with a combining function. -- @@ -943,7 +943,7 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 intersection +infixl 5 `intersection` -- | /O(n+m)/. The intersection with a combining function. -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index f2dfb90..bd78790 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -321,13 +321,13 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -516,7 +516,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 union +infixl 5 `union` {-------------------------------------------------------------------- Difference @@ -591,7 +591,7 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 intersection +infixl 5 `intersection` {-------------------------------------------------------------------- Subset diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 92ff096..ae291c7 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -466,7 +466,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- @@ -481,7 +481,7 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. @@ -1245,7 +1245,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b @@ -1367,7 +1367,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 0c4f62b..732e973 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -356,7 +356,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool @@ -367,7 +367,7 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -620,7 +620,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 @@ -680,7 +680,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip From git at git.haskell.org Fri Jan 23 22:41:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:28 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Use GHC version for coercion rules (8da46db) Message-ID: <20150123224128.536483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/8da46dbc4598062397c6a6b684f7bae9931f3d80 >--------------------------------------------------------------- commit 8da46dbc4598062397c6a6b684f7bae9931f3d80 Author: David Feuer Date: Fri Nov 21 10:14:38 2014 -0500 Use GHC version for coercion rules Using the library version didn't make much sense, especially since the tests-ghc tests had to switch on compiler version anyway, but also because compiling without cabal would prevent the code from being used. The conditional fake MIN_VERSION_base definition should probably stay up top where I moved it, though, in case someone needs to use it to adjust imports or exports in the future--the top seems an inherently better place for that. >--------------------------------------------------------------- 8da46dbc4598062397c6a6b684f7bae9931f3d80 Data/Map/Base.hs | 7 +++---- Data/Map/Strict.hs | 7 +++---- Data/Sequence.hs | 7 +++---- 3 files changed, 9 insertions(+), 12 deletions(-) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 3911125..e582e16 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -294,7 +294,7 @@ import qualified GHC.Exts as GHCExts import Text.Read import Data.Data #endif -#if MIN_VERSION_base(4,8,0) +#if __GLASGOW_HASKELL__ >= 709 import Data.Coerce #endif @@ -1668,9 +1668,8 @@ map f (Bin sx kx x l r) = Bin sx kx (f x) (map f l) (map f r) "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} #endif -#if MIN_VERSION_base(4,8,0) --- Safe coercions were introduced in 4.7.0, but I am not sure if they played --- well enough with RULES to do what we want. +#if __GLASGOW_HASKELL__ >= 709 +-- Safe coercions were introduced in 7.8, but did not work well with RULES yet. {-# RULES "map/coerce" map coerce = coerce #-} diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs index 6255e91..88f494e 100644 --- a/Data/Map/Strict.hs +++ b/Data/Map/Strict.hs @@ -279,7 +279,7 @@ import Data.Utils.StrictFold import Data.Utils.StrictPair import Data.Bits (shiftL, shiftR) -#if MIN_VERSION_base(4,8,0) +#if __GLASGOW_HASKELL__ >= 709 import Data.Coerce #endif @@ -941,9 +941,8 @@ map f (Bin sx kx x l r) = let x' = f x in x' `seq` Bin sx kx x' (map f l) (map f "map/map" forall f g xs . map f (map g xs) = map (f . g) xs #-} #endif -#if MIN_VERSION_base(4,8,0) --- Safe coercions were introduced in 4.7.0, but I am not sure if they played --- well enough with RULES to do what we want. +#if __GLASGOW_HASKELL__ >= 709 +-- Safe coercions were introduced in 7.8, but did not work well with RULES yet. {-# RULES "mapSeq/coerce" map coerce = coerce #-} diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 331ac30..4799056 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -165,7 +165,7 @@ import Text.Read (Lexeme(Ident), lexP, parens, prec, readPrec, readListPrec, readListPrecDefault) import Data.Data #endif -#if MIN_VERSION_base(4,8,0) +#if __GLASGOW_HASKELL__ >= 709 import Data.Coerce #endif @@ -197,9 +197,8 @@ fmapSeq f (Seq xs) = Seq (fmap (fmap f) xs) "fmapSeq/fmapSeq" forall f g xs . fmapSeq f (fmapSeq g xs) = fmapSeq (f . g) xs #-} #endif -#if MIN_VERSION_base(4,8,0) --- Safe coercions were introduced in 4.7.0, but I am not sure if they played --- well enough with RULES to do what we want. +#if __GLASGOW_HASKELL__ >= 709 +-- Safe coercions were introduced in 7.8, but did not work well with RULES yet. {-# RULES "fmapSeq/coerce" fmapSeq coerce = coerce #-} From git at git.haskell.org Fri Jan 23 22:41:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:28 +0000 (UTC) Subject: [commit: packages/containers] master: Bump version number to 0.5.6.0 (b9e4e22) Message-ID: <20150123224128.98D243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/b9e4e22d6e37150dcf5c04e4c4beabfba5342576 >--------------------------------------------------------------- commit b9e4e22d6e37150dcf5c04e4c4beabfba5342576 Author: Johan Tibell Date: Mon Dec 15 19:57:52 2014 +0100 Bump version number to 0.5.6.0 >--------------------------------------------------------------- b9e4e22d6e37150dcf5c04e4c4beabfba5342576 containers.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/containers.cabal b/containers.cabal index ae7e247..bbf5913 100644 --- a/containers.cabal +++ b/containers.cabal @@ -1,5 +1,5 @@ name: containers -version: 0.5.5.1 +version: 0.5.6.0 license: BSD3 license-file: LICENSE maintainer: fox at ucw.cz From git at git.haskell.org Fri Jan 23 22:41:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:30 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #75 from treeowl/coerce-version (ddf12fd) Message-ID: <20150123224130.5C0553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/ddf12fd51a0611cba8250bdbde9fdcbb66211b1d >--------------------------------------------------------------- commit ddf12fd51a0611cba8250bdbde9fdcbb66211b1d Merge: dde7a53 8da46db Author: Milan Straka Date: Fri Nov 21 18:50:11 2014 +0100 Merge pull request #75 from treeowl/coerce-version Use GHC version for coercion rules >--------------------------------------------------------------- ddf12fd51a0611cba8250bdbde9fdcbb66211b1d Data/Map/Base.hs | 7 +++---- Data/Map/Strict.hs | 7 +++---- Data/Sequence.hs | 7 +++---- 3 files changed, 9 insertions(+), 12 deletions(-) From git at git.haskell.org Fri Jan 23 22:41:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:30 +0000 (UTC) Subject: [commit: packages/containers] master: Add Ross Paterson to 2014 copyright statement (302d6b4) Message-ID: <20150123224130.A01C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/302d6b4839702ce6e18fd1908240b920efb1b04a >--------------------------------------------------------------- commit 302d6b4839702ce6e18fd1908240b920efb1b04a Author: David Feuer Date: Mon Dec 15 15:54:22 2014 -0500 Add Ross Paterson to 2014 copyright statement He wrote the first draft of the new `fromList` code. >--------------------------------------------------------------- 302d6b4839702ce6e18fd1908240b920efb1b04a Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 690a9fe..9a23f77 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -19,7 +19,7 @@ -- Module : Data.Sequence -- Copyright : (c) Ross Paterson 2005 -- (c) Louis Wasserman 2009 --- (c) David Feuer and Milan Straka 2014 +-- (c) David Feuer, Ross Paterson, and Milan Straka 2014 -- License : BSD-style -- Maintainer : libraries at haskell.org -- Stability : experimental From git at git.haskell.org Fri Jan 23 22:41:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:32 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Use Data.Functor.Identity (bd7b470) Message-ID: <20150123224132.644413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/bd7b470abda94c486c784fd7d6c69dd91e0ae2be >--------------------------------------------------------------- commit bd7b470abda94c486c784fd7d6c69dd91e0ae2be Author: David Feuer Date: Fri Nov 21 11:25:58 2014 -0500 Use Data.Functor.Identity This has just entered base, and includes some optimizations that may or may not be relevant. For older versions, don't bother making Identity a Monad instance--it's not exported, and that instance is never used. Make applicativeTree slightly more readable. >--------------------------------------------------------------- bd7b470abda94c486c784fd7d6c69dd91e0ae2be Data/Sequence.hs | 40 ++++++++++++++++++++-------------------- 1 file changed, 20 insertions(+), 20 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 4799056..4e37dbf 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -168,6 +168,9 @@ import Data.Data #if __GLASGOW_HASKELL__ >= 709 import Data.Coerce #endif +#if MIN_VERSION_base(4,8,0) +import Data.Functor.Identity (Identity(..)) +#endif infixr 5 `consTree` @@ -554,19 +557,16 @@ instance NFData a => NFData (Elem a) where ------------------------------------------------------- -- Applicative construction ------------------------------------------------------- +#if !MIN_VERSION_base(4,8,0) +newtype Identity a = Identity {runIdentity :: a} -newtype Id a = Id {runId :: a} - -instance Functor Id where - fmap f (Id x) = Id (f x) - -instance Monad Id where - return = Id - m >>= k = k (runId m) +instance Functor Identity where + fmap f (Identity x) = Identity (f x) -instance Applicative Id where - pure = return - (<*>) = ap +instance Applicative Identity where + pure = Identity + Identity f <*> Identity x = Identity (f x) +#endif -- | This is essentially a clone of Control.Monad.State.Strict. newtype State s a = State {runState :: s -> (s, a)} @@ -598,13 +598,13 @@ mapAccumL' f s t = runState (traverse (State . flip f) t) s -- specified. This is a generalization of 'replicateA', which itself -- is a generalization of many Data.Sequence methods. {-# SPECIALIZE applicativeTree :: Int -> Int -> State s a -> State s (FingerTree a) #-} -{-# SPECIALIZE applicativeTree :: Int -> Int -> Id a -> Id (FingerTree a) #-} --- Special note: the Id specialization automatically does node sharing, +{-# SPECIALIZE applicativeTree :: Int -> Int -> Identity a -> Identity (FingerTree a) #-} +-- Special note: the Identity specialization automatically does node sharing, -- reducing memory usage of the resulting tree to /O(log n)/. applicativeTree :: Applicative f => Int -> Int -> f a -> f (FingerTree a) applicativeTree n mSize m = mSize `seq` case n of 0 -> pure Empty - 1 -> liftA Single m + 1 -> fmap Single m 2 -> deepA one emptyTree one 3 -> deepA two emptyTree one 4 -> deepA two emptyTree two @@ -612,12 +612,12 @@ applicativeTree n mSize m = mSize `seq` case n of 6 -> deepA three emptyTree three 7 -> deepA four emptyTree three 8 -> deepA four emptyTree four - _ -> let (q, r) = n `quotRem` 3 in q `seq` case r of - 0 -> deepA three (applicativeTree (q - 2) mSize' n3) three - 1 -> deepA four (applicativeTree (q - 2) mSize' n3) three - _ -> deepA four (applicativeTree (q - 2) mSize' n3) four + _ -> case n `quotRem` 3 of + (q,0) -> deepA three (applicativeTree (q - 2) mSize' n3) three + (q,1) -> deepA four (applicativeTree (q - 2) mSize' n3) three + (q,_) -> deepA four (applicativeTree (q - 2) mSize' n3) four where - one = liftA One m + one = fmap One m two = liftA2 Two m m three = liftA3 Three m m m four = liftA3 Four m m m <*> m @@ -641,7 +641,7 @@ singleton x = Seq (Single (Elem x)) -- | /O(log n)/. @replicate n x@ is a sequence consisting of @n@ copies of @x at . replicate :: Int -> a -> Seq a replicate n x - | n >= 0 = runId (replicateA n (Id x)) + | n >= 0 = runIdentity (replicateA n (Identity x)) | otherwise = error "replicate takes a nonnegative integer argument" -- | 'replicateA' is an 'Applicative' version of 'replicate', and makes From git at git.haskell.org Fri Jan 23 22:41:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:32 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #97 from treeowl/add-credit (33e65be) Message-ID: <20150123224132.A7FF33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/33e65bea1713e1720857fb1c1f982631b872913f >--------------------------------------------------------------- commit 33e65bea1713e1720857fb1c1f982631b872913f Merge: b9e4e22 302d6b4 Author: Milan Straka Date: Mon Dec 15 22:01:23 2014 +0100 Merge pull request #97 from treeowl/add-credit Add Ross Paterson to 2014 copyright statement >--------------------------------------------------------------- 33e65bea1713e1720857fb1c1f982631b872913f Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:41:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:34 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #76 from treeowl/identity (c138008) Message-ID: <20150123224134.6BBAD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c1380089319e24ce1373b6cd0a027f7447b45d32 >--------------------------------------------------------------- commit c1380089319e24ce1373b6cd0a027f7447b45d32 Merge: ddf12fd bd7b470 Author: Milan Straka Date: Fri Nov 21 19:56:10 2014 +0100 Merge pull request #76 from treeowl/identity Use Data.Functor.Identity >--------------------------------------------------------------- c1380089319e24ce1373b6cd0a027f7447b45d32 Data/Sequence.hs | 40 ++++++++++++++++++++-------------------- 1 file changed, 20 insertions(+), 20 deletions(-) From git at git.haskell.org Fri Jan 23 22:41:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:34 +0000 (UTC) Subject: [commit: packages/containers] master: Fix warnings. (2bdc5f3) Message-ID: <20150123224134.AFC753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/2bdc5f38f740f43b49bad0a53c81b9d4a25a56bd >--------------------------------------------------------------- commit 2bdc5f38f740f43b49bad0a53c81b9d4a25a56bd Author: Milan Straka Date: Mon Dec 15 22:47:28 2014 +0100 Fix warnings. In getNodes, pass (a, [a]) instead of an [a] which we know is nonempty. This way we do not have to create void pattern-match case for empty list. Also use STRICT_x_OF_y macros instead of `seq`-ing in every pattern-match case. >--------------------------------------------------------------- 2bdc5f38f740f43b49bad0a53c81b9d4a25a56bd Data/Sequence.hs | 40 ++++++++++++++++++++++++---------------- 1 file changed, 24 insertions(+), 16 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 9a23f77..1f19c62 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -183,7 +183,6 @@ import Data.Data -- Array stuff, with GHC.Arr on GHC import Data.Array (Ix, Array) -import qualified Data.Array #ifdef __GLASGOW_HASKELL__ import qualified GHC.Arr #endif @@ -200,6 +199,15 @@ import qualified GHC.Exts import Data.Functor.Identity (Identity(..)) #endif + +-- Use macros to define strictness of functions. +-- STRICT_x_OF_y denotes an y-ary function strict in the x-th parameter. +-- We do not use BangPatterns, because they are not in any standard and we +-- want the compilers to be compiled by as many compilers as possible. +#define STRICT_1_OF_2(fn) fn arg _ | arg `seq` False = undefined +#define STRICT_1_OF_3(fn) fn arg _ _ | arg `seq` False = undefined + + infixr 5 `consTree` infixl 5 `snocTree` @@ -1783,27 +1791,27 @@ findIndicesR p xs = foldlWithIndex g [] xs -- There is a function 'toList' in the opposite direction for all -- instances of the 'Foldable' class, including 'Seq'. fromList :: [a] -> Seq a -fromList xs = Seq $ mkTree 1 $ map_elem xs +fromList = Seq . mkTree 1 . map_elem where {-# SPECIALIZE mkTree :: Int -> [Elem a] -> FingerTree (Elem a) #-} {-# SPECIALIZE mkTree :: Int -> [Node a] -> FingerTree (Node a) #-} mkTree :: (Sized a) => Int -> [a] -> FingerTree a - mkTree s [] = s `seq` Empty - mkTree s [x1] = s `seq` Single x1 + STRICT_1_OF_2(mkTree) + mkTree _ [] = Empty + mkTree _ [x1] = Single x1 mkTree s [x1, x2] = Deep (2*s) (One x1) Empty (One x2) mkTree s [x1, x2, x3] = Deep (3*s) (One x1) Empty (Two x2 x3) - mkTree s (x1:x2:x3:xs) = s `seq` case getNodes (3*s) xs of - (ns, sf) -> m `seq` deep' (Three x1 x2 x3) m sf - where m = mkTree (3*s) ns - - deep' pr@(Three x1 _ _) m sf = Deep (3*size x1 + size m + size sf) pr m sf - - getNodes :: Int -> [a] -> ([Node a], Digit a) - getNodes s [x1] = s `seq` ([], One x1) - getNodes s [x1, x2] = s `seq` ([], Two x1 x2) - getNodes s [x1, x2, x3] = s `seq` ([], Three x1 x2 x3) - getNodes s (x1:x2:x3:xs) = s `seq` (Node3 s x1 x2 x3:ns, d) - where (ns, d) = getNodes s xs + mkTree s (x1:x2:x3:x4:xs) = case getNodes (3*s) x4 xs of + (ns, sf) -> case mkTree (3*s) ns of + m -> m `seq` Deep (3*size x1 + size m + size sf) (Three x1 x2 x3) m sf + + getNodes :: Int -> a -> [a] -> ([Node a], Digit a) + STRICT_1_OF_3(getNodes) + getNodes _ x1 [] = ([], One x1) + getNodes _ x1 [x2] = ([], Two x1 x2) + getNodes _ x1 [x2, x3] = ([], Three x1 x2 x3) + getNodes s x1 (x2:x3:x4:xs) = (Node3 s x1 x2 x3:ns, d) + where (ns, d) = getNodes s x4 xs map_elem :: [a] -> [Elem a] #if __GLASGOW_HASKELL__ >= 708 From git at git.haskell.org Fri Jan 23 22:41:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:36 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Make index middle-lazy (aedfe3f) Message-ID: <20150123224136.73AAD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/aedfe3f327f781484ec6fb4718156919791c4979 >--------------------------------------------------------------- commit aedfe3f327f781484ec6fb4718156919791c4979 Author: David Feuer Date: Sun Nov 23 15:36:39 2014 -0500 Make index middle-lazy `index` should not descend the finger tree spine unless it needs to. >--------------------------------------------------------------- aedfe3f327f781484ec6fb4718156919791c4979 Data/Sequence.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 4e37dbf..511cad9 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1159,14 +1159,14 @@ data Place a = Place {-# UNPACK #-} !Int a lookupTree :: Sized a => Int -> FingerTree a -> Place a lookupTree _ Empty = error "lookupTree of empty tree" lookupTree i (Single x) = Place i x -lookupTree i (Deep _ pr m sf) +lookupTree i (Deep totalSize pr m sf) | i < spr = lookupDigit i pr | i < spm = case lookupTree (i - spr) m of Place i' xs -> lookupNode i' xs | otherwise = lookupDigit (i - spm) sf where spr = size pr - spm = spr + size m + spm = totalSize - size sf {-# SPECIALIZE lookupNode :: Int -> Node (Elem a) -> Place (Elem a) #-} {-# SPECIALIZE lookupNode :: Int -> Node (Node a) -> Place (Node a) #-} From git at git.haskell.org Fri Jan 23 22:41:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:36 +0000 (UTC) Subject: [commit: packages/containers] master: Nuke include/Typeable.h, create include/containers.h instead. (b3257c8) Message-ID: <20150123224136.C63293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/b3257c8b59a9f4dec03be19b6d2cd7a562691e04 >--------------------------------------------------------------- commit b3257c8b59a9f4dec03be19b6d2cd7a562691e04 Author: Milan Straka Date: Mon Dec 15 23:48:18 2014 +0100 Nuke include/Typeable.h, create include/containers.h instead. The "Typeable.h" collides with the header of same name in base. The new "containers.h" is now used in every Haskell source. It contains more stuff used across the containers codebase: - INSTANCE_TYPEABLE[0-2] (was in Typeable.h) - include MachDeps on __GLASGOW_HASKELL__ to define WORD_SIZE_IN_BITS - define STRICT_x_OF_y macros - define MIN_VERSION_base if not defined by cabal (during cabal-less build) >--------------------------------------------------------------- b3257c8b59a9f4dec03be19b6d2cd7a562691e04 Data/Graph.hs | 3 +++ Data/IntMap.hs | 3 +++ Data/IntMap/Base.hs | 15 ++--------- Data/IntMap/Lazy.hs | 3 +++ Data/IntMap/Strict.hs | 3 +++ Data/IntSet.hs | 3 +++ Data/IntSet/Base.hs | 25 +++---------------- Data/Map.hs | 3 +++ Data/Map/Base.hs | 20 +++------------ Data/Map/Lazy.hs | 3 +++ Data/Map/Strict.hs | 23 ++++------------- Data/Sequence.hs | 18 +++----------- Data/Set.hs | 3 +++ Data/Set/Base.hs | 19 +++----------- Data/Tree.hs | 9 ++----- Data/Utils/BitUtil.hs | 8 +++--- Data/Utils/StrictFold.hs | 3 +++ Data/Utils/StrictPair.hs | 3 +++ containers.cabal | 2 +- include/Typeable.h | 65 ------------------------------------------------ include/containers.h | 61 +++++++++++++++++++++++++++++++++++++++++++++ 21 files changed, 116 insertions(+), 179 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b3257c8b59a9f4dec03be19b6d2cd7a562691e04 From git at git.haskell.org Fri Jan 23 22:41:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:38 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #80 from treeowl/fix-index (e1e75b8) Message-ID: <20150123224138.7B5673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/e1e75b83e3f4bd4bf4031d01d3cec56428c2be33 >--------------------------------------------------------------- commit e1e75b83e3f4bd4bf4031d01d3cec56428c2be33 Merge: c138008 aedfe3f Author: Milan Straka Date: Sun Nov 23 23:05:14 2014 +0100 Merge pull request #80 from treeowl/fix-index Make index middle-lazy >--------------------------------------------------------------- e1e75b83e3f4bd4bf4031d01d3cec56428c2be33 Data/Sequence.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Jan 23 22:41:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:38 +0000 (UTC) Subject: [commit: packages/containers] master: Add the include dir also to tests. (040309f) Message-ID: <20150123224138.CC5BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/040309f6915306cc7aa7da02f144fe026e4fb6fe >--------------------------------------------------------------- commit 040309f6915306cc7aa7da02f144fe026e4fb6fe Author: Milan Straka Date: Tue Dec 16 00:24:50 2014 +0100 Add the include dir also to tests. This worked with Typeable because Typeable from `base` instead of `containers` was used. >--------------------------------------------------------------- 040309f6915306cc7aa7da02f144fe026e4fb6fe containers.cabal | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/containers.cabal b/containers.cabal index afd2e34..6c77693 100644 --- a/containers.cabal +++ b/containers.cabal @@ -85,6 +85,7 @@ Test-suite map-lazy-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -102,6 +103,7 @@ Test-suite map-strict-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -119,6 +121,7 @@ Test-suite set-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -136,6 +139,7 @@ Test-suite intmap-lazy-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -153,6 +157,7 @@ Test-suite intmap-strict-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -170,6 +175,7 @@ Test-suite intset-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -187,6 +193,7 @@ Test-suite deprecated-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -202,6 +209,7 @@ Test-suite seq-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -225,6 +233,7 @@ test-suite map-strictness-properties test-framework-quickcheck2 >= 0.2.9 ghc-options: -Wall + include-dirs: include test-suite intmap-strictness-properties hs-source-dirs: tests, . @@ -242,3 +251,4 @@ test-suite intmap-strictness-properties test-framework-quickcheck2 >= 0.2.9 ghc-options: -Wall + include-dirs: include From git at git.haskell.org Fri Jan 23 22:41:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:40 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add an IsList instance for Data.Sequence.Seq (1931ecf) Message-ID: <20150123224140.836B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/1931ecf7da3d4e4ead4bd1ef5f5ed07807893339 >--------------------------------------------------------------- commit 1931ecf7da3d4e4ead4bd1ef5f5ed07807893339 Author: David Feuer Date: Wed Dec 3 17:16:39 2014 -0500 Add an IsList instance for Data.Sequence.Seq >--------------------------------------------------------------- 1931ecf7da3d4e4ead4bd1ef5f5ed07807893339 Data/Sequence.hs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 511cad9..757f677 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -5,6 +5,9 @@ #if __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE TypeFamilies #-} +#endif -- We use cabal-generated MIN_VERSION_base to adapt to changes of base. -- Nevertheless, as a convenience, we also allow compiling without cabal by -- defining trivial MIN_VERSION_base if needed. @@ -171,7 +174,9 @@ import Data.Coerce #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity(..)) #endif - +#if __GLASGOW_HASKELL__ >= 708 +import qualified GHC.Exts +#endif infixr 5 `consTree` infixl 5 `snocTree` @@ -1655,6 +1660,13 @@ findIndicesR p xs = foldlWithIndex g [] xs fromList :: [a] -> Seq a fromList = Data.List.foldl' (|>) empty +#if __GLASGOW_HASKELL__ >= 708 +instance GHC.Exts.IsList (Seq a) where + type Item (Seq a) = a + fromList = fromList + toList = toList +#endif + ------------------------------------------------------------------------ -- Reverse ------------------------------------------------------------------------ From git at git.haskell.org Fri Jan 23 22:41:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:40 +0000 (UTC) Subject: [commit: packages/containers] master: Disable coercion tests for the time being. (bc74f91) Message-ID: <20150123224140.D46503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/bc74f915a5c223ae976290161b1b2f4ef7ea5b41 >--------------------------------------------------------------- commit bc74f915a5c223ae976290161b1b2f4ef7ea5b41 Author: Milan Straka Date: Tue Dec 16 09:38:16 2014 +0100 Disable coercion tests for the time being. >--------------------------------------------------------------- bc74f915a5c223ae976290161b1b2f4ef7ea5b41 tests-ghc/all.T | 5 ----- tests-ghc/unreliable/README | 2 ++ tests-ghc/{all.T => unreliable/coerce_tests} | 7 ------- tests-ghc/{ => unreliable}/mapcoerceintmap.hs | 0 tests-ghc/{ => unreliable}/mapcoerceintmap.stdout | 0 tests-ghc/{ => unreliable}/mapcoerceintmapstrict.hs | 0 tests-ghc/{ => unreliable}/mapcoerceintmapstrict.hs.stdout | 0 tests-ghc/{ => unreliable}/mapcoercemap.hs | 0 tests-ghc/{ => unreliable}/mapcoercemap.stdout | 0 tests-ghc/{ => unreliable}/mapcoerceseq.hs | 0 tests-ghc/{ => unreliable}/mapcoerceseq.stdout | 0 tests-ghc/{ => unreliable}/mapcoercesmap.hs | 0 tests-ghc/{ => unreliable}/mapcoercesmap.stdout | 0 13 files changed, 2 insertions(+), 12 deletions(-) diff --git a/tests-ghc/all.T b/tests-ghc/all.T index eba1dcc..b7887dc 100644 --- a/tests-ghc/all.T +++ b/tests-ghc/all.T @@ -5,8 +5,3 @@ test('datamap001', normal, compile_and_run, ['-package containers']) test('datamap002', normal, compile_and_run, ['-package containers']) test('dataintset001', normal, compile_and_run, ['-package containers']) test('sequence001', normal, compile_and_run, ['-package containers']) -test('mapcoerceseq', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) -test('mapcoercemap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) -test('mapcoercesmap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) -test('mapcoerceintmap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) -test('mapcoerceintmapstrict', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) diff --git a/tests-ghc/unreliable/README b/tests-ghc/unreliable/README new file mode 100644 index 0000000..23240fe --- /dev/null +++ b/tests-ghc/unreliable/README @@ -0,0 +1,2 @@ +These coerce tests depend on whether RULES are fired or not, +so adding them to general GHC suite might cause testing failures. diff --git a/tests-ghc/all.T b/tests-ghc/unreliable/coerce_tests similarity index 55% copy from tests-ghc/all.T copy to tests-ghc/unreliable/coerce_tests index eba1dcc..5cc72d0 100644 --- a/tests-ghc/all.T +++ b/tests-ghc/unreliable/coerce_tests @@ -1,10 +1,3 @@ -# This is a test script for use with GHC's testsuite framework, see -# http://darcs.haskell.org/testsuite - -test('datamap001', normal, compile_and_run, ['-package containers']) -test('datamap002', normal, compile_and_run, ['-package containers']) -test('dataintset001', normal, compile_and_run, ['-package containers']) -test('sequence001', normal, compile_and_run, ['-package containers']) test('mapcoerceseq', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) test('mapcoercemap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) test('mapcoercesmap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) diff --git a/tests-ghc/mapcoerceintmap.hs b/tests-ghc/unreliable/mapcoerceintmap.hs similarity index 100% rename from tests-ghc/mapcoerceintmap.hs rename to tests-ghc/unreliable/mapcoerceintmap.hs diff --git a/tests-ghc/mapcoerceintmap.stdout b/tests-ghc/unreliable/mapcoerceintmap.stdout similarity index 100% rename from tests-ghc/mapcoerceintmap.stdout rename to tests-ghc/unreliable/mapcoerceintmap.stdout diff --git a/tests-ghc/mapcoerceintmapstrict.hs b/tests-ghc/unreliable/mapcoerceintmapstrict.hs similarity index 100% rename from tests-ghc/mapcoerceintmapstrict.hs rename to tests-ghc/unreliable/mapcoerceintmapstrict.hs diff --git a/tests-ghc/mapcoerceintmapstrict.hs.stdout b/tests-ghc/unreliable/mapcoerceintmapstrict.hs.stdout similarity index 100% rename from tests-ghc/mapcoerceintmapstrict.hs.stdout rename to tests-ghc/unreliable/mapcoerceintmapstrict.hs.stdout diff --git a/tests-ghc/mapcoercemap.hs b/tests-ghc/unreliable/mapcoercemap.hs similarity index 100% rename from tests-ghc/mapcoercemap.hs rename to tests-ghc/unreliable/mapcoercemap.hs diff --git a/tests-ghc/mapcoercemap.stdout b/tests-ghc/unreliable/mapcoercemap.stdout similarity index 100% rename from tests-ghc/mapcoercemap.stdout rename to tests-ghc/unreliable/mapcoercemap.stdout diff --git a/tests-ghc/mapcoerceseq.hs b/tests-ghc/unreliable/mapcoerceseq.hs similarity index 100% rename from tests-ghc/mapcoerceseq.hs rename to tests-ghc/unreliable/mapcoerceseq.hs diff --git a/tests-ghc/mapcoerceseq.stdout b/tests-ghc/unreliable/mapcoerceseq.stdout similarity index 100% rename from tests-ghc/mapcoerceseq.stdout rename to tests-ghc/unreliable/mapcoerceseq.stdout diff --git a/tests-ghc/mapcoercesmap.hs b/tests-ghc/unreliable/mapcoercesmap.hs similarity index 100% rename from tests-ghc/mapcoercesmap.hs rename to tests-ghc/unreliable/mapcoercesmap.hs diff --git a/tests-ghc/mapcoercesmap.stdout b/tests-ghc/unreliable/mapcoercesmap.stdout similarity index 100% rename from tests-ghc/mapcoercesmap.stdout rename to tests-ghc/unreliable/mapcoercesmap.stdout From git at git.haskell.org Fri Jan 23 22:41:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:42 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #85 from treeowl/islist (cd5a854) Message-ID: <20150123224142.8C7E53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/cd5a854691c34dbea4a7fddd166095b7d2f0b3e0 >--------------------------------------------------------------- commit cd5a854691c34dbea4a7fddd166095b7d2f0b3e0 Merge: e1e75b8 1931ecf Author: Milan Straka Date: Thu Dec 4 10:01:51 2014 +0100 Merge pull request #85 from treeowl/islist Add an IsList instance for Data.Sequence.Seq >--------------------------------------------------------------- cd5a854691c34dbea4a7fddd166095b7d2f0b3e0 Data/Sequence.hs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:41:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:42 +0000 (UTC) Subject: [commit: packages/containers] master: Remove circular `toList` definition. (446e295) Message-ID: <20150123224142.DC3CD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/446e295ee0db08bb10f6e5dca6f930669b565ffc >--------------------------------------------------------------- commit 446e295ee0db08bb10f6e5dca6f930669b565ffc Author: Milan Straka Date: Tue Dec 16 11:11:07 2014 +0100 Remove circular `toList` definition. When writing this, I assumed we have explicit `toList` as we have in other containers. We do not have `toList`, and even if we did, the code would not compile, as the two `toList`s (ours and `Foldable`) would collide. >--------------------------------------------------------------- 446e295ee0db08bb10f6e5dca6f930669b565ffc Data/Sequence.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 800ec46..b540978 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -247,8 +247,6 @@ instance Foldable Seq where {-# INLINE length #-} null = null {-# INLINE null #-} - toList = toList - {-# INLINE toList #-} #endif instance Traversable Seq where From git at git.haskell.org Fri Jan 23 22:41:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:43 +0000 (UTC) Subject: [commit: packages/bytestring] branch '0.10.4.x' created Message-ID: <20150123224143.9A9D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring New branch : 0.10.4.x Referencing: 030f5669bcb48285a9b19577e05da854c762b907 From git at git.haskell.org Fri Jan 23 22:41:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:44 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Make version-appropriate Foldable imports (39e9ee9) Message-ID: <20150123224144.938563A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/39e9ee9992269eb2ad3a9b7e608457c6d1a92b04 >--------------------------------------------------------------- commit 39e9ee9992269eb2ad3a9b7e608457c6d1a92b04 Author: David Feuer Date: Thu Dec 4 10:59:22 2014 -0500 Make version-appropriate Foldable imports foldl' and foldr' moved into the Foldable class, then toList. This gets rid of a warning about the imports. >--------------------------------------------------------------- 39e9ee9992269eb2ad3a9b7e608457c6d1a92b04 Data/Sequence.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 511cad9..88faf62 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -155,7 +155,15 @@ import Control.DeepSeq (NFData(rnf)) import Control.Monad (MonadPlus(..), ap) import Data.Monoid (Monoid(..)) import Data.Functor (Functor(..)) +#if MIN_VERSION_base(4,8,0) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr', toList)) +#else +#if MIN_VERSION_base(4,6,0) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr'), toList) +#else import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', foldr', toList) +#endif +#endif import Data.Traversable import Data.Typeable From git at git.haskell.org Fri Jan 23 22:41:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:44 +0000 (UTC) Subject: [commit: packages/containers] master: Import only used class methods of Foldable. (6b026a7) Message-ID: <20150123224144.E2BC63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/6b026a7a730569d21b27ad2a8c18961cd8662a35 >--------------------------------------------------------------- commit 6b026a7a730569d21b27ad2a8c18961cd8662a35 Author: Milan Straka Date: Tue Dec 16 14:12:37 2014 +0100 Import only used class methods of Foldable. On GHC 7.8, the Foldable class contains also null and length, which conflicts with Data.Sequence{null,length}. >--------------------------------------------------------------- 6b026a7a730569d21b27ad2a8c18961cd8662a35 tests/seq-properties.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index a64e66d..4cf0876 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -3,7 +3,7 @@ import Data.Sequence -- needs to be compiled with -DTESTING for use here import Control.Applicative (Applicative(..)) import Control.Arrow ((***)) import Data.Array (listArray) -import Data.Foldable (Foldable(..), toList, all, sum) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1), toList, all, sum) import Data.Functor ((<$>), (<$)) import Data.Maybe import Data.Monoid (Monoid(..)) From git at git.haskell.org Fri Jan 23 22:41:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:45 +0000 (UTC) Subject: [commit: packages/bytestring] branch 'ghc-head' deleted Message-ID: <20150123224145.9BA053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring Deleted branch: ghc-head From git at git.haskell.org Fri Jan 23 22:41:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:46 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Merge pull request #86 from treeowl/foldableimports (f22d14b) Message-ID: <20150123224146.9D89D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/f22d14b56e2c70d6525436a178912c7010bd5169 >--------------------------------------------------------------- commit f22d14b56e2c70d6525436a178912c7010bd5169 Merge: cd5a854 39e9ee9 Author: Milan Straka Date: Fri Dec 5 07:12:40 2014 +0100 Merge pull request #86 from treeowl/foldableimports Make version-appropriate Foldable imports >--------------------------------------------------------------- f22d14b56e2c70d6525436a178912c7010bd5169 Data/Sequence.hs | 8 ++++++++ 1 file changed, 8 insertions(+) From git at git.haskell.org Fri Jan 23 22:41:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:46 +0000 (UTC) Subject: [commit: packages/containers] master: It is perfectly fine to import class methods... (d288dc7) Message-ID: <20150123224146.EA7FA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/d288dc750949e476af221a832dea8d8c053808a4 >--------------------------------------------------------------- commit d288dc750949e476af221a832dea8d8c053808a4 Author: Milan Straka Date: Tue Dec 16 14:16:20 2014 +0100 It is perfectly fine to import class methods... ...without specifying the class, see Haskell 2010 5.2.1. That allows us to get rid of some conditional includes. Nevetheless, we still conditionally include foldr', as we do not use it for base <4.8. >--------------------------------------------------------------- d288dc750949e476af221a832dea8d8c053808a4 Data/Sequence.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index b540978..7d31f79 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -158,14 +158,9 @@ import Control.DeepSeq (NFData(rnf)) import Control.Monad (MonadPlus(..), ap) import Data.Monoid (Monoid(..)) import Data.Functor (Functor(..)) -#if MIN_VERSION_base(4,8,0) -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr', toList)) -#else -#if MIN_VERSION_base(4,6,0) -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl'), toList) -#else import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', toList) -#endif +#if MIN_VERSION_base(4,8,0) +import Data.Foldable (foldr') #endif import Data.Traversable import Data.Typeable From git at git.haskell.org Fri Jan 23 22:41:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:47 +0000 (UTC) Subject: [commit: packages/bytestring] tag 'bytestring-0.10.4.1-release' created Message-ID: <20150123224147.9C2103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring New tag : bytestring-0.10.4.1-release Referencing: 94fb2699c4ba21e9b9970d3611a6ad58a80a7800 From git at git.haskell.org Fri Jan 23 22:41:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:48 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6,develop-0.6-questionable,master,zip-devel: Specialize splitTraverse; strictify pair splitting (7e6d75f) Message-ID: <20150123224148.A5CB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/7e6d75f9cfb524ccb3c7dfd149c6f7f74e276285 >--------------------------------------------------------------- commit 7e6d75f9cfb524ccb3c7dfd149c6f7f74e276285 Author: David Feuer Date: Wed Dec 3 13:27:41 2014 -0500 Specialize splitTraverse; strictify pair splitting Explicitly specialize `splitTraverse` functions to the necessary types. This has no immediate performance impact, but makes it clearer what the functions are about. Make splitting pairs a bit stricter; we don't need that much laziness. >--------------------------------------------------------------- 7e6d75f9cfb524ccb3c7dfd149c6f7f74e276285 Data/Sequence.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 10d3a92..9955584 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1726,14 +1726,18 @@ instance Splittable (Seq a) where splitState = splitAt instance (Splittable a, Splittable b) => Splittable (a, b) where - splitState i (a, b) = ((al, bl), (ar, br)) + splitState i (a, b) = (al `seq` bl `seq` (al, bl), ar `seq` br `seq` (ar, br)) where (al, ar) = splitState i a (bl, br) = splitState i b +{-# SPECIALIZE splitTraverseSeq :: (Seq x -> a -> b) -> Seq x -> Seq a -> Seq b #-} +{-# SPECIALIZE splitTraverseSeq :: ((Seq x, Seq y) -> a -> b) -> (Seq x, Seq y) -> Seq a -> Seq b #-} splitTraverseSeq :: (Splittable s) => (s -> a -> b) -> s -> Seq a -> Seq b splitTraverseSeq f s (Seq xs) = Seq $ splitTraverseTree (\s' (Elem a) -> Elem (f s' a)) s xs +{-# SPECIALIZE splitTraverseTree :: (Seq x -> Elem y -> b) -> Seq x -> FingerTree (Elem y) -> FingerTree b #-} +{-# SPECIALIZE splitTraverseTree :: (Seq x -> Node y -> b) -> Seq x -> FingerTree (Node y) -> FingerTree b #-} splitTraverseTree :: (Sized a, Splittable s) => (s -> a -> b) -> s -> FingerTree a -> FingerTree b splitTraverseTree _f _s Empty = Empty splitTraverseTree f s (Single xs) = Single $ f s xs @@ -1742,6 +1746,8 @@ splitTraverseTree f s (Deep n pr m sf) = Deep n (splitTraverseDigit f prs pr) (s (prs, r) = splitState (size pr) s (ms, sfs) = splitState (n - size pr - size sf) r +{-# SPECIALIZE splitTraverseDigit :: (Seq x -> Elem y -> b) -> Seq x -> Digit (Elem y) -> Digit b #-} +{-# SPECIALIZE splitTraverseDigit :: (Seq x -> Node y -> b) -> Seq x -> Digit (Node y) -> Digit b #-} splitTraverseDigit :: (Sized a, Splittable s) => (s -> a -> b) -> s -> Digit a -> Digit b splitTraverseDigit f s (One a) = One (f s a) splitTraverseDigit f s (Two a b) = Two (f first a) (f second b) @@ -1757,6 +1763,8 @@ splitTraverseDigit f s (Four a b c d) = Four (f first a) (f second b) (f third c (middle, fourth) = splitState (size b + size c) s' (second, third) = splitState (size b) middle +{-# SPECIALIZE splitTraverseNode :: (Seq x -> Elem y -> b) -> Seq x -> Node (Elem y) -> Node b #-} +{-# SPECIALIZE splitTraverseNode :: (Seq x -> Node y -> b) -> Seq x -> Node (Node y) -> Node b #-} splitTraverseNode :: (Sized a, Splittable s) => (s -> a -> b) -> s -> Node a -> Node b splitTraverseNode f s (Node2 ns a b) = Node2 ns (f first a) (f second b) where From git at git.haskell.org Fri Jan 23 22:41:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:48 +0000 (UTC) Subject: [commit: packages/containers] master: Add forgotten foldMap to the imports. (4a6bbb1) Message-ID: <20150123224148.F1D353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/4a6bbb14e6d982825235a521510afd55c565cc59 >--------------------------------------------------------------- commit 4a6bbb14e6d982825235a521510afd55c565cc59 Author: Milan Straka Date: Tue Dec 16 14:32:23 2014 +0100 Add forgotten foldMap to the imports. The foldMap is in Prelude on base 4.8, that is why I missed it. >--------------------------------------------------------------- 4a6bbb14e6d982825235a521510afd55c565cc59 tests/seq-properties.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index 4cf0876..4f4f468 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -3,7 +3,7 @@ import Data.Sequence -- needs to be compiled with -DTESTING for use here import Control.Applicative (Applicative(..)) import Control.Arrow ((***)) import Data.Array (listArray) -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1), toList, all, sum) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), toList, all, sum) import Data.Functor ((<$>), (<$)) import Data.Maybe import Data.Monoid (Monoid(..)) From git at git.haskell.org Fri Jan 23 22:41:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:49 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Apparently the Unsafe extension is only in ghc 7.4+ (f0bac1d) Message-ID: <20150123224149.A9EA53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/f0bac1db84821ba0b8457d77fab02d2334b706df >--------------------------------------------------------------- commit f0bac1db84821ba0b8457d77fab02d2334b706df Author: Duncan Coutts Date: Mon Oct 21 16:02:56 2013 +0100 Apparently the Unsafe extension is only in ghc 7.4+ >--------------------------------------------------------------- f0bac1db84821ba0b8457d77fab02d2334b706df Data/ByteString/Builder/Internal.hs | 2 +- Data/ByteString/Builder/Prim/Internal.hs | 2 +- Data/ByteString/Internal.hs | 2 +- Data/ByteString/Lazy/Internal.hs | 2 +- Data/ByteString/Short/Internal.hs | 2 +- bytestring.cabal | 7 +------ 6 files changed, 6 insertions(+), 11 deletions(-) diff --git a/Data/ByteString/Builder/Internal.hs b/Data/ByteString/Builder/Internal.hs index e1ee141..e8617ef 100644 --- a/Data/ByteString/Builder/Internal.hs +++ b/Data/ByteString/Builder/Internal.hs @@ -1,5 +1,5 @@ {-# LANGUAGE ScopedTypeVariables, CPP, BangPatterns, RankNTypes #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Unsafe #-} #endif {-# OPTIONS_HADDOCK hide #-} diff --git a/Data/ByteString/Builder/Prim/Internal.hs b/Data/ByteString/Builder/Prim/Internal.hs index 85084d4..4baf81a 100644 --- a/Data/ByteString/Builder/Prim/Internal.hs +++ b/Data/ByteString/Builder/Prim/Internal.hs @@ -1,5 +1,5 @@ {-# LANGUAGE ScopedTypeVariables, CPP, BangPatterns #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Unsafe #-} #endif {-# OPTIONS_HADDOCK hide #-} diff --git a/Data/ByteString/Internal.hs b/Data/ByteString/Internal.hs index ca1326c..e7f7a19 100644 --- a/Data/ByteString/Internal.hs +++ b/Data/ByteString/Internal.hs @@ -2,7 +2,7 @@ #if __GLASGOW_HASKELL__ {-# LANGUAGE UnliftedFFITypes, MagicHash, UnboxedTuples, DeriveDataTypeable #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Unsafe #-} #endif #endif diff --git a/Data/ByteString/Lazy/Internal.hs b/Data/ByteString/Lazy/Internal.hs index 2de77af..9ed6d05 100644 --- a/Data/ByteString/Lazy/Internal.hs +++ b/Data/ByteString/Lazy/Internal.hs @@ -1,7 +1,7 @@ {-# LANGUAGE CPP, ForeignFunctionInterface, BangPatterns #-} #if __GLASGOW_HASKELL__ {-# LANGUAGE DeriveDataTypeable #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Unsafe #-} #endif #endif diff --git a/Data/ByteString/Short/Internal.hs b/Data/ByteString/Short/Internal.hs index 092f062..78eeac7 100644 --- a/Data/ByteString/Short/Internal.hs +++ b/Data/ByteString/Short/Internal.hs @@ -2,7 +2,7 @@ ForeignFunctionInterface, MagicHash, UnboxedTuples, UnliftedFFITypes #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Unsafe #-} #endif {-# OPTIONS_HADDOCK hide #-} diff --git a/bytestring.cabal b/bytestring.cabal index d3e314a..0762d81 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -1,5 +1,5 @@ Name: bytestring -Version: 0.10.4.0 +Version: 0.10.4.1 Synopsis: Fast, compact, strict and lazy byte strings with a list interface Description: An efficient compact, immutable byte string type (both strict and lazy) @@ -64,11 +64,6 @@ source-repository head type: git location: https://github.com/haskell/bytestring -source-repository this - type: git - location: https://github.com/haskell/bytestring - tag: 0.10.4.0 - flag integer-simple description: Use the simple integer library instead of GMP default: False From git at git.haskell.org Fri Jan 23 22:41:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:50 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Make zipWith faster (31e1234) Message-ID: <20150123224150.AE5573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/31e1234435ae734bbf3d33a79e9cce89d06ac738 >--------------------------------------------------------------- commit 31e1234435ae734bbf3d33a79e9cce89d06ac738 Author: David Feuer Date: Tue Dec 2 17:09:49 2014 -0500 Make zipWith faster Make `zipWith` build its result with the structure of its first argument, splitting up its second argument as it goes. This allows fast random access to the elements of the results immediately, without having to build large portions of the structure. It also seems to be slightly faster than the old implementation when the entire result is used, presumably by avoiding rebalancing costs. I believe most of this code will also help implement a fast `(<*>)`. Use the same approach to implement `zipWith3` and `zipWith4`. Clean up a couple warnings. Many thanks to Carter Schonwald for suggesting that I use the structure of the first sequence to structure the result, and for helping me come up with the splitTraverse approach. Benchmarks: Zipping two 100000 element lists and extracting the 50000th element takes about 11.4ms with the new implementation, as opposed to 88ms with the old. Zipping two 10000 element sequences and forcing the result to normal form takes 4.0ms now rather than 19.7ms. The indexing gains show up for even very short sequences, but the new implementation really starts to look good once the size gets to around 1000--presumably it handles cache effects better than the old one. Note that the naive approach of converting sequences to lists, zipping them, and then converting back, actually works very well for forcing short sequences to normal form, even better than the new implementation. But it starts to lose a lot of ground by the time the size gets to around 10000, and its performance on the indexing tests is bad. >--------------------------------------------------------------- 31e1234435ae734bbf3d33a79e9cce89d06ac738 Data/Sequence.hs | 106 +++++++++++++++++++++++++++++++++++++++++++++++-------- 1 file changed, 92 insertions(+), 14 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index b54f1e6..10d3a92 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -676,10 +676,10 @@ replicateM n x -- | @'replicateSeq' n xs@ concatenates @n@ copies of @xs at . replicateSeq :: Int -> Seq a -> Seq a -replicateSeq n xs +replicateSeq n s | n < 0 = error "replicateSeq takes a nonnegative integer argument" | n == 0 = empty - | otherwise = go n xs + | otherwise = go n s where -- Invariant: k >= 1 go 1 xs = xs @@ -1703,6 +1703,75 @@ reverseNode f (Node2 s a b) = Node2 s (f b) (f a) reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) ------------------------------------------------------------------------ +-- Traversing with splittable "state" +------------------------------------------------------------------------ + +-- For zipping, and probably also for (<*>), it is useful to build a result by +-- traversing a sequence while splitting up something else. For zipping, we +-- traverse the first sequence while splitting up the second [and third [and +-- fourth]]. For fs <*> xs, we expect soon to traverse +-- +-- > replicate (length fs * length xs) () +-- +-- while splitting something essentially equivalent to +-- +-- > fmap (\f -> fmap f xs) fs +-- +-- David Feuer, with excellent guidance from Carter Schonwald, December 2014 + +class Splittable s where + splitState :: Int -> s -> (s,s) + +instance Splittable (Seq a) where + splitState = splitAt + +instance (Splittable a, Splittable b) => Splittable (a, b) where + splitState i (a, b) = ((al, bl), (ar, br)) + where + (al, ar) = splitState i a + (bl, br) = splitState i b + +splitTraverseSeq :: (Splittable s) => (s -> a -> b) -> s -> Seq a -> Seq b +splitTraverseSeq f s (Seq xs) = Seq $ splitTraverseTree (\s' (Elem a) -> Elem (f s' a)) s xs + +splitTraverseTree :: (Sized a, Splittable s) => (s -> a -> b) -> s -> FingerTree a -> FingerTree b +splitTraverseTree _f _s Empty = Empty +splitTraverseTree f s (Single xs) = Single $ f s xs +splitTraverseTree f s (Deep n pr m sf) = Deep n (splitTraverseDigit f prs pr) (splitTraverseTree (splitTraverseNode f) ms m) (splitTraverseDigit f sfs sf) + where + (prs, r) = splitState (size pr) s + (ms, sfs) = splitState (n - size pr - size sf) r + +splitTraverseDigit :: (Sized a, Splittable s) => (s -> a -> b) -> s -> Digit a -> Digit b +splitTraverseDigit f s (One a) = One (f s a) +splitTraverseDigit f s (Two a b) = Two (f first a) (f second b) + where + (first, second) = splitState (size a) s +splitTraverseDigit f s (Three a b c) = Three (f first a) (f second b) (f third c) + where + (first, r) = splitState (size a) s + (second, third) = splitState (size b) r +splitTraverseDigit f s (Four a b c d) = Four (f first a) (f second b) (f third c) (f fourth d) + where + (first, s') = splitState (size a) s + (middle, fourth) = splitState (size b + size c) s' + (second, third) = splitState (size b) middle + +splitTraverseNode :: (Sized a, Splittable s) => (s -> a -> b) -> s -> Node a -> Node b +splitTraverseNode f s (Node2 ns a b) = Node2 ns (f first a) (f second b) + where + (first, second) = splitState (size a) s +splitTraverseNode f s (Node3 ns a b c) = Node3 ns (f first a) (f second b) (f third c) + where + (first, r) = splitState (size a) s + (second, third) = splitState (size b) r + +getSingleton :: Seq a -> a +getSingleton (Seq (Single (Elem a))) = a +getSingleton (Seq Empty) = error "getSingleton: Empty" +getSingleton _ = error "getSingleton: Not a singleton." + +------------------------------------------------------------------------ -- Zipping ------------------------------------------------------------------------ @@ -1717,17 +1786,11 @@ zip = zipWith (,) -- For example, @zipWith (+)@ is applied to two sequences to take the -- sequence of corresponding sums. zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c -zipWith f xs ys - | length xs <= length ys = zipWith' f xs ys - | otherwise = zipWith' (flip f) ys xs - --- like 'zipWith', but assumes length xs <= length ys -zipWith' :: (a -> b -> c) -> Seq a -> Seq b -> Seq c -zipWith' f xs ys = snd (mapAccumL k ys xs) +zipWith f s1 s2 = splitTraverseSeq (\s a -> f a (getSingleton s)) s2' s1' where - k kys x = case viewl kys of - (z :< zs) -> (zs, f x z) - EmptyL -> error "zipWith': unexpected EmptyL" + minLen = min (length s1) (length s2) + s1' = take minLen s1 + s2' = take minLen s2 -- | /O(min(n1,n2,n3))/. 'zip3' takes three sequences and returns a -- sequence of triples, analogous to 'zip'. @@ -1738,7 +1801,14 @@ zip3 = zipWith3 (,,) -- three elements, as well as three sequences and returns a sequence of -- their point-wise combinations, analogous to 'zipWith'. zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d -zipWith3 f s1 s2 s3 = zipWith ($) (zipWith f s1 s2) s3 +zipWith3 f s1 s2 s3 = splitTraverseSeq (\s a -> + case s of + (b, c) -> f a (getSingleton b) (getSingleton c)) (s2', s3') s1' + where + minLen = minimum [length s1, length s2, length s3] + s1' = take minLen s1 + s2' = take minLen s2 + s3' = take minLen s3 -- | /O(min(n1,n2,n3,n4))/. 'zip4' takes four sequences and returns a -- sequence of quadruples, analogous to 'zip'. @@ -1749,7 +1819,15 @@ zip4 = zipWith4 (,,,) -- four elements, as well as four sequences and returns a sequence of -- their point-wise combinations, analogous to 'zipWith'. zipWith4 :: (a -> b -> c -> d -> e) -> Seq a -> Seq b -> Seq c -> Seq d -> Seq e -zipWith4 f s1 s2 s3 s4 = zipWith ($) (zipWith ($) (zipWith f s1 s2) s3) s4 +zipWith4 f s1 s2 s3 s4 = splitTraverseSeq (\s a -> + case s of + (b, (c, d)) -> f a (getSingleton b) (getSingleton c) (getSingleton d)) (s2', (s3', s4')) s1' + where + minLen = minimum [length s1, length s2, length s3, length s4] + s1' = take minLen s1 + s2' = take minLen s2 + s3' = take minLen s3 + s4' = take minLen s4 ------------------------------------------------------------------------ -- Sorting From git at git.haskell.org Fri Jan 23 22:41:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:51 +0000 (UTC) Subject: [commit: packages/containers] master: Bump version number to 0.5.6.1 (ddf4e4a) Message-ID: <20150123224151.062D63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/ddf4e4a7abbfb81161251437a6a5bbe8167a7cde >--------------------------------------------------------------- commit ddf4e4a7abbfb81161251437a6a5bbe8167a7cde Author: Milan Straka Date: Tue Dec 16 14:41:17 2014 +0100 Bump version number to 0.5.6.1 >--------------------------------------------------------------- ddf4e4a7abbfb81161251437a6a5bbe8167a7cde containers.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/containers.cabal b/containers.cabal index 6c77693..169507a 100644 --- a/containers.cabal +++ b/containers.cabal @@ -1,5 +1,5 @@ name: containers -version: 0.5.6.0 +version: 0.5.6.1 license: BSD3 license-file: LICENSE maintainer: fox at ucw.cz From git at git.haskell.org Fri Jan 23 22:41:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:51 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Add Travis-CI script (9ea13b7) Message-ID: <20150123224151.B34243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/9ea13b7eb457fb9b2e0d48ecf547e96ac7f847da >--------------------------------------------------------------- commit 9ea13b7eb457fb9b2e0d48ecf547e96ac7f847da Author: Herbert Valerio Riedel Date: Mon Oct 21 16:38:17 2013 +0200 Add Travis-CI script >--------------------------------------------------------------- 9ea13b7eb457fb9b2e0d48ecf547e96ac7f847da .travis.yml | 40 ++++++++++++++++++++++++++++++++++++++++ 1 file changed, 40 insertions(+) diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..367c274 --- /dev/null +++ b/.travis.yml @@ -0,0 +1,40 @@ +# NB: don't set `language: haskell` here +# See https://github.com/hvr/multi-ghc-travis for more information + +env: + - GHCVER=6.12.3 +# - GHCVER=7.0.1 # disabled due to internal GHC failure + - GHCVER=7.0.2 + - GHCVER=7.0.3 + - GHCVER=7.0.4 + - GHCVER=7.2.1 + - GHCVER=7.2.2 + - GHCVER=7.4.1 + - GHCVER=7.4.2 + - GHCVER=7.6.1 + - GHCVER=7.6.2 + - GHCVER=7.6.3 + - GHCVER=head + +matrix: + allow_failures: + - env: GHCVER=head + +before_install: + - sudo add-apt-repository -y ppa:hvr/ghc + - sudo apt-get update + - sudo apt-get install cabal-install-1.18 ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:$PATH + +install: + - cabal-1.18 update +# can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle + - cabal-1.18 install "QuickCheck >=2.4 && <3" "byteorder ==1.0.*" "dlist ==0.5.*" "mtl >=2.0 && <2.2" deepseq + +script: + - cabal-1.18 configure --enable-tests -v2 + - cabal-1.18 build + - cabal-1.18 test +# "cabal check" disabled due to -O2 warning +# - cabal-1.18 check + - cabal-1.18 sdist From git at git.haskell.org Fri Jan 23 22:41:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:52 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add zip benchmarks (cdf173f) Message-ID: <20150123224152.B68983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/cdf173f4cb1f792a4ac54b939bf197c214abcd43 >--------------------------------------------------------------- commit cdf173f4cb1f792a4ac54b939bf197c214abcd43 Author: David Feuer Date: Wed Dec 3 12:31:45 2014 -0500 Add zip benchmarks >--------------------------------------------------------------- cdf173f4cb1f792a4ac54b939bf197c214abcd43 benchmarks/Sequence.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index 8c18582..ccaca6c 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -20,10 +20,16 @@ main = do r1000 = rlist 1000 rnf [r10, r100, r1000] `seq` return () defaultMain - [ bench "splitAt/append 10" $ nf (shuffle r10) s10 - , bench "splitAt/append 100" $ nf (shuffle r100) s100 - , bench "splitAt/append 1000" $ nf (shuffle r1000) s1000 - ] + [ bgroup "splitAt/append" + [ bench "10" $ nf (shuffle r10) s10 + , bench "100" $ nf (shuffle r100) s100 + , bench "1000" $ nf (shuffle r1000) s1000 + ] + , bgroup "zip" + [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (S.replicate 10000 (), S.fromList [1..10000::Int]) + , bench "nf150" $ nf (uncurry S.zip) (S.fromList [1..150::Int], S.replicate 150 ()) + , bench "nf10000" $ nf (uncurry S.zip) (S.fromList [1..10000::Int], S.replicate 10000 ()) + ] ] -- splitAt+append: repeatedly cut the sequence at a random point -- and rejoin the pieces in the opposite order. From git at git.haskell.org Fri Jan 23 22:41:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:53 +0000 (UTC) Subject: [commit: packages/containers] master: Fix efficiency claim for zipWith. (107ec12) Message-ID: <20150123224153.0E1523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/107ec12d17aa98d8fd552276b81a94fe6f44224b >--------------------------------------------------------------- commit 107ec12d17aa98d8fd552276b81a94fe6f44224b Author: David Feuer Date: Thu Dec 18 11:19:53 2014 -0500 Fix efficiency claim for zipWith. >--------------------------------------------------------------- 107ec12d17aa98d8fd552276b81a94fe6f44224b Data/Sequence.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 7d31f79..7675698 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1872,9 +1872,9 @@ reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) -- them up further and zip them with their matching pieces can be delayed until -- they're actually needed. We do the same thing for Digits (splitting into -- between one and four pieces) and Nodes (splitting into two or three). The --- ultimate result is that we can index, or split at, any location in zs in --- O(log(min{i,n-i})) time *immediately*, with only a constant-factor slowdown --- as thunks are forced along the path. +-- ultimate result is that we can index into, or split at, any location in zs +-- in O((log(min{i,n-i}))^2) time *immediately*, while still being able to +-- force all the thunks in O(n) time. -- -- Benchmark info, and alternatives: -- From git at git.haskell.org Fri Jan 23 22:41:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:53 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Merge pull request #7 from hvr/master (a14c7ce) Message-ID: <20150123224153.BE7703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/a14c7ce55c096b17a13eed859ba93516cf9a2ebb >--------------------------------------------------------------- commit a14c7ce55c096b17a13eed859ba93516cf9a2ebb Merge: f0bac1d 9ea13b7 Author: Duncan Coutts Date: Thu Oct 24 06:19:35 2013 -0700 Merge pull request #7 from hvr/master Add Travis-CI script >--------------------------------------------------------------- a14c7ce55c096b17a13eed859ba93516cf9a2ebb .travis.yml | 40 ++++++++++++++++++++++++++++++++++++++++ 1 file changed, 40 insertions(+) From git at git.haskell.org Fri Jan 23 22:41:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:54 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Nix the Splittable class; add fromFunction (4abaee4) Message-ID: <20150123224154.C04293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/4abaee4c2edadc13413a78848c6eea0558ec06c8 >--------------------------------------------------------------- commit 4abaee4c2edadc13413a78848c6eea0558ec06c8 Author: David Feuer Date: Sat Dec 6 00:23:44 2014 -0500 Nix the Splittable class; add fromFunction Also export splitTraverse, and write mapWithIndex using a hand-unboxed mapWithIndex#. >--------------------------------------------------------------- 4abaee4c2edadc13413a78848c6eea0558ec06c8 Data/Sequence.hs | 220 +++++++++++++++++++++++++++++++++++-------------------- 1 file changed, 142 insertions(+), 78 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4abaee4c2edadc13413a78848c6eea0558ec06c8 From git at git.haskell.org Fri Jan 23 22:41:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:55 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #101 from treeowl/zipdocfix (314f798) Message-ID: <20150123224155.14DF83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/314f7983819861c68e77f0f5798c86812b23fa39 >--------------------------------------------------------------- commit 314f7983819861c68e77f0f5798c86812b23fa39 Merge: ddf4e4a 107ec12 Author: Milan Straka Date: Thu Dec 18 22:59:51 2014 +0100 Merge pull request #101 from treeowl/zipdocfix Fix efficiency claim for zipWith. >--------------------------------------------------------------- 314f7983819861c68e77f0f5798c86812b23fa39 Data/Sequence.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Jan 23 22:41:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:55 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Rename and document inlinePerformIO to better reflect its behaviour (80ff4a3) Message-ID: <20150123224155.CCFD13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/80ff4a3018cd8909abb1d4e0c32f012a523883ec >--------------------------------------------------------------- commit 80ff4a3018cd8909abb1d4e0c32f012a523883ec Author: Duncan Coutts Date: Thu Feb 6 15:06:26 2014 +0000 Rename and document inlinePerformIO to better reflect its behaviour We've had a few instances of people being tempted to use it without really understanding the consequences. >--------------------------------------------------------------- 80ff4a3018cd8909abb1d4e0c32f012a523883ec Data/ByteString.hs | 73 ++++++++++++++++++++------------------- Data/ByteString/Char8.hs | 8 ++--- Data/ByteString/Internal.hs | 55 +++++++++++++++++++++-------- Data/ByteString/Lazy.hs | 6 ++-- Data/ByteString/Short/Internal.hs | 8 +++-- Data/ByteString/Unsafe.hs | 6 ++-- 6 files changed, 95 insertions(+), 61 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 80ff4a3018cd8909abb1d4e0c32f012a523883ec From git at git.haskell.org Fri Jan 23 22:41:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:56 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Add comments explaining the splitting traversal (c0e8c7d) Message-ID: <20150123224156.C83A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master,zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/c0e8c7d9e135527a188c5a932cab1e96c11c1de5 >--------------------------------------------------------------- commit c0e8c7d9e135527a188c5a932cab1e96c11c1de5 Author: David Feuer Date: Thu Dec 4 11:50:20 2014 -0500 Add comments explaining the splitting traversal Why it's a good idea, how it works, and what the benchmarks say. >--------------------------------------------------------------- c0e8c7d9e135527a188c5a932cab1e96c11c1de5 Data/Sequence.hs | 58 +++++++++++++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 57 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 9955584..212c926 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -128,6 +128,7 @@ module Data.Sequence ( foldlWithIndex, -- :: (b -> Int -> a -> b) -> b -> Seq a -> b foldrWithIndex, -- :: (Int -> a -> b -> b) -> b -> Seq a -> b -- * Transformations + genSplitTraverseSeq, mapWithIndex, -- :: (Int -> a -> b) -> Seq a -> Seq b reverse, -- :: Seq a -> Seq a -- ** Zips @@ -1709,7 +1710,7 @@ reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) -- For zipping, and probably also for (<*>), it is useful to build a result by -- traversing a sequence while splitting up something else. For zipping, we -- traverse the first sequence while splitting up the second [and third [and --- fourth]]. For fs <*> xs, we expect soon to traverse +-- fourth]]. For fs <*> xs, we hope to traverse -- -- > replicate (length fs * length xs) () -- @@ -1717,6 +1718,51 @@ reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) -- -- > fmap (\f -> fmap f xs) fs -- +-- What makes all this crazy code a good idea: +-- +-- Suppose we zip together two sequences of the same length: +-- +-- zs = zip xs ys +-- +-- We want to get reasonably fast indexing into zs immediately, rather than +-- needing to construct the entire thing first, as the previous implementation +-- required. The first aspect is that we build the result "outside-in" or +-- "top-down", rather than left to right. That gives us access to both ends +-- quickly. But that's not enough, by itself, to give immediate access to the +-- center of zs. For that, we need to be able to skip over larger segments of +-- zs, delaying their construction until we actually need them. The way we do +-- this is to traverse xs, while splitting up ys according to the structure of +-- xs. If we have a Deep _ pr m sf, we split ys into three pieces, and hand off +-- one piece to the prefix, one to the middle, and one to the suffix of the +-- result. The key point is that we don't need to actually do anything further +-- with those pieces until we actually need them; the computations to split +-- them up further and zip them with their matching pieces can be delayed until +-- they're actually needed. We do the same thing for Digits (splitting into +-- between one and four pieces) and Nodes (splitting into two or three). The +-- ultimate result is that we can index, or split at, any location in zs in +-- O(log(min{i,n-i})) time *immediately*, with only a constant-factor slowdown +-- as thunks are forced along the path. +-- +-- Benchmark info, and alternatives: +-- +-- The old zipping code used mapAccumL to traverse the first sequence while +-- cutting down the second sequence one piece at a time. +-- +-- An alternative way to express that basic idea is to convert both sequences +-- to lists, zip the lists, and then convert the result back to a sequence. +-- I'll call this the "listy" implementation. +-- +-- I benchmarked two operations: Each started by zipping two sequences +-- constructed with replicate and/or fromList. The first would then immediately +-- index into the result. The second would apply deepseq to force the entire +-- result. The new implementation worked much better than either of the others +-- on the immediate indexing test, as expected. It also worked better than the +-- old implementation for all the deepseq tests. For short sequences, the listy +-- implementation outperformed all the others on the deepseq test. However, the +-- splitting implementation caught up and surpassed it once the sequences grew +-- long enough. It seems likely that by avoiding rebuilding, it interacts +-- better with the cache hierarchy. +-- -- David Feuer, with excellent guidance from Carter Schonwald, December 2014 class Splittable s where @@ -1731,6 +1777,16 @@ instance (Splittable a, Splittable b) => Splittable (a, b) where (al, ar) = splitState i a (bl, br) = splitState i b +data GenSplittable s = GenSplittable s (Int -> s -> (s,s)) +instance Splittable (GenSplittable s) where + splitState i (GenSplittable s spl) = (GenSplittable l spl, GenSplittable r spl) + where + (l,r) = spl i s + +{-# INLINE genSplitTraverseSeq #-} +genSplitTraverseSeq :: (Int -> s -> (s, s)) -> (s -> a -> b) -> s -> Seq a -> Seq b +genSplitTraverseSeq spl f s = splitTraverseSeq (\(GenSplittable s _) -> f s) (GenSplittable s spl) + {-# SPECIALIZE splitTraverseSeq :: (Seq x -> a -> b) -> Seq x -> Seq a -> Seq b #-} {-# SPECIALIZE splitTraverseSeq :: ((Seq x, Seq y) -> a -> b) -> (Seq x, Seq y) -> Seq a -> Seq b #-} splitTraverseSeq :: (Splittable s) => (s -> a -> b) -> s -> Seq a -> Seq b From git at git.haskell.org Fri Jan 23 22:41:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:57 +0000 (UTC) Subject: [commit: packages/containers] master: Use fromList2 to implement fromListN in IsList (ace8f7f) Message-ID: <20150123224157.1D6A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/ace8f7fd88e5458a8401804e32a2d921d653fdfa >--------------------------------------------------------------- commit ace8f7fd88e5458a8401804e32a2d921d653fdfa Author: David Feuer Date: Fri Dec 19 15:09:03 2014 -0500 Use fromList2 to implement fromListN in IsList >--------------------------------------------------------------- ace8f7fd88e5458a8401804e32a2d921d653fdfa Data/Sequence.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 7d31f79..b216b12 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1806,6 +1806,7 @@ fromList = Seq . mkTree 1 . map_elem instance GHC.Exts.IsList (Seq a) where type Item (Seq a) = a fromList = fromList + fromListN = fromList2 toList = toList #endif From git at git.haskell.org Fri Jan 23 22:41:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:57 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Fixed logic on CONLIKE hack. (35b38d1) Message-ID: <20150123224157.D5DEE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/35b38d1021c68200bf472eea2342035fbf5c86f7 >--------------------------------------------------------------- commit 35b38d1021c68200bf472eea2342035fbf5c86f7 Author: Duncan Coutts Date: Thu Feb 6 17:10:39 2014 +0000 Fixed logic on CONLIKE hack. Based closely on a patch by Stijn van Drongelen >--------------------------------------------------------------- 35b38d1021c68200bf472eea2342035fbf5c86f7 Data/ByteString/Builder/Prim/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/ByteString/Builder/Prim/Internal.hs b/Data/ByteString/Builder/Prim/Internal.hs index 4baf81a..fb52404 100644 --- a/Data/ByteString/Builder/Prim/Internal.hs +++ b/Data/ByteString/Builder/Prim/Internal.hs @@ -69,7 +69,7 @@ module Data.ByteString.Builder.Prim.Internal ( import Foreign import Prelude hiding (maxBound) -#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 611 +#if !(__GLASGOW_HASKELL__ >= 612) -- ghc-6.10 and older do not support {-# INLINE CONLIKE #-} #define CONLIKE #endif From git at git.haskell.org Fri Jan 23 22:41:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:58 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Make <*> fast (73c06d4) Message-ID: <20150123224158.D0AE23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/73c06d4421aaca2dc3c06d07d452d3e8f586ecf4 >--------------------------------------------------------------- commit 73c06d4421aaca2dc3c06d07d452d3e8f586ecf4 Author: David Feuer Date: Sat Dec 6 18:46:49 2014 -0500 Make <*> fast Use the `splitTraverse` mechanism to implement `<*>` with optimal incremental performance. Stop exporting `splitTraverse`. Many thanks to Joachim Breitner for writing the splitting code for this. >--------------------------------------------------------------- 73c06d4421aaca2dc3c06d07d452d3e8f586ecf4 Data/Sequence.hs | 61 ++++++++++++++++++++++++++++++++++++++++++++++++++++---- 1 file changed, 57 insertions(+), 4 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 9e78ce1..f7d551c 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -133,7 +133,6 @@ module Data.Sequence ( -- * Transformations mapWithIndex, -- :: (Int -> a -> b) -> Seq a -> Seq b reverse, -- :: Seq a -> Seq a - splitTraverse, -- :: (Int -> s -> (s, s)) -> (s -> a -> b) -> s -> Seq a -> Seq b -- ** Zips zip, -- :: Seq a -> Seq b -> Seq (a, b) zipWith, -- :: (a -> b -> c) -> Seq a -> Seq b -> Seq c @@ -257,10 +256,65 @@ instance Monad Seq where instance Applicative Seq where pure = singleton - fs <*> xs = foldl' add empty fs - where add ys f = ys >< fmap f xs + + Seq Empty <*> _ = empty + _ <*> Seq Empty = empty + Seq (Single (Elem f)) <*> xs = fmap f xs + fs <*> Seq (Single (Elem x)) = fmap ($x) fs + fs <*> xs = splitTraverse splitCPs + (\s _ -> uncurry ($) (getSingletonCPs s)) + (createCPs fs xs) + (replicate (length fs * length xs) ()) + xs *> ys = replicateSeq (length xs) ys +-- The splitCPs code below, for splitting ragged-ended Cartesian products, +-- was generously provided by Joachim Breitner. + +data CPs x y = + CPs (Seq x) + (Seq y) + {-# UNPACK #-} !Int {- beginning column -} + {-# UNPACK #-} !Int {- last column -} + | SingleCPs x (Seq y) +#ifdef TESTING + deriving Show +#endif + +-- Note: The total length of CPs xs ys fc lc is +-- (length xs - 1) * length ys - fc + lc + 1 + +-- Create a non-trivial Cps given two sequences +createCPs :: Seq x -> Seq y -> CPs x y +createCPs xs ys = CPs xs ys 0 (length ys - 1) + +-- Smart constructor +mkCPs :: Seq x -> Seq y -> Int -> Int -> CPs x y +mkCPs (Seq (Single (Elem x))) ys fc lc = SingleCPs x (drop fc $ take (lc+1) ys) +mkCPs xs ys fc lc = CPs xs ys fc lc + +splitCPs:: Int -> CPs x y -> (CPs x y, CPs x y) +splitCPs n (SingleCPs x ys) + = ( SingleCPs x ys1, SingleCPs x ys2 ) + where (ys1, ys2) = splitAt n ys +splitCPs n (CPs xs ys fc lc) + = ( mkCPs (take r_end xs) ys fc c_end + , mkCPs (drop r_begin xs) ys c_begin lc + ) + where + -- Coordinates of the beginning of the second chunk + (r_begin, -- number of rows that do not go into the second chunk + c_begin) = (n + fc) `quotRem` length ys + + -- Coordinates of the end of the first chunk + r_end | c_begin == 0 = r_begin -- cut nicely along rows, keep the other rows + | otherwise = r_begin + 1 -- we need to keep one row in both chunks + c_end = (c_begin - 1 + length ys) `rem` length ys + +getSingletonCPs :: CPs x y -> (x, y) +getSingletonCPs (SingleCPs x ys) = (x, getSingleton ys) +getSingletonCPs _ = error "getSingletonCPs: Not a singleton" + instance MonadPlus Seq where mzero = empty mplus = (><) @@ -1370,7 +1424,6 @@ mapWithIndex# f (Seq xs) = Seq $ mapWithIndexTree# (\s (Elem a) -> Elem (f s a)) !(I# sb) = size b !sPsa = s +# sa !sPsab = sPsa +# sb - #endif -- | /O(n)/. Convert a given sequence length and a function representing that From git at git.haskell.org Fri Jan 23 22:41:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:59 +0000 (UTC) Subject: [commit: packages/containers] master: Fix Arbitrary instance for FingerTree (0086aa7) Message-ID: <20150123224159.242433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/0086aa753795237cec28be6d2a261708eb7dacf6 >--------------------------------------------------------------- commit 0086aa753795237cec28be6d2a261708eb7dacf6 Author: Ross Paterson Date: Fri Dec 19 23:24:20 2014 +0000 Fix Arbitrary instance for FingerTree The previous version never generated deep trees containing Empty. Also tweaked the size handling so that the tree size is closer to the specified size (though it can still run over a bit). >--------------------------------------------------------------- 0086aa753795237cec28be6d2a261708eb7dacf6 tests/seq-properties.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index 4f4f468..def17b3 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -112,7 +112,15 @@ instance (Arbitrary a, Sized a) => Arbitrary (FingerTree a) where arb :: (Arbitrary a, Sized a) => Int -> Gen (FingerTree a) arb 0 = return Empty arb 1 = Single <$> arbitrary - arb n = deep <$> arbitrary <*> arb (n `div` 2) <*> arbitrary + arb n = do + pr <- arbitrary + sf <- arbitrary + let n_pr = Prelude.length (toList pr) + let n_sf = Prelude.length (toList sf) + -- adding n `div` 7 ensures that n_m >= 0, and makes more Singles + let n_m = max (n `div` 7) ((n - n_pr - n_sf) `div` 3) + m <- arb n_m + return $ deep pr m sf shrink (Deep _ (One a) Empty (One b)) = [Single a, Single b] shrink (Deep _ pr m sf) = From git at git.haskell.org Fri Jan 23 22:41:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:41:59 +0000 (UTC) Subject: [commit: packages/bytestring] master: Added Data.ByteString.Lazy.elemIndexEnd implementation (8312989) Message-ID: <20150123224159.DFD883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/831298906342f9d8cd0f5ae6f2ed0e9dd474a281 >--------------------------------------------------------------- commit 831298906342f9d8cd0f5ae6f2ed0e9dd474a281 Author: David Turner Date: Thu Feb 27 11:24:09 2014 +0000 Added Data.ByteString.Lazy.elemIndexEnd implementation >--------------------------------------------------------------- 831298906342f9d8cd0f5ae6f2ed0e9dd474a281 Data/ByteString/Lazy.hs | 23 +++++++++++------------ tests/Properties.hs | 10 ++++++++++ 2 files changed, 21 insertions(+), 12 deletions(-) diff --git a/Data/ByteString/Lazy.hs b/Data/ByteString/Lazy.hs index 22ba1ee..d4fe0d2 100644 --- a/Data/ByteString/Lazy.hs +++ b/Data/ByteString/Lazy.hs @@ -166,6 +166,7 @@ module Data.ByteString.Lazy ( -- * Indexing ByteStrings index, -- :: ByteString -> Int64 -> Word8 elemIndex, -- :: Word8 -> ByteString -> Maybe Int64 + elemIndexEnd, -- :: Word8 -> ByteString -> Maybe Int64 elemIndices, -- :: Word8 -> ByteString -> [Int64] findIndex, -- :: (Word8 -> Bool) -> ByteString -> Maybe Int64 findIndices, -- :: (Word8 -> Bool) -> ByteString -> [Int64] @@ -222,6 +223,7 @@ import qualified Data.ByteString.Unsafe as S import Data.ByteString.Lazy.Internal import Data.Monoid (Monoid(..)) +import Control.Monad (mplus) import Data.Word (Word8) import Data.Int (Int64) @@ -904,7 +906,6 @@ elemIndex w cs0 = elemIndex' 0 cs0 Nothing -> elemIndex' (n + fromIntegral (S.length c)) cs Just i -> Just (n + fromIntegral i) -{- -- | /O(n)/ The 'elemIndexEnd' function returns the last index of the -- element in the given 'ByteString' which is equal to the query -- element, or 'Nothing' if there is no such element. The following @@ -912,18 +913,16 @@ elemIndex w cs0 = elemIndex' 0 cs0 -- -- > elemIndexEnd c xs == -- > (-) (length xs - 1) `fmap` elemIndex c (reverse xs) --- -elemIndexEnd :: Word8 -> ByteString -> Maybe Int -elemIndexEnd ch (PS x s l) = accursedUnutterablePerformIO $ withForeignPtr x $ \p -> - go (p `plusPtr` s) (l-1) + +elemIndexEnd :: Word8 -> ByteString -> Maybe Int64 +elemIndexEnd w = elemIndexEnd' 0 where - STRICT2(go) - go p i | i < 0 = return Nothing - | otherwise = do ch' <- peekByteOff p i - if ch == ch' - then return $ Just i - else go p (i-1) --} + elemIndexEnd' _ Empty = Nothing + elemIndexEnd' n (Chunk c cs) = let + n' = n + S.length c + i = fmap (fromIntegral . (n +)) $ S.elemIndexEnd w c + in n' `seq` i `seq` elemIndexEnd' n' cs `mplus` i + -- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning -- the indices of all elements equal to the query element, in ascending order. -- This implementation uses memchr(3). diff --git a/tests/Properties.hs b/tests/Properties.hs index 9f60552..729e649 100644 --- a/tests/Properties.hs +++ b/tests/Properties.hs @@ -1090,6 +1090,14 @@ prop_elemIndexEnd1CC c xs = (C.elemIndexEnd c (C.pack xs)) == prop_elemIndexEnd2BB c xs = (P.elemIndexEnd c (P.pack xs)) == ((-) (length xs - 1) `fmap` P.elemIndex c (P.pack $ reverse xs)) +prop_elemIndexEnd1LL c xs = (L.elemIndexEnd c (L.pack xs)) == + (case L.elemIndex c (L.pack (reverse xs)) of + Nothing -> Nothing + Just i -> Just (fromIntegral (length xs) -1 -i)) + +prop_elemIndexEnd2LL c xs = (L.elemIndexEnd c (L.pack xs)) == + ((-) (fromIntegral (length xs) - 1) `fmap` L.elemIndex c (L.pack $ reverse xs)) + prop_elemIndicesBB xs c = elemIndices c xs == P.elemIndices c (P.pack xs) prop_findIndexBB xs a = (findIndex (==a) xs) == (P.findIndex (==a) (P.pack xs)) @@ -2333,6 +2341,8 @@ bb_tests = , testProperty "elemIndexEnd 1" prop_elemIndexEnd1BB , testProperty "elemIndexEnd 1" prop_elemIndexEnd1CC , testProperty "elemIndexEnd 2" prop_elemIndexEnd2BB + , testProperty "elemIndexEnd 1" prop_elemIndexEnd1LL + , testProperty "elemIndexEnd 2" prop_elemIndexEnd2LL -- , testProperty "words'" prop_wordsBB' -- , testProperty "lines'" prop_linesBB' -- , testProperty "dropSpaceEnd" prop_dropSpaceEndBB From git at git.haskell.org Fri Jan 23 22:42:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:00 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Update benchmark running script to new Criterion options. (83f32bc) Message-ID: <20150123224200.D6AE33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/83f32bcf58a43dfec32a4151d2f677635da7e5cd >--------------------------------------------------------------- commit 83f32bcf58a43dfec32a4151d2f677635da7e5cd Author: Milan Straka Date: Sun Dec 7 14:57:04 2014 +0100 Update benchmark running script to new Criterion options. >--------------------------------------------------------------- 83f32bcf58a43dfec32a4151d2f677635da7e5cd benchmarks/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/benchmarks/Makefile b/benchmarks/Makefile index 1539a2a..ff45493 100644 --- a/benchmarks/Makefile +++ b/benchmarks/Makefile @@ -4,7 +4,7 @@ bench-%: %.hs force ghc -O2 -DTESTING $< -i../$(TOP) -o $@ -outputdir tmp -rtsopts bench-%.csv: bench-% - ./bench-$* $(BENCHMARK) -v -u bench-$*.csv + ./bench-$* $(BENCHMARK) -v 2 --csv bench-$*.csv .PHONY: force clean veryclean force: From git at git.haskell.org Fri Jan 23 22:42:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:01 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #108 from RossPaterson/master (54c3603) Message-ID: <20150123224201.2B47B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/54c36030839949659b9dd4d12b6e92ec22698d40 >--------------------------------------------------------------- commit 54c36030839949659b9dd4d12b6e92ec22698d40 Merge: 314f798 0086aa7 Author: Milan Straka Date: Sat Dec 20 00:50:39 2014 +0100 Merge pull request #108 from RossPaterson/master Fix Arbitrary instance for FingerTree >--------------------------------------------------------------- 54c36030839949659b9dd4d12b6e92ec22698d40 tests/seq-properties.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:42:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:01 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: QuickCheck update from yesterday breaks the build (6093aef) Message-ID: <20150123224201.EC7983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/6093aef1f967f97eebd2ac2e7a98825ae6ec505e >--------------------------------------------------------------- commit 6093aef1f967f97eebd2ac2e7a98825ae6ec505e Author: Daniel Peebles Date: Thu Mar 20 00:06:04 2014 -0400 QuickCheck update from yesterday breaks the build QuickCheck 2.7 changed `Property` to a newtype instead of a type synonym. This should fix it until we update our test code. >--------------------------------------------------------------- 6093aef1f967f97eebd2ac2e7a98825ae6ec505e bytestring.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/bytestring.cabal b/bytestring.cabal index 0762d81..5bbae89 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -153,7 +153,7 @@ test-suite prop-compiled TestFramework hs-source-dirs: . tests build-depends: base, ghc-prim, deepseq, random, directory, - QuickCheck >= 2.3 && < 3 + QuickCheck >= 2.3 && < 2.7 c-sources: cbits/fpstring.c include-dirs: include ghc-options: -fwarn-unused-binds @@ -176,7 +176,7 @@ test-suite test-builder build-depends: base, ghc-prim, deepseq, - QuickCheck >= 2.4 && < 3, + QuickCheck >= 2.4 && < 2.7, byteorder == 1.0.*, dlist == 0.5.*, directory, From git at git.haskell.org Fri Jan 23 22:42:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:02 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Add simple fromFunction benchmark. (fc87eee) Message-ID: <20150123224202.DD94B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/fc87eeefa5907559b2669a16baed03db79f82981 >--------------------------------------------------------------- commit fc87eeefa5907559b2669a16baed03db79f82981 Author: Milan Straka Date: Sun Dec 7 14:57:24 2014 +0100 Add simple fromFunction benchmark. >--------------------------------------------------------------- fc87eeefa5907559b2669a16baed03db79f82981 benchmarks/Sequence.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index ccaca6c..58e1114 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -29,7 +29,13 @@ main = do [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (S.replicate 10000 (), S.fromList [1..10000::Int]) , bench "nf150" $ nf (uncurry S.zip) (S.fromList [1..150::Int], S.replicate 150 ()) , bench "nf10000" $ nf (uncurry S.zip) (S.fromList [1..10000::Int], S.replicate 10000 ()) - ] ] + ] + , bgroup "fromFunction" + [ bench "ix10000/5000" $ nf (\size -> S.fromFunction size id `S.index` (size `div` 2)) 10000 + , bench "nf100" $ nf (\size -> S.fromFunction size id) 100 + , bench "nf10000" $ nf (\size -> S.fromFunction size id) 10000 + ] + ] -- splitAt+append: repeatedly cut the sequence at a random point -- and rejoin the pieces in the opposite order. From git at git.haskell.org Fri Jan 23 22:42:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:03 +0000 (UTC) Subject: [commit: packages/containers] master: Add tests for Applicative and Monad instances (0decaa1) Message-ID: <20150123224203.328AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/0decaa120039ff4bafbfd4cc62306925a2c31475 >--------------------------------------------------------------- commit 0decaa120039ff4bafbfd4cc62306925a2c31475 Author: David Feuer Date: Thu Dec 18 12:44:57 2014 -0500 Add tests for Applicative and Monad instances Unfortunately, these tests are rather slow, so I hid them behind a SLOW_TESTS macro. I don't know nearly enough about cabal to know how to arrange for tests to be run conditionally, so hopefully someone else can set that up properly. >--------------------------------------------------------------- 0decaa120039ff4bafbfd4cc62306925a2c31475 tests/seq-properties.hs | 28 ++++++++++++++++++++++++++++ 1 file changed, 28 insertions(+) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index def17b3..2b4774d 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -17,6 +17,9 @@ import qualified Prelude import qualified Data.List import Test.QuickCheck hiding ((><)) import Test.QuickCheck.Poly +#ifdef SLOW_TESTS +import Test.QuickCheck.Function +#endif import Test.Framework import Test.Framework.Providers.QuickCheck2 @@ -93,6 +96,11 @@ main = defaultMain , testProperty "zipWith3" prop_zipWith3 , testProperty "zip4" prop_zip4 , testProperty "zipWith4" prop_zipWith4 +#ifdef SLOW_TESTS + , testProperty "<*>" prop_ap + , testProperty "*>" prop_then + , testProperty ">>=" prop_bind +#endif ] ------------------------------------------------------------------------ @@ -588,6 +596,26 @@ prop_zipWith4 xs ys zs ts = toList' (zipWith4 f xs ys zs ts) ~= Data.List.zipWith4 f (toList xs) (toList ys) (toList zs) (toList ts) where f = (,,,) +-- Applicative operations + +#ifdef SLOW_TESTS +prop_ap :: Seq A -> Seq B -> Bool +prop_ap xs ys = + toList' ((,) <$> xs <*> ys) ~= ( (,) <$> toList xs <*> toList ys ) + +prop_then :: Seq A -> Seq B -> Bool +prop_then xs ys = + toList' (xs *> ys) ~= (toList xs *> toList ys) +#endif + +-- Monad operations + +#ifdef SLOW_TESTS +prop_bind :: Seq A -> Fun A (Seq B) -> Bool +prop_bind xs (Fun _ f) = + toList' (xs >>= f) ~= (toList xs >>= toList . f) +#endif + -- Simple test monad data M a = Action Int a From git at git.haskell.org Fri Jan 23 22:42:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:03 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Make travis builds work again (e2d2352) Message-ID: <20150123224203.F3E8A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/e2d2352db9082d20affdc6bba4512d5b1855ef55 >--------------------------------------------------------------- commit e2d2352db9082d20affdc6bba4512d5b1855ef55 Author: Daniel Peebles Date: Thu Mar 20 00:21:16 2014 -0400 Make travis builds work again QuickCheck 2.7 broke it, so we need a tighter upper bound (already fixed in the .cabal file) >--------------------------------------------------------------- e2d2352db9082d20affdc6bba4512d5b1855ef55 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 367c274..53c1778 100644 --- a/.travis.yml +++ b/.travis.yml @@ -29,7 +29,7 @@ before_install: install: - cabal-1.18 update # can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle - - cabal-1.18 install "QuickCheck >=2.4 && <3" "byteorder ==1.0.*" "dlist ==0.5.*" "mtl >=2.0 && <2.2" deepseq + - cabal-1.18 install "QuickCheck >=2.4 && <2.7" "byteorder ==1.0.*" "dlist ==0.5.*" "mtl >=2.0 && <2.2" deepseq script: - cabal-1.18 configure --enable-tests -v2 From git at git.haskell.org Fri Jan 23 22:42:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:04 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Add simple mapWithIndex benchmark. (0f3ac0b) Message-ID: <20150123224204.E41623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/0f3ac0b3e48f49e5565b692f2abcb2219895d145 >--------------------------------------------------------------- commit 0f3ac0b3e48f49e5565b692f2abcb2219895d145 Author: Milan Straka Date: Sun Dec 7 15:43:09 2014 +0100 Add simple mapWithIndex benchmark. >--------------------------------------------------------------- 0f3ac0b3e48f49e5565b692f2abcb2219895d145 benchmarks/Sequence.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index 58e1114..5ae2cd3 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -12,7 +12,8 @@ main = do let s10 = S.fromList [1..10] :: S.Seq Int s100 = S.fromList [1..100] :: S.Seq Int s1000 = S.fromList [1..1000] :: S.Seq Int - rnf [s10, s100, s1000] `seq` return () + s10000 = S.fromList [1..10000] :: S.Seq Int + rnf [s10, s100, s1000, s10000] `seq` return () let g = mkStdGen 1 let rlist n = map (`mod` (n+1)) (take 10000 (randoms g)) :: [Int] r10 = rlist 10 @@ -35,6 +36,11 @@ main = do , bench "nf100" $ nf (\size -> S.fromFunction size id) 100 , bench "nf10000" $ nf (\size -> S.fromFunction size id) 10000 ] + , bgroup "mapWithIndex" + [ bench "ix10000/5000" $ nf (S.mapWithIndex (+)) s10000 + , bench "nf100" $ nf (S.mapWithIndex (+)) s100 + , bench "nf10000" $ nf (S.mapWithIndex (+)) s10000 + ] ] -- splitAt+append: repeatedly cut the sequence at a random point From git at git.haskell.org Fri Jan 23 22:42:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:05 +0000 (UTC) Subject: [commit: packages/containers] master: Remove CPP (b2b55b0) Message-ID: <20150123224205.39BC73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/b2b55b01aa985bb190a3f1580bf55eb2c83eb18f >--------------------------------------------------------------- commit b2b55b01aa985bb190a3f1580bf55eb2c83eb18f Author: David Feuer Date: Fri Dec 19 23:49:35 2014 -0500 Remove CPP >--------------------------------------------------------------- b2b55b01aa985bb190a3f1580bf55eb2c83eb18f tests/seq-properties.hs | 8 -------- 1 file changed, 8 deletions(-) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index 2b4774d..880d772 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -17,9 +17,7 @@ import qualified Prelude import qualified Data.List import Test.QuickCheck hiding ((><)) import Test.QuickCheck.Poly -#ifdef SLOW_TESTS import Test.QuickCheck.Function -#endif import Test.Framework import Test.Framework.Providers.QuickCheck2 @@ -96,11 +94,9 @@ main = defaultMain , testProperty "zipWith3" prop_zipWith3 , testProperty "zip4" prop_zip4 , testProperty "zipWith4" prop_zipWith4 -#ifdef SLOW_TESTS , testProperty "<*>" prop_ap , testProperty "*>" prop_then , testProperty ">>=" prop_bind -#endif ] ------------------------------------------------------------------------ @@ -598,7 +594,6 @@ prop_zipWith4 xs ys zs ts = -- Applicative operations -#ifdef SLOW_TESTS prop_ap :: Seq A -> Seq B -> Bool prop_ap xs ys = toList' ((,) <$> xs <*> ys) ~= ( (,) <$> toList xs <*> toList ys ) @@ -606,15 +601,12 @@ prop_ap xs ys = prop_then :: Seq A -> Seq B -> Bool prop_then xs ys = toList' (xs *> ys) ~= (toList xs *> toList ys) -#endif -- Monad operations -#ifdef SLOW_TESTS prop_bind :: Seq A -> Fun A (Seq B) -> Bool prop_bind xs (Fun _ f) = toList' (xs >>= f) ~= (toList xs >>= toList . f) -#endif -- Simple test monad From git at git.haskell.org Fri Jan 23 22:42:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:06 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Updated README (86ab496) Message-ID: <20150123224206.0C8703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/86ab4960dd5b17ef8454dfd9345f405bd6103f0b >--------------------------------------------------------------- commit 86ab4960dd5b17ef8454dfd9345f405bd6103f0b Author: Daniel Peebles Date: Thu Mar 20 20:09:09 2014 -0400 Updated README >--------------------------------------------------------------- 86ab4960dd5b17ef8454dfd9345f405bd6103f0b README | 205 -------------------------------------------------------------- README.md | 38 ++++++++++++ 2 files changed, 38 insertions(+), 205 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 86ab4960dd5b17ef8454dfd9345f405bd6103f0b From git at git.haskell.org Fri Jan 23 22:42:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:06 +0000 (UTC) Subject: [commit: packages/containers] zip-devel: Direct implementation of fromFunction. (ce7f531) Message-ID: <20150123224206.ED8723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : zip-devel Link : http://git.haskell.org/packages/containers.git/commitdiff/ce7f531605b5f2bb350f36c51a74d9ebd84ff8b6 >--------------------------------------------------------------- commit ce7f531605b5f2bb350f36c51a74d9ebd84ff8b6 Author: Milan Straka Date: Sun Dec 7 16:16:59 2014 +0100 Direct implementation of fromFunction. We avoid using Four Digit, so that elements can be added to the new Seq without forcing a large rebuild. >--------------------------------------------------------------- ce7f531605b5f2bb350f36c51a74d9ebd84ff8b6 Data/Sequence.hs | 23 ++++++++++++++++++++++- 1 file changed, 22 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index f7d551c..4f7eb86 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1429,7 +1429,28 @@ mapWithIndex# f (Seq xs) = Seq $ mapWithIndexTree# (\s (Elem a) -> Elem (f s a)) -- | /O(n)/. Convert a given sequence length and a function representing that -- sequence into a sequence. fromFunction :: Int -> (Int -> a) -> Seq a -fromFunction len f = mapWithIndex (\i _ -> f i) (replicate len ()) +fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with negative len" + | len == 0 = empty + | otherwise = Seq $ create (Elem . f) 1 0 len + where + create :: (Int -> a) -> Int -> Int -> Int -> FingerTree a + create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = case trees of + 1 -> Single $ b i + 2 -> Deep (2*s) (One (b i)) Empty (One (b (i+s))) + 3 -> Deep (3*s) (Two (b i) (b (i+s))) Empty (One (b (i+2*s))) + 4 -> Deep (4*s) (Two (b i) (b (i+s))) Empty (Two (b (i+2*s)) (b (i+3*s))) + 5 -> Deep (5*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Two (b (i+3*s)) (b (i+4*s))) + 6 -> Deep (5*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Three (b (i+3*s)) (b (i+4*s)) (b (i+5*s))) + _ -> case trees `quotRem` 3 of + (trees',1) -> Deep (trees*s) (Two (b i) (b (i+s))) + (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+2*s) (trees'-1)) + (Two (b (i+(2+3*(trees'-1))*s)) (b (i+(3+3*(trees'-1))*s))) + (trees',2) -> Deep (trees*s) (Three (b i) (b (i+s)) (b (i+2*s))) + (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+3*s) (trees'-1)) + (Two (b (i+(3+3*(trees'-1))*s)) (b (i+(4+3*(trees'-1))*s))) + (trees',0) -> Deep (trees*s) (Three (b i) (b (i+s)) (b (i+2*s))) + (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+3*s) (trees'-2)) + (Three (b (i+(3+3*(trees'-2))*s)) (b (i+(4+3*(trees'-2))*s)) (b (i+(5+3*(trees'-2))*s))) -- Splitting From git at git.haskell.org Fri Jan 23 22:42:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:07 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #102 from treeowl/validation (5482318) Message-ID: <20150123224207.4149F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/5482318831df6f67bb3dffca98dfc72d1dcefc7a >--------------------------------------------------------------- commit 5482318831df6f67bb3dffca98dfc72d1dcefc7a Merge: 54c3603 b2b55b0 Author: Milan Straka Date: Sat Dec 20 12:59:45 2014 +0100 Merge pull request #102 from treeowl/validation Add tests for Applicative and Monad instances >--------------------------------------------------------------- 5482318831df6f67bb3dffca98dfc72d1dcefc7a tests/seq-properties.hs | 20 ++++++++++++++++++++ 1 file changed, 20 insertions(+) From git at git.haskell.org Fri Jan 23 22:42:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:08 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Whoops, the .cabal file referred to the README (737332b) Message-ID: <20150123224208.155DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/737332b8d1333a69c457b3488a254d30bba9e613 >--------------------------------------------------------------- commit 737332b8d1333a69c457b3488a254d30bba9e613 Author: Daniel Peebles Date: Thu Mar 20 23:30:27 2014 -0400 Whoops, the .cabal file referred to the README >--------------------------------------------------------------- 737332b8d1333a69c457b3488a254d30bba9e613 bytestring.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/bytestring.cabal b/bytestring.cabal index 5bbae89..4f524b5 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -58,7 +58,7 @@ Bug-reports: https://github.com/haskell/bytestring/issues Tested-With: GHC==7.8.1, GHC==7.6.3, GHC==7.4.2, GHC==7.0.4, GHC==6.12.3 Build-Type: Simple Cabal-Version: >= 1.10 -extra-source-files: README TODO +extra-source-files: README.md TODO source-repository head type: git From git at git.haskell.org Fri Jan 23 22:42:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:09 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6,develop-0.6-questionable,master: Nix the Splittable class; add fromFunction (41cc152) Message-ID: <20150123224209.02C953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/41cc1523f99cecfd93efed16abab28eebd873abb >--------------------------------------------------------------- commit 41cc1523f99cecfd93efed16abab28eebd873abb Author: David Feuer Date: Sat Dec 6 00:23:44 2014 -0500 Nix the Splittable class; add fromFunction Write mapWithIndex using a hand-unboxed mapWithIndex#. Make `split` strict, and add an internal strict `splitAt'`. This helps `zipWith` a little. >--------------------------------------------------------------- 41cc1523f99cecfd93efed16abab28eebd873abb Data/Sequence.hs | 249 +++++++++++++++++++++++++++++++++++++------------------ 1 file changed, 167 insertions(+), 82 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 41cc1523f99cecfd93efed16abab28eebd873abb From git at git.haskell.org Fri Jan 23 22:42:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:09 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #107 from treeowl/fromListN (ae97ceb) Message-ID: <20150123224209.4AABD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/ae97ceb44766fb5e78f23670e09a20a9625b0963 >--------------------------------------------------------------- commit ae97ceb44766fb5e78f23670e09a20a9625b0963 Merge: 5482318 ace8f7f Author: Milan Straka Date: Sat Dec 20 13:06:44 2014 +0100 Merge pull request #107 from treeowl/fromListN Use fromList2 to implement fromListN in IsList >--------------------------------------------------------------- ae97ceb44766fb5e78f23670e09a20a9625b0963 Data/Sequence.hs | 1 + 1 file changed, 1 insertion(+) From git at git.haskell.org Fri Jan 23 22:42:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:10 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Delete prologue.txt (4c5855c) Message-ID: <20150123224210.1DB683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/4c5855c9d30fa66607a1fb1bc406c69003b8ce1d >--------------------------------------------------------------- commit 4c5855c9d30fa66607a1fb1bc406c69003b8ce1d Author: Daniel Peebles Date: Fri Mar 28 20:06:34 2014 -0400 Delete prologue.txt No need for this anymore >--------------------------------------------------------------- 4c5855c9d30fa66607a1fb1bc406c69003b8ce1d prologue.txt | 1 - 1 file changed, 1 deletion(-) diff --git a/prologue.txt b/prologue.txt deleted file mode 100644 index 94c9c63..0000000 --- a/prologue.txt +++ /dev/null @@ -1 +0,0 @@ -This package contains the bytestring library. From git at git.haskell.org Fri Jan 23 22:42:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:11 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Simplify zipWith3 and zipWith4 to reduce code size (58f3597) Message-ID: <20150123224211.0B08A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/58f359787438f18dc7fbfe25f115654bd28ac94b >--------------------------------------------------------------- commit 58f359787438f18dc7fbfe25f115654bd28ac94b Author: David Feuer Date: Wed Dec 10 18:33:27 2014 -0500 Simplify zipWith3 and zipWith4 to reduce code size The performance impact isn't worth the code blowup. Also, fix a bug in `fromFunction`. >--------------------------------------------------------------- 58f359787438f18dc7fbfe25f115654bd28ac94b Data/Sequence.hs | 17 +++++++++++------ 1 file changed, 11 insertions(+), 6 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 29a19b3..62d76b3 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1382,7 +1382,7 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg 3 -> Deep (3*s) (Two (b i) (b (i+s))) Empty (One (b (i+2*s))) 4 -> Deep (4*s) (Two (b i) (b (i+s))) Empty (Two (b (i+2*s)) (b (i+3*s))) 5 -> Deep (5*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Two (b (i+3*s)) (b (i+4*s))) - 6 -> Deep (5*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Three (b (i+3*s)) (b (i+4*s)) (b (i+5*s))) + 6 -> Deep (6*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Three (b (i+3*s)) (b (i+4*s)) (b (i+5*s))) _ -> case trees `quotRem` 3 of (trees',1) -> Deep (trees*s) (Two (b i) (b (i+s))) (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+2*s) (trees'-1)) @@ -1937,12 +1937,16 @@ zip = zipWith (,) -- For example, @zipWith (+)@ is applied to two sequences to take the -- sequence of corresponding sums. zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c -zipWith f s1 s2 = splitMap splitAt' (\s a -> f a (getSingleton s)) s2' s1' +zipWith f s1 s2 = zipWith' f s1' s2' where minLen = min (length s1) (length s2) s1' = take minLen s1 s2' = take minLen s2 +-- | A version of zipWith that assumes the sequences have the same length. +zipWith' :: (a -> b -> c) -> Seq a -> Seq b -> Seq c +zipWith' f s1 s2 = splitMap splitAt' (\s a -> f a (getSingleton s)) s2 s1 + -- | /O(min(n1,n2,n3))/. 'zip3' takes three sequences and returns a -- sequence of triples, analogous to 'zip'. zip3 :: Seq a -> Seq b -> Seq c -> Seq (a,b,c) @@ -1952,14 +1956,16 @@ zip3 = zipWith3 (,,) -- three elements, as well as three sequences and returns a sequence of -- their point-wise combinations, analogous to 'zipWith'. zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d -zipWith3 f s1 s2 s3 = splitMap (\i (s,t) -> case (splitAt' i s, splitAt' i t) of ((s', s''), (t', t'')) -> ((s',t'),(s'',t''))) - (\(b,c) a -> f a (getSingleton b) (getSingleton c)) (s2',s3') s1' +zipWith3 f s1 s2 s3 = zipWith' ($) (zipWith' f s1' s2') s3' where minLen = minimum [length s1, length s2, length s3] s1' = take minLen s1 s2' = take minLen s2 s3' = take minLen s3 +zipWith3' :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d +zipWith3' f s1 s2 s3 = zipWith' ($) (zipWith' f s1 s2) s3 + -- | /O(min(n1,n2,n3,n4))/. 'zip4' takes four sequences and returns a -- sequence of quadruples, analogous to 'zip'. zip4 :: Seq a -> Seq b -> Seq c -> Seq d -> Seq (a,b,c,d) @@ -1969,8 +1975,7 @@ zip4 = zipWith4 (,,,) -- four elements, as well as four sequences and returns a sequence of -- their point-wise combinations, analogous to 'zipWith'. zipWith4 :: (a -> b -> c -> d -> e) -> Seq a -> Seq b -> Seq c -> Seq d -> Seq e -zipWith4 f s1 s2 s3 s4 = splitMap (\i (s,t,u) -> case (splitAt' i s, splitAt' i t, splitAt' i u) of ((s',s''),(t',t''),(u',u'')) -> ((s',t',u'),(s'',t'',u''))) - (\(b, c, d) a -> f a (getSingleton b) (getSingleton c) (getSingleton d)) (s2',s3',s4') s1' +zipWith4 f s1 s2 s3 s4 = zipWith' ($) (zipWith3' f s1' s2' s3') s4' where minLen = minimum [length s1, length s2, length s3, length s4] s1' = take minLen s1 From git at git.haskell.org Fri Jan 23 22:42:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:11 +0000 (UTC) Subject: [commit: packages/containers] master: Reimplement `<*>` (38b1b81) Message-ID: <20150123224211.542913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/38b1b81c8b5536525d0daad9bd8ee9821a3fb929 >--------------------------------------------------------------- commit 38b1b81c8b5536525d0daad9bd8ee9821a3fb929 Author: David Feuer Date: Thu Dec 18 16:31:10 2014 -0500 Reimplement `<*>` Use `coerce` for the `Functor` instance of `Elem` Using `fmap = coerce` for `Elem` speeds up `<*>` by somewhere around 20%. Benchmark results: OLD: benchmarking <*>/ix1000/500000 time 11.47 ms (11.37 ms .. 11.59 ms) 0.999 R? (0.998 R? .. 1.000 R?) mean 11.61 ms (11.52 ms .. 11.73 ms) std dev 279.9 ?s (209.5 ?s .. 385.6 ?s) benchmarking <*>/nf100/2500/rep time 8.530 ms (8.499 ms .. 8.568 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 8.511 ms (8.498 ms .. 8.528 ms) std dev 40.40 ?s (28.55 ?s .. 63.84 ?s) benchmarking <*>/nf100/2500/ff time 27.13 ms (26.16 ms .. 28.70 ms) 0.994 R? (0.988 R? .. 1.000 R?) mean 26.49 ms (26.29 ms .. 27.43 ms) std dev 697.1 ?s (153.0 ?s .. 1.443 ms) benchmarking <*>/nf500/500/rep time 8.421 ms (8.331 ms .. 8.491 ms) 0.991 R? (0.967 R? .. 1.000 R?) mean 8.518 ms (8.417 ms .. 9.003 ms) std dev 529.9 ?s (40.37 ?s .. 1.176 ms) variance introduced by outliers: 32% (moderately inflated) benchmarking <*>/nf500/500/ff time 33.71 ms (33.58 ms .. 33.86 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 33.69 ms (33.62 ms .. 33.76 ms) std dev 150.0 ?s (119.0 ?s .. 191.0 ?s) benchmarking <*>/nf2500/100/rep time 8.390 ms (8.259 ms .. 8.456 ms) 0.997 R? (0.992 R? .. 1.000 R?) mean 8.544 ms (8.441 ms .. 8.798 ms) std dev 402.6 ?s (21.25 ?s .. 714.9 ?s) variance introduced by outliers: 23% (moderately inflated) benchmarking <*>/nf2500/100/ff time 53.69 ms (53.33 ms .. 54.08 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 53.59 ms (53.38 ms .. 53.75 ms) std dev 341.2 ?s (231.7 ?s .. 473.9 ?s) NEW benchmarking <*>/ix1000/500000 time 2.688 ?s (2.607 ?s .. 2.798 ?s) 0.994 R? (0.988 R? .. 1.000 R?) mean 2.632 ?s (2.607 ?s .. 2.715 ?s) std dev 129.9 ns (65.93 ns .. 242.8 ns) variance introduced by outliers: 64% (severely inflated) benchmarking <*>/nf100/2500/rep time 8.371 ms (8.064 ms .. 8.535 ms) 0.983 R? (0.947 R? .. 1.000 R?) mean 8.822 ms (8.590 ms .. 9.463 ms) std dev 991.2 ?s (381.3 ?s .. 1.809 ms) variance introduced by outliers: 61% (severely inflated) benchmarking <*>/nf100/2500/ff time 22.84 ms (22.74 ms .. 22.94 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 22.78 ms (22.71 ms .. 22.86 ms) std dev 183.3 ?s (116.3 ?s .. 291.3 ?s) benchmarking <*>/nf500/500/rep time 8.320 ms (8.102 ms .. 8.514 ms) 0.995 R? (0.990 R? .. 0.999 R?) mean 8.902 ms (8.675 ms .. 9.407 ms) std dev 952.4 ?s (435.5 ?s .. 1.672 ms) variance introduced by outliers: 58% (severely inflated) benchmarking <*>/nf500/500/ff time 24.50 ms (24.41 ms .. 24.58 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 24.44 ms (24.41 ms .. 24.48 ms) std dev 75.08 ?s (50.16 ?s .. 111.3 ?s) benchmarking <*>/nf2500/100/rep time 8.419 ms (8.366 ms .. 8.458 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 8.571 ms (8.525 ms .. 8.670 ms) std dev 179.5 ?s (112.0 ?s .. 278.1 ?s) benchmarking <*>/nf2500/100/ff time 24.14 ms (24.07 ms .. 24.26 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 24.11 ms (24.07 ms .. 24.17 ms) std dev 103.8 ?s (68.34 ?s .. 142.0 ?s) >--------------------------------------------------------------- 38b1b81c8b5536525d0daad9bd8ee9821a3fb929 Data/Sequence.hs | 261 ++++++++++++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 258 insertions(+), 3 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 38b1b81c8b5536525d0daad9bd8ee9821a3fb929 From git at git.haskell.org Fri Jan 23 22:42:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:12 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Use S.foldl' on each chunk when strictly folding a lazy bytestring. (e97df17) Message-ID: <20150123224212.269DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/e97df17c0c63dc2503e8e43b51a581f27166d04f >--------------------------------------------------------------- commit e97df17c0c63dc2503e8e43b51a581f27166d04f Author: Lemmih Date: Sun May 11 16:04:57 2014 +0800 Use S.foldl' on each chunk when strictly folding a lazy bytestring. >--------------------------------------------------------------- e97df17c0c63dc2503e8e43b51a581f27166d04f Data/ByteString/Lazy.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/ByteString/Lazy.hs b/Data/ByteString/Lazy.hs index 22ba1ee..aa1cee5 100644 --- a/Data/ByteString/Lazy.hs +++ b/Data/ByteString/Lazy.hs @@ -479,7 +479,7 @@ foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a foldl' f z = go z where go a _ | a `seq` False = undefined go a Empty = a - go a (Chunk c cs) = go (S.foldl f a c) cs + go a (Chunk c cs) = go (S.foldl' f a c) cs {-# INLINE foldl' #-} -- | 'foldr', applied to a binary operator, a starting value From git at git.haskell.org Fri Jan 23 22:42:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:13 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Revert the fromFunction shallowing (d8c9008) Message-ID: <20150123224213.128C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/d8c90085755397b0180a349385fdd1b1820ae1aa >--------------------------------------------------------------- commit d8c90085755397b0180a349385fdd1b1820ae1aa Author: David Feuer Date: Thu Dec 11 21:21:38 2014 -0500 Revert the fromFunction shallowing I don't actually know whether we want it shallower or "safer". Make `fromFunction` easier to read. >--------------------------------------------------------------- d8c90085755397b0180a349385fdd1b1820ae1aa Data/Sequence.hs | 42 +++++++++++++++++++++++------------------- 1 file changed, 23 insertions(+), 19 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 62d76b3..f3fbbe7 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1374,25 +1374,29 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg #else | otherwise = Seq $ create (Elem . f) 1 0 len #endif - where - create :: (Int -> a) -> Int -> Int -> Int -> FingerTree a - create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = i `seq` s `seq` case trees of - 1 -> Single $ b i - 2 -> Deep (2*s) (One (b i)) Empty (One (b (i+s))) - 3 -> Deep (3*s) (Two (b i) (b (i+s))) Empty (One (b (i+2*s))) - 4 -> Deep (4*s) (Two (b i) (b (i+s))) Empty (Two (b (i+2*s)) (b (i+3*s))) - 5 -> Deep (5*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Two (b (i+3*s)) (b (i+4*s))) - 6 -> Deep (6*s) (Three (b i) (b (i+s)) (b (i+2*s))) Empty (Three (b (i+3*s)) (b (i+4*s)) (b (i+5*s))) - _ -> case trees `quotRem` 3 of - (trees',1) -> Deep (trees*s) (Two (b i) (b (i+s))) - (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+2*s) (trees'-1)) - (Two (b (i+(2+3*(trees'-1))*s)) (b (i+(3+3*(trees'-1))*s))) - (trees',2) -> Deep (trees*s) (Three (b i) (b (i+s)) (b (i+2*s))) - (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+3*s) (trees'-1)) - (Two (b (i+(3+3*(trees'-1))*s)) (b (i+(4+3*(trees'-1))*s))) - (trees',0) -> Deep (trees*s) (Three (b i) (b (i+s)) (b (i+2*s))) - (create (\j -> Node3 (3*s) (b j) (b (j+s)) (b (j+2*s))) (3*s) (i+3*s) (trees'-2)) - (Three (b (i+(3+3*(trees'-2))*s)) (b (i+(4+3*(trees'-2))*s)) (b (i+(5+3*(trees'-2))*s))) + where + create :: (Int -> a) -> Int -> Int -> Int -> FingerTree a + create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = i `seq` s `seq` case trees of + 1 -> Single $ b i + 2 -> Deep (2*s) (One (b i)) Empty (One (b (i+s))) + 3 -> Deep (3*s) (createTwo b s i) Empty (One (b (i+2*s))) + 4 -> Deep (4*s) (createTwo b s i) Empty (createTwo b s (i+2*s)) + 5 -> Deep (5*s) (createThree b s i) Empty (createTwo b s (i+3*s)) + 6 -> Deep (6*s) (createThree b s i) Empty (createThree b s (i+3*s)) + _ -> case trees `quotRem` 3 of + (trees', 1) -> Deep (trees*s) (createTwo b s i) + (create mb (3*s) (i+2*s) (trees'-1)) + (createTwo b s (i+(2+3*(trees'-1))*s)) + (trees', 2) -> Deep (trees*s) (createThree b s i) + (create mb (3*s) (i+3*s) (trees'-1)) + (createTwo b s (i+(3+3*(trees'-1))*s)) + (trees', 0) -> Deep (trees*s) (createThree b s i) + (create mb (3*s) (i+3*s) (trees'-2)) + (createThree b s (i+(3+3*(trees'-2))*s)) + where + createTwo b s i = Two (b i) (b (i + s)) + createThree b s i = Three (b i) (b (i + s)) (b (i + s + s)) + mb j = Node3 (3*s) (b j) (b (j + s)) (b (j + 2*s)) -- Splitting From git at git.haskell.org Fri Jan 23 22:42:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:13 +0000 (UTC) Subject: [commit: packages/containers] master: Add Applicative benchmarks (8b47db3) Message-ID: <20150123224213.5AA443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/8b47db3af79c31fe5434e95143242a2ef3e1e184 >--------------------------------------------------------------- commit 8b47db3af79c31fe5434e95143242a2ef3e1e184 Author: David Feuer Date: Sat Dec 20 15:02:05 2014 -0500 Add Applicative benchmarks >--------------------------------------------------------------- 8b47db3af79c31fe5434e95143242a2ef3e1e184 benchmarks/Sequence.hs | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index b6b82fa..a152c3b 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -1,6 +1,7 @@ -- > ghc -DTESTING --make -O2 -fforce-recomp -i.. Sequence.hs module Main where +import Control.Applicative import Control.DeepSeq import Criterion.Main import Data.List (foldl') @@ -44,6 +45,22 @@ main = do , bench "nf1000" $ nf (\s -> S.fromFunction s (+1)) 1000 , bench "nf10000" $ nf (\s -> S.fromFunction s (+1)) 10000 ] + , bgroup "<*>" + [ bench "ix1000/500000" $ + nf (\s -> ((+) <$> s <*> s) `S.index` (S.length s `div` 2)) (S.fromFunction 1000 (+1)) + , bench "nf100/2500/rep" $ + nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (100,2500) + , bench "nf100/2500/ff" $ + nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (100,2500) + , bench "nf500/500/rep" $ + nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (500,500) + , bench "nf500/500/ff" $ + nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (500,500) + , bench "nf2500/100/rep" $ + nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (2500,100) + , bench "nf2500/100/ff" $ + nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (2500,100) + ] ] -- splitAt+append: repeatedly cut the sequence at a random point From git at git.haskell.org Fri Jan 23 22:42:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:14 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Update .travis.yml description (38540d3) Message-ID: <20150123224214.2F8B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/38540d332935dd71127a1e28875caedf54124f38 >--------------------------------------------------------------- commit 38540d332935dd71127a1e28875caedf54124f38 Author: Herbert Valerio Riedel Date: Wed May 28 09:04:00 2014 +0200 Update .travis.yml description This adds GHC 7.8.2 and drops GHC 6.12.3 plus a few interim GHC releases from the GHC config matrix to reduce the resource usage on Travis. (Also, keeping support for GHC 6.12.3 is getting more and more tedious in 2014) >--------------------------------------------------------------- 38540d332935dd71127a1e28875caedf54124f38 .travis.yml | 60 ++++++++++++++++++++++++++++++------------------------------ 1 file changed, 30 insertions(+), 30 deletions(-) diff --git a/.travis.yml b/.travis.yml index 53c1778..f50da28 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,40 +1,40 @@ -# NB: don't set `language: haskell` here -# See https://github.com/hvr/multi-ghc-travis for more information - env: - - GHCVER=6.12.3 -# - GHCVER=7.0.1 # disabled due to internal GHC failure - - GHCVER=7.0.2 - - GHCVER=7.0.3 - - GHCVER=7.0.4 - - GHCVER=7.2.1 - - GHCVER=7.2.2 - - GHCVER=7.4.1 - - GHCVER=7.4.2 - - GHCVER=7.6.1 - - GHCVER=7.6.2 - - GHCVER=7.6.3 - - GHCVER=head + - GHCVER=7.0.4 CABALVER=1.16 + # we have to use CABALVER=1.16 for GHC<7.6 as well, as there's + # no package for earlier cabal versions in the PPA + - GHCVER=7.2.2 CABALVER=1.16 + - GHCVER=7.4.2 CABALVER=1.16 + - GHCVER=7.6.3 CABALVER=1.16 + - GHCVER=7.8.2 CABALVER=1.18 + - GHCVER=head CABALVER=1.20 matrix: allow_failures: - - env: GHCVER=head + - env: GHCVER=head CABALVER=1.20 before_install: - - sudo add-apt-repository -y ppa:hvr/ghc - - sudo apt-get update - - sudo apt-get install cabal-install-1.18 ghc-$GHCVER - - export PATH=/opt/ghc/$GHCVER/bin:$PATH + - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH + - cabal --version install: - - cabal-1.18 update -# can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle - - cabal-1.18 install "QuickCheck >=2.4 && <2.7" "byteorder ==1.0.*" "dlist ==0.5.*" "mtl >=2.0 && <2.2" deepseq + - travis_retry cabal update + # can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle + - cabal install "QuickCheck >=2.4 && <2.7" "byteorder ==1.0.*" "dlist ==0.5.*" "mtl >=2.0 && <2.2" deepseq script: - - cabal-1.18 configure --enable-tests -v2 - - cabal-1.18 build - - cabal-1.18 test -# "cabal check" disabled due to -O2 warning -# - cabal-1.18 check - - cabal-1.18 sdist + - cabal configure --enable-tests -v2 + - cabal build + - cabal test + - cabal sdist + # "cabal check" disabled due to -O2 warning + - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; + cd dist/; + if [ -f "$SRC_TGZ" ]; then + cabal install "$SRC_TGZ"; + else + echo "expected '$SRC_TGZ' not found"; + exit 1; + fi From git at git.haskell.org Fri Jan 23 22:42:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:15 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Rename strictness tests to match other test names. (7e42d81) Message-ID: <20150123224215.1A0EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/7e42d81350aac6db1aa52180572a117e67b168b3 >--------------------------------------------------------------- commit 7e42d81350aac6db1aa52180572a117e67b168b3 Author: Milan Straka Date: Sun Dec 14 15:56:15 2014 +0100 Rename strictness tests to match other test names. >--------------------------------------------------------------- 7e42d81350aac6db1aa52180572a117e67b168b3 containers.cabal | 4 ++-- tests/{IntMapStrictness.hs => intmap-strictness.hs} | 0 tests/{MapStrictness.hs => map-strictness.hs} | 0 3 files changed, 2 insertions(+), 2 deletions(-) diff --git a/containers.cabal b/containers.cabal index 050257c..ae7e247 100644 --- a/containers.cabal +++ b/containers.cabal @@ -211,7 +211,7 @@ Test-suite seq-properties test-suite map-strictness-properties hs-source-dirs: tests, . - main-is: MapStrictness.hs + main-is: map-strictness.hs type: exitcode-stdio-1.0 build-depends: @@ -228,7 +228,7 @@ test-suite map-strictness-properties test-suite intmap-strictness-properties hs-source-dirs: tests, . - main-is: IntMapStrictness.hs + main-is: intmap-strictness.hs type: exitcode-stdio-1.0 build-depends: diff --git a/tests/IntMapStrictness.hs b/tests/intmap-strictness.hs similarity index 100% rename from tests/IntMapStrictness.hs rename to tests/intmap-strictness.hs diff --git a/tests/MapStrictness.hs b/tests/map-strictness.hs similarity index 100% rename from tests/MapStrictness.hs rename to tests/map-strictness.hs From git at git.haskell.org Fri Jan 23 22:42:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:15 +0000 (UTC) Subject: [commit: packages/containers] master: Exploit some invariants (41b7cb4) Message-ID: <20150123224215.6261B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/41b7cb48a1f61911651fc4ea40ac552332de9e96 >--------------------------------------------------------------- commit 41b7cb48a1f61911651fc4ea40ac552332de9e96 Author: Bertram Felgenhauer Date: Sun Dec 21 16:37:11 2014 +0100 Exploit some invariants Consequently, get rid of ApState. This speeds up the immediate-indexing test substantially: Old: benchmarking <*>/ix1000/500000 time 2.688 ?s (2.607 ?s .. 2.798 ?s) 0.994 R? (0.988 R? .. 1.000 R?) mean 2.632 ?s (2.607 ?s .. 2.715 ?s) std dev 129.9 ns (65.93 ns .. 242.8 ns) variance introduced by outliers: 64% (severely inflated) New: benchmarking <*>/ix1000/500000 time 1.410 ?s (1.402 ?s .. 1.417 ?s) 1.000 R? (1.000 R? .. 1.000 R?) mean 1.417 ?s (1.411 ?s .. 1.425 ?s) std dev 21.45 ns (16.80 ns .. 31.73 ns) variance introduced by outliers: 14% (moderately inflated) >--------------------------------------------------------------- 41b7cb48a1f61911651fc4ea40ac552332de9e96 Data/Sequence.hs | 120 ++++++++++++++++++++++--------------------------------- 1 file changed, 47 insertions(+), 73 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 7a2de82..0a64c3e 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -277,7 +277,7 @@ apShort :: Seq (a -> b) -> Seq a -> Seq b apShort (Seq fs) xs = Seq $ case toList xs of [a,b] -> ap2FT fs (a,b) [a,b,c] -> ap3FT fs (a,b,c) - _ -> error "apShort: not 2-6" + _ -> error "apShort: not 2-3" ap2FT :: FingerTree (Elem (a->b)) -> (a,a) -> FingerTree (Elem b) ap2FT fs (x,y) = Deep (size fs * 2) @@ -298,104 +298,85 @@ ap3FT fs (x,y,z) = Deep (size fs * 3) -- <*> when the length of each argument is at least four. apty :: Seq (a -> b) -> Seq a -> Seq b apty (Seq fs) (Seq xs at Deep{}) = Seq $ - runApState (fmap firstf) (fmap lastf) fmap fs' (ApState xs' xs' xs') + Deep (s' * size fs) + (fmap (fmap firstf) pr') + (aptyMiddle (fmap firstf) (fmap lastf) fmap fs' xs') + (fmap (fmap lastf) sf') where (Elem firstf, fs', Elem lastf) = trimTree fs - xs' = rigidify xs + xs'@(Deep s' pr' _m' sf') = rigidify xs apty _ _ = error "apty: expects a Deep constructor" -data ApState a = ApState (FingerTree a) (FingerTree a) (FingerTree a) - --- | 'runApState' uses three copies of the @xs@ tree to produce the @fs<*>xs@ --- tree. It pulls left digits off the left tree, right digits off the right tree, --- and squashes down the other four digits. Once it gets to the bottom, it turns --- the middle tree into a 2-3 tree, applies 'mapMulFT' to produce the main body, --- and glues all the pieces together. -runApState +-- | 'aptyMiddle' does most of the hard work of computing @fs<*>xs at . +-- It produces the center part of a finger tree, with a prefix corresponding +-- to the prefix of @xs@ and a suffix corresponding to the suffix of @xs@ +-- omitted; the missing suffix and prefix are added by the caller. +-- For the recursive call, it squashes the prefix and the suffix into +-- the center tree. Once it gets to the bottom, it turns the tree into +-- a 2-3 tree, applies 'mapMulFT' to produce the main body, and glues all +-- the pieces together. +aptyMiddle :: Sized c => (c -> d) -> (c -> d) -> ((a -> b) -> c -> d) -> FingerTree (Elem (a -> b)) - -> ApState c - -> FingerTree d + -> FingerTree c + -> FingerTree (Node d) -- Not at the bottom yet -runApState firstf +aptyMiddle firstf lastf map23 fs - (ApState - (Deep sl - prl - (Deep sml prml mml sfml) - sfl) - (Deep sm - prm - (Deep _smm prmm mmm sfmm) - sfm) - (Deep sr - prr - (Deep smr prmr mmr sfmr) - sfr)) - = Deep (sl + sr + sm * size fs) - (fmap firstf prl) - (runApState (fmap firstf) + (Deep s pr (Deep sm prm mm sfm) sf) + = Deep (sm + s * (size fs + 1)) -- note: sm = s - size pr - size sf + (fmap (fmap firstf) prm) + (aptyMiddle (fmap firstf) (fmap lastf) (\f -> fmap (map23 f)) fs - nextState) - (fmap lastf sfr) - where nextState = - ApState - (Deep (sml + size sfl) prml mml (squashR sfml sfl)) - (Deep sm (squashL prm prmm) mmm (squashR sfmm sfm)) - (Deep (smr + size prr) (squashL prr prmr) mmr sfmr) + (Deep s (squashL pr prm) mm (squashR sfm sf))) + (fmap (fmap lastf) sfm) -- At the bottom -runApState firstf +aptyMiddle firstf lastf map23 fs - (ApState - (Deep sl prl ml sfl) - (Deep sm prm mm sfm) - (Deep sr prr mr sfr)) - = Deep (sl + sr + sm * size fs) - (fmap firstf prl) - ((fmap (fmap firstf) ml `snocTree` fmap firstf (digitToNode sfl)) - `appendTree0` middle `appendTree0` - (fmap lastf (digitToNode prr) `consTree` fmap (fmap lastf) mr)) - (fmap lastf sfr) - where middle = case trimTree $ mapMulFT sm (\(Elem f) -> fmap (fmap (map23 f)) converted) fs of + (Deep s pr m sf) + = (fmap (fmap firstf) m `snocTree` fmap firstf (digitToNode sf)) + `appendTree0` middle `appendTree0` + (fmap lastf (digitToNode pr) `consTree` fmap (fmap lastf) m) + where middle = case trimTree $ mapMulFT s (\(Elem f) -> fmap (fmap (map23 f)) converted) fs of (firstMapped, restMapped, lastMapped) -> Deep (size firstMapped + size restMapped + size lastMapped) (nodeToDigit firstMapped) restMapped (nodeToDigit lastMapped) - converted = case mm of - Empty -> Node2 sm lconv rconv - Single q -> Node3 sm lconv q rconv - Deep{} -> error "runApState: a tree is shallower than the middle tree" - lconv = digitToNode prm - rconv = digitToNode sfm + converted = case m of + Empty -> Node2 s lconv rconv + Single q -> Node3 s lconv q rconv + Deep{} -> error "aptyMiddle: impossible" + lconv = digitToNode pr + rconv = digitToNode sf -runApState _ _ _ _ _ = error "runApState: ApState must hold Deep finger trees of the same depth" +aptyMiddle _ _ _ _ _ = error "aptyMiddle: expected Deep finger tree" {-# SPECIALIZE - runApState + aptyMiddle :: (Node c -> d) -> (Node c -> d) -> ((a -> b) -> Node c -> d) -> FingerTree (Elem (a -> b)) - -> ApState (Node c) - -> FingerTree d + -> FingerTree (Node c) + -> FingerTree (Node d) #-} {-# SPECIALIZE - runApState + aptyMiddle :: (Elem c -> d) -> (Elem c -> d) -> ((a -> b) -> Elem c -> d) -> FingerTree (Elem (a -> b)) - -> ApState (Elem c) - -> FingerTree d + -> FingerTree (Elem c) + -> FingerTree (Node d) #-} digitToNode :: Sized a => Digit a -> Node a @@ -2096,16 +2077,9 @@ reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) -- Mapping with a splittable value ------------------------------------------------------------------------ --- For zipping, and probably also for (<*>), it is useful to build a result by +-- For zipping, it is useful to build a result by -- traversing a sequence while splitting up something else. For zipping, we --- traverse the first sequence while splitting up the second [and third [and --- fourth]]. For fs <*> xs, we hope to traverse --- --- > replicate (length fs * length xs) () --- --- while splitting something essentially equivalent to --- --- > fmap (\f -> fmap f xs) fs +-- traverse the first sequence while splitting up the second. -- -- What makes all this crazy code a good idea: -- @@ -2129,8 +2103,8 @@ reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) -- they're actually needed. We do the same thing for Digits (splitting into -- between one and four pieces) and Nodes (splitting into two or three). The -- ultimate result is that we can index into, or split at, any location in zs --- in O((log(min{i,n-i}))^2) time *immediately*, while still being able to --- force all the thunks in O(n) time. +-- in polylogarithmic time *immediately*, while still being able to force all +-- the thunks in O(n) time. -- -- Benchmark info, and alternatives: -- From git at git.haskell.org Fri Jan 23 22:42:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:16 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Add `FlexibleContexts` to fix compilation with GHC HEAD (6cf683d) Message-ID: <20150123224216.3B0C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/6cf683d78ab1272c0da0c20944c7eeb4a367bc48 >--------------------------------------------------------------- commit 6cf683d78ab1272c0da0c20944c7eeb4a367bc48 Author: Herbert Valerio Riedel Date: Wed May 28 10:48:21 2014 +0200 Add `FlexibleContexts` to fix compilation with GHC HEAD This fixes the compile error tests/builder/Data/ByteString/Builder/Tests.hs:210:5: Non type-variable argument in the constraint: MonadWriter (D.DList Word8) m (Use FlexibleContexts to permit this) In the context: (MonadWriter (D.DList Word8) m, MonadState Int m) While checking the inferred type for ?renderAction? ... See also http://permalink.gmane.org/gmane.comp.lang.haskell.glasgow.user/24612 for more details >--------------------------------------------------------------- 6cf683d78ab1272c0da0c20944c7eeb4a367bc48 tests/builder/Data/ByteString/Builder/Tests.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/builder/Data/ByteString/Builder/Tests.hs b/tests/builder/Data/ByteString/Builder/Tests.hs index 49f1f01..793248a 100644 --- a/tests/builder/Data/ByteString/Builder/Tests.hs +++ b/tests/builder/Data/ByteString/Builder/Tests.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, ScopedTypeVariables, BangPatterns #-} +{-# LANGUAGE CPP, FlexibleContexts, ScopedTypeVariables, BangPatterns #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- | From git at git.haskell.org Fri Jan 23 22:42:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:17 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #104 from treeowl/ap (2546efe) Message-ID: <20150123224217.6AEB93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/2546efeadaca6c078b5ddc23557af71fd3d6966d >--------------------------------------------------------------- commit 2546efeadaca6c078b5ddc23557af71fd3d6966d Merge: ae97ceb 41b7cb4 Author: Milan Straka Date: Mon Dec 22 11:13:16 2014 +0100 Merge pull request #104 from treeowl/ap Make <*> fast >--------------------------------------------------------------- 2546efeadaca6c078b5ddc23557af71fd3d6966d Data/Sequence.hs | 257 ++++++++++++++++++++++++++++++++++++++++++++++--- benchmarks/Sequence.hs | 17 ++++ 2 files changed, 260 insertions(+), 14 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:17 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Use pre-evaluated sequences in benchmarks. (999851e) Message-ID: <20150123224217.221CB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/999851e33acde2db08b06cf8d0331f37bbeb3c0b >--------------------------------------------------------------- commit 999851e33acde2db08b06cf8d0331f37bbeb3c0b Author: Milan Straka Date: Sun Dec 14 16:26:42 2014 +0100 Use pre-evaluated sequences in benchmarks. >--------------------------------------------------------------- 999851e33acde2db08b06cf8d0331f37bbeb3c0b benchmarks/Sequence.hs | 17 ++++++++++++----- 1 file changed, 12 insertions(+), 5 deletions(-) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index ccaca6c..8fd1fcf 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -12,13 +12,20 @@ main = do let s10 = S.fromList [1..10] :: S.Seq Int s100 = S.fromList [1..100] :: S.Seq Int s1000 = S.fromList [1..1000] :: S.Seq Int - rnf [s10, s100, s1000] `seq` return () + s10000 = S.fromList [1..10000] :: S.Seq Int + rnf [s10, s100, s1000, s10000] `seq` return () let g = mkStdGen 1 let rlist n = map (`mod` (n+1)) (take 10000 (randoms g)) :: [Int] r10 = rlist 10 r100 = rlist 100 r1000 = rlist 1000 - rnf [r10, r100, r1000] `seq` return () + r10000 = rlist 10000 + rnf [r10, r100, r1000, r10000] `seq` return () + let u10 = S.replicate 10 () :: S.Seq () + u100 = S.replicate 100 () :: S.Seq () + u1000 = S.replicate 1000 () :: S.Seq () + u10000 = S.replicate 10000 () :: S.Seq () + rnf [u10, u100, u1000, u10000] `seq` return () defaultMain [ bgroup "splitAt/append" [ bench "10" $ nf (shuffle r10) s10 @@ -26,9 +33,9 @@ main = do , bench "1000" $ nf (shuffle r1000) s1000 ] , bgroup "zip" - [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (S.replicate 10000 (), S.fromList [1..10000::Int]) - , bench "nf150" $ nf (uncurry S.zip) (S.fromList [1..150::Int], S.replicate 150 ()) - , bench "nf10000" $ nf (uncurry S.zip) (S.fromList [1..10000::Int], S.replicate 10000 ()) + [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (s10000, u10000) + , bench "nf100" $ nf (uncurry S.zip) (s100, u100) + , bench "nf10000" $ nf (uncurry S.zip) (s10000, u10000) ] ] -- splitAt+append: repeatedly cut the sequence at a random point From git at git.haskell.org Fri Jan 23 22:42:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:18 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Add GHC 7.8.3 to the Travis build-matrix (b916e3b) Message-ID: <20150123224218.450183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/b916e3b4e9c2baf67e34237cae1636a4bdb5bfac >--------------------------------------------------------------- commit b916e3b4e9c2baf67e34237cae1636a4bdb5bfac Author: Herbert Valerio Riedel Date: Wed Jun 4 10:20:54 2014 +0200 Add GHC 7.8.3 to the Travis build-matrix Right now `ghc-7.8.3` is just a snapshot of the soon-to-be-7.8.3 `ghc-7.8` branch >--------------------------------------------------------------- b916e3b4e9c2baf67e34237cae1636a4bdb5bfac .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index f50da28..413f89b 100644 --- a/.travis.yml +++ b/.travis.yml @@ -6,6 +6,7 @@ env: - GHCVER=7.4.2 CABALVER=1.16 - GHCVER=7.6.3 CABALVER=1.16 - GHCVER=7.8.2 CABALVER=1.18 + - GHCVER=7.8.3 CABALVER=1.18 - GHCVER=head CABALVER=1.20 matrix: From git at git.haskell.org Fri Jan 23 22:42:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:19 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Update URL of the fingertree paper. (7ffc123) Message-ID: <20150123224219.2A68E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/7ffc123000d82a676a23e0ce5e916a871598610f >--------------------------------------------------------------- commit 7ffc123000d82a676a23e0ce5e916a871598610f Author: Milan Straka Date: Sun Dec 14 16:40:11 2014 +0100 Update URL of the fingertree paper. >--------------------------------------------------------------- 7ffc123000d82a676a23e0ce5e916a871598610f Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index f3fbbe7..9f3f543 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -40,7 +40,7 @@ -- * Ralf Hinze and Ross Paterson, -- \"Finger trees: a simple general-purpose data structure\", -- /Journal of Functional Programming/ 16:2 (2006) pp 197-217. --- +-- -- -- /Note/: Many of these operations have the same names as similar -- operations on lists in the "Prelude". The ambiguity may be resolved From git at git.haskell.org Fri Jan 23 22:42:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:19 +0000 (UTC) Subject: [commit: packages/containers] master: Bump version number to 0.5.6.2 (924fafe) Message-ID: <20150123224219.7310C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/924fafe1030301ee1d62d7acd576e86b50251157 >--------------------------------------------------------------- commit 924fafe1030301ee1d62d7acd576e86b50251157 Author: Milan Straka Date: Mon Dec 22 11:54:05 2014 +0100 Bump version number to 0.5.6.2 >--------------------------------------------------------------- 924fafe1030301ee1d62d7acd576e86b50251157 containers.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/containers.cabal b/containers.cabal index 169507a..c5d7523 100644 --- a/containers.cabal +++ b/containers.cabal @@ -1,5 +1,5 @@ name: containers -version: 0.5.6.1 +version: 0.5.6.2 license: BSD3 license-file: LICENSE maintainer: fox at ucw.cz From git at git.haskell.org Fri Jan 23 22:42:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:20 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Constrain version of QuickCheck for compatibility (f04e6f5) Message-ID: <20150123224220.4E8223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/f04e6f563dc5275bdefe84984a4e50695919e5a0 >--------------------------------------------------------------- commit f04e6f563dc5275bdefe84984a4e50695919e5a0 Author: Bryan O'Sullivan Date: Fri Jun 6 13:23:09 2014 -0700 Constrain version of QuickCheck for compatibility >--------------------------------------------------------------- f04e6f563dc5275bdefe84984a4e50695919e5a0 tests/bytestring-tests.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/bytestring-tests.cabal b/tests/bytestring-tests.cabal index f78981a..efece04 100644 --- a/tests/bytestring-tests.cabal +++ b/tests/bytestring-tests.cabal @@ -27,7 +27,7 @@ executable prop-compiled hs-source-dirs: . .. build-depends: base, ghc-prim, deepseq, random, directory, test-framework, test-framework-quickcheck2, - QuickCheck >= 2.3 && < 3 + QuickCheck >= 2.3 && < 2.7 c-sources: ../cbits/fpstring.c include-dirs: ../include cpp-options: -DHAVE_TEST_FRAMEWORK=1 From git at git.haskell.org Fri Jan 23 22:42:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:21 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Add test for fromFunction. (61eeeec) Message-ID: <20150123224221.315263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/61eeeec856e39108ba3d5cb4251b249acc782305 >--------------------------------------------------------------- commit 61eeeec856e39108ba3d5cb4251b249acc782305 Author: Milan Straka Date: Sun Dec 14 16:49:49 2014 +0100 Add test for fromFunction. >--------------------------------------------------------------- 61eeeec856e39108ba3d5cb4251b249acc782305 tests/seq-properties.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index 74b2e9c..14d5a5f 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -36,6 +36,7 @@ main = defaultMain , testProperty "(|>)" prop_snoc , testProperty "(><)" prop_append , testProperty "fromList" prop_fromList + , testProperty "fromFunction" prop_fromFunction , testProperty "replicate" prop_replicate , testProperty "replicateA" prop_replicateA , testProperty "replicateM" prop_replicateM @@ -270,6 +271,10 @@ prop_fromList :: [A] -> Bool prop_fromList xs = toList' (fromList xs) ~= xs +prop_fromFunction :: [A] -> Bool +prop_fromFunction xs = + toList' (fromFunction (Prelude.length xs) (xs!!)) ~= xs + -- ** Repetition prop_replicate :: NonNegative Int -> A -> Bool From git at git.haskell.org Fri Jan 23 22:42:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:21 +0000 (UTC) Subject: [commit: packages/containers] master: update benchmarks Makefile (5f9af63) Message-ID: <20150123224221.7A0583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/5f9af637de232236abf1890f1e05a3df4421ef15 >--------------------------------------------------------------- commit 5f9af637de232236abf1890f1e05a3df4421ef15 Author: Bertram Felgenhauer Date: Sun Dec 21 21:01:11 2014 +0100 update benchmarks Makefile >--------------------------------------------------------------- 5f9af637de232236abf1890f1e05a3df4421ef15 benchmarks/Makefile | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/benchmarks/Makefile b/benchmarks/Makefile index 1539a2a..aacccef 100644 --- a/benchmarks/Makefile +++ b/benchmarks/Makefile @@ -1,10 +1,12 @@ all: bench-%: %.hs force - ghc -O2 -DTESTING $< -i../$(TOP) -o $@ -outputdir tmp -rtsopts + ghc -O2 -DTESTING $< -I../include -i../$(TOP) -o $@ -outputdir tmp -rtsopts + +.PRECIOUS: bench-% bench-%.csv: bench-% - ./bench-$* $(BENCHMARK) -v -u bench-$*.csv + ./bench-$* "$(BENCHMARK)" -v1 --csv bench-$*.csv .PHONY: force clean veryclean force: From git at git.haskell.org Fri Jan 23 22:42:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:22 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Allow tests to use multiple cores (37b3017) Message-ID: <20150123224222.58D6B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/37b30175dae3355a5a1362d1ef58d40c18f911aa >--------------------------------------------------------------- commit 37b30175dae3355a5a1362d1ef58d40c18f911aa Author: Bryan O'Sullivan Date: Fri Jun 6 13:25:36 2014 -0700 Allow tests to use multiple cores >--------------------------------------------------------------- 37b30175dae3355a5a1362d1ef58d40c18f911aa bytestring.cabal | 3 ++- tests/bytestring-tests.cabal | 3 ++- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/bytestring.cabal b/bytestring.cabal index 4f524b5..d27ca48 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -158,6 +158,7 @@ test-suite prop-compiled include-dirs: include ghc-options: -fwarn-unused-binds -fno-enable-rewrite-rules + -threaded -rtsopts default-language: Haskell98 -- older ghc had issues with language pragmas guarded by cpp if impl(ghc < 7) @@ -182,7 +183,7 @@ test-suite test-builder directory, mtl >= 2.0 && < 2.2 - ghc-options: -Wall -fwarn-tabs + ghc-options: -Wall -fwarn-tabs -threaded -rtsopts default-language: Haskell98 -- older ghc had issues with language pragmas guarded by cpp diff --git a/tests/bytestring-tests.cabal b/tests/bytestring-tests.cabal index efece04..bddadde 100644 --- a/tests/bytestring-tests.cabal +++ b/tests/bytestring-tests.cabal @@ -33,6 +33,7 @@ executable prop-compiled cpp-options: -DHAVE_TEST_FRAMEWORK=1 ghc-options: -fwarn-unused-binds -fno-enable-rewrite-rules + -threaded -rtsopts extensions: BangPatterns UnliftedFFITypes, MagicHash, @@ -61,7 +62,7 @@ executable test-builder test-framework-quickcheck2 >= 0.3 cpp-options: -DHAVE_TEST_FRAMEWORK=1 - ghc-options: -Wall -fwarn-tabs -fhpc + ghc-options: -Wall -fwarn-tabs -fhpc -threaded -rtsopts extensions: CPP, ForeignFunctionInterface UnliftedFFITypes, From git at git.haskell.org Fri Jan 23 22:42:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:23 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Fix warnings. (610ebfb) Message-ID: <20150123224223.38FF63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/610ebfbe4eecfb04886ed87691aeb65869ee0445 >--------------------------------------------------------------- commit 610ebfbe4eecfb04886ed87691aeb65869ee0445 Author: Milan Straka Date: Mon Dec 15 07:41:55 2014 +0100 Fix warnings. >--------------------------------------------------------------- 610ebfbe4eecfb04886ed87691aeb65869ee0445 Data/Sequence.hs | 48 ++++++++++++++++++++++-------------------------- 1 file changed, 22 insertions(+), 26 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 9f3f543..d85cab6 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -164,9 +164,9 @@ import Data.Functor (Functor(..)) import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr', toList)) #else #if MIN_VERSION_base(4,6,0) -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr'), toList) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl'), toList) #else -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', foldr', toList) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', toList) #endif #endif import Data.Traversable @@ -180,6 +180,7 @@ import Data.Data #endif #if __GLASGOW_HASKELL__ >= 708 import Data.Coerce +import qualified GHC.Exts #define COERCE coerce #else #ifdef __GLASGOW_HASKELL__ @@ -192,9 +193,6 @@ import qualified Unsafe.Coerce #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity(..)) #endif -#ifdef __GLASGOW_HASKELL__ -import qualified GHC.Exts -#endif infixr 5 `consTree` infixl 5 `snocTree` @@ -246,6 +244,8 @@ instance Foldable Seq where {-# INLINE length #-} null = null {-# INLINE null #-} + toList = toList + {-# INLINE toList #-} #endif instance Traversable Seq where @@ -611,10 +611,6 @@ instance Applicative (State s) where execState :: State s a -> s -> a execState m x = snd (runState m x) --- | A helper method: a strict version of mapAccumL. -mapAccumL' :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) -mapAccumL' f s t = runState (traverse (State . flip f) t) s - -- | 'applicativeTree' takes an Applicative-wrapped construction of a -- piece of a FingerTree, assumed to always have the same size (which -- is put in the second argument), and replicates it as many times as @@ -1305,12 +1301,12 @@ adjustDigit f i (Four a b c d) -- function that also depends on the element's index, and applies it to every -- element in the sequence. mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b -mapWithIndex f (Seq xs) = Seq $ mapWithIndexTree (\s (Elem a) -> Elem (f s a)) 0 xs +mapWithIndex f' (Seq xs') = Seq $ mapWithIndexTree (\s (Elem a) -> Elem (f' s a)) 0 xs' where {-# SPECIALIZE mapWithIndexTree :: (Int -> Elem y -> b) -> Int -> FingerTree (Elem y) -> FingerTree b #-} {-# SPECIALIZE mapWithIndexTree :: (Int -> Node y -> b) -> Int -> FingerTree (Node y) -> FingerTree b #-} mapWithIndexTree :: Sized a => (Int -> a -> b) -> Int -> FingerTree a -> FingerTree b - mapWithIndexTree _f s Empty = s `seq` Empty + mapWithIndexTree _ s Empty = s `seq` Empty mapWithIndexTree f s (Single xs) = Single $ f s xs mapWithIndexTree f s (Deep n pr m sf) = sPspr `seq` sPsprm `seq` Deep n @@ -1379,23 +1375,23 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = i `seq` s `seq` case trees of 1 -> Single $ b i 2 -> Deep (2*s) (One (b i)) Empty (One (b (i+s))) - 3 -> Deep (3*s) (createTwo b s i) Empty (One (b (i+2*s))) - 4 -> Deep (4*s) (createTwo b s i) Empty (createTwo b s (i+2*s)) - 5 -> Deep (5*s) (createThree b s i) Empty (createTwo b s (i+3*s)) - 6 -> Deep (6*s) (createThree b s i) Empty (createThree b s (i+3*s)) + 3 -> Deep (3*s) (createTwo i) Empty (One (b (i+2*s))) + 4 -> Deep (4*s) (createTwo i) Empty (createTwo (i+2*s)) + 5 -> Deep (5*s) (createThree i) Empty (createTwo (i+3*s)) + 6 -> Deep (6*s) (createThree i) Empty (createThree (i+3*s)) _ -> case trees `quotRem` 3 of - (trees', 1) -> Deep (trees*s) (createTwo b s i) + (trees', 1) -> Deep (trees*s) (createTwo i) (create mb (3*s) (i+2*s) (trees'-1)) - (createTwo b s (i+(2+3*(trees'-1))*s)) - (trees', 2) -> Deep (trees*s) (createThree b s i) + (createTwo (i+(2+3*(trees'-1))*s)) + (trees', 2) -> Deep (trees*s) (createThree i) (create mb (3*s) (i+3*s) (trees'-1)) - (createTwo b s (i+(3+3*(trees'-1))*s)) - (trees', 0) -> Deep (trees*s) (createThree b s i) + (createTwo (i+(3+3*(trees'-1))*s)) + (trees', _) -> Deep (trees*s) (createThree i) (create mb (3*s) (i+3*s) (trees'-2)) - (createThree b s (i+(3+3*(trees'-2))*s)) + (createThree (i+(3+3*(trees'-2))*s)) where - createTwo b s i = Two (b i) (b (i + s)) - createThree b s i = Three (b i) (b (i + s)) (b (i + s + s)) + createTwo j = Two (b j) (b (j + s)) + createThree j = Three (b j) (b (j + s)) (b (j + 2*s)) mb j = Node3 (3*s) (b j) (b (j + s)) (b (j + 2*s)) -- Splitting @@ -1884,8 +1880,8 @@ splitMap splt' = go {-# SPECIALIZE splitMapTree :: (Int -> s -> (s,s)) -> (s -> Elem y -> b) -> s -> FingerTree (Elem y) -> FingerTree b #-} {-# SPECIALIZE splitMapTree :: (Int -> s -> (s,s)) -> (s -> Node y -> b) -> s -> FingerTree (Node y) -> FingerTree b #-} splitMapTree :: Sized a => (Int -> s -> (s,s)) -> (s -> a -> b) -> s -> FingerTree a -> FingerTree b - splitMapTree splt _f _s Empty = Empty - splitMapTree splt f s (Single xs) = Single $ f s xs + splitMapTree _ _ _ Empty = Empty + splitMapTree _ f s (Single xs) = Single $ f s xs splitMapTree splt f s (Deep n pr m sf) = Deep n (splitMapDigit splt f prs pr) (splitMapTree splt (splitMapNode splt f) ms m) (splitMapDigit splt f sfs sf) where (prs, r) = splt (size pr) s @@ -1894,7 +1890,7 @@ splitMap splt' = go {-# SPECIALIZE splitMapDigit :: (Int -> s -> (s,s)) -> (s -> Elem y -> b) -> s -> Digit (Elem y) -> Digit b #-} {-# SPECIALIZE splitMapDigit :: (Int -> s -> (s,s)) -> (s -> Node y -> b) -> s -> Digit (Node y) -> Digit b #-} splitMapDigit :: Sized a => (Int -> s -> (s,s)) -> (s -> a -> b) -> s -> Digit a -> Digit b - splitMapDigit splt f s (One a) = One (f s a) + splitMapDigit _ f s (One a) = One (f s a) splitMapDigit splt f s (Two a b) = Two (f first a) (f second b) where (first, second) = splt (size a) s From git at git.haskell.org Fri Jan 23 22:42:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:23 +0000 (UTC) Subject: [commit: packages/containers] master: update benchmarks to work with criterion-1.0 (5364bea) Message-ID: <20150123224223.804683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/5364beaa69609ba3c0868cec4380b9c36105b740 >--------------------------------------------------------------- commit 5364beaa69609ba3c0868cec4380b9c36105b740 Author: Bertram Felgenhauer Date: Mon Dec 22 17:08:21 2014 +0100 update benchmarks to work with criterion-1.0 >--------------------------------------------------------------- 5364beaa69609ba3c0868cec4380b9c36105b740 benchmarks/IntMap.hs | 6 ++---- benchmarks/IntSet.hs | 6 ++---- benchmarks/Map.hs | 6 ++---- benchmarks/Sequence.hs | 7 ++++--- benchmarks/Set.hs | 6 ++---- 5 files changed, 12 insertions(+), 19 deletions(-) diff --git a/benchmarks/IntMap.hs b/benchmarks/IntMap.hs index 87465a7..38104c0 100644 --- a/benchmarks/IntMap.hs +++ b/benchmarks/IntMap.hs @@ -4,7 +4,6 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Config import Criterion.Main import Data.List (foldl') import qualified Data.IntMap as M @@ -13,9 +12,8 @@ import Prelude hiding (lookup) main = do let m = M.fromAscList elems :: M.IntMap Int - defaultMainWith - defaultConfig - (liftIO . evaluate $ rnf [m]) + evaluate $ rnf [m] + defaultMain [ bench "lookup" $ whnf (lookup keys) m , bench "insert" $ whnf (ins elems) M.empty , bench "insertWith empty" $ whnf (insWith elems) M.empty diff --git a/benchmarks/IntSet.hs b/benchmarks/IntSet.hs index 7c16c91..a768a32 100644 --- a/benchmarks/IntSet.hs +++ b/benchmarks/IntSet.hs @@ -5,7 +5,6 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Config import Criterion.Main import Data.List (foldl') import qualified Data.IntSet as S @@ -14,9 +13,8 @@ main = do let s = S.fromAscList elems :: S.IntSet s_even = S.fromAscList elems_even :: S.IntSet s_odd = S.fromAscList elems_odd :: S.IntSet - defaultMainWith - defaultConfig - (liftIO . evaluate $ rnf [s, s_even, s_odd]) + evaluate $ rnf [s, s_even, s_odd] + defaultMain [ bench "member" $ whnf (member elems) s , bench "insert" $ whnf (ins elems) S.empty , bench "map" $ whnf (S.map (+ 1)) s diff --git a/benchmarks/Map.hs b/benchmarks/Map.hs index d0d539a..60e7ace 100644 --- a/benchmarks/Map.hs +++ b/benchmarks/Map.hs @@ -4,7 +4,6 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Config import Criterion.Main import Data.List (foldl') import qualified Data.Map as M @@ -15,9 +14,8 @@ main = do let m = M.fromAscList elems :: M.Map Int Int m_even = M.fromAscList elems_even :: M.Map Int Int m_odd = M.fromAscList elems_odd :: M.Map Int Int - defaultMainWith - defaultConfig - (liftIO . evaluate $ rnf [m, m_even, m_odd]) + evaluate $ rnf [m, m_even, m_odd] + defaultMain [ bench "lookup absent" $ whnf (lookup evens) m_odd , bench "lookup present" $ whnf (lookup evens) m_even , bench "insert absent" $ whnf (ins elems_even) m_odd diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index a152c3b..7ccede9 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -3,6 +3,7 @@ module Main where import Control.Applicative import Control.DeepSeq +import Control.Exception (evaluate) import Criterion.Main import Data.List (foldl') import qualified Data.Sequence as S @@ -14,19 +15,19 @@ main = do s100 = S.fromList [1..100] :: S.Seq Int s1000 = S.fromList [1..1000] :: S.Seq Int s10000 = S.fromList [1..10000] :: S.Seq Int - rnf [s10, s100, s1000, s10000] `seq` return () + evaluate $ rnf [s10, s100, s1000, s10000] let g = mkStdGen 1 let rlist n = map (`mod` (n+1)) (take 10000 (randoms g)) :: [Int] r10 = rlist 10 r100 = rlist 100 r1000 = rlist 1000 r10000 = rlist 10000 - rnf [r10, r100, r1000, r10000] `seq` return () + evaluate $ rnf [r10, r100, r1000, r10000] let u10 = S.replicate 10 () :: S.Seq () u100 = S.replicate 100 () :: S.Seq () u1000 = S.replicate 1000 () :: S.Seq () u10000 = S.replicate 10000 () :: S.Seq () - rnf [u10, u100, u1000, u10000] `seq` return () + evaluate $ rnf [u10, u100, u1000, u10000] defaultMain [ bgroup "splitAt/append" [ bench "10" $ nf (shuffle r10) s10 diff --git a/benchmarks/Set.hs b/benchmarks/Set.hs index e21001c..3a6e8aa 100644 --- a/benchmarks/Set.hs +++ b/benchmarks/Set.hs @@ -6,7 +6,6 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Config import Criterion.Main import Data.List (foldl') import qualified Data.Set as S @@ -15,9 +14,8 @@ main = do let s = S.fromAscList elems :: S.Set Int s_even = S.fromAscList elems_even :: S.Set Int s_odd = S.fromAscList elems_odd :: S.Set Int - defaultMainWith - defaultConfig - (liftIO . evaluate $ rnf [s, s_even, s_odd]) + evaluate $ rnf [s, s_even, s_odd] + defaultMain [ bench "member" $ whnf (member elems) s , bench "insert" $ whnf (ins elems) S.empty , bench "map" $ whnf (S.map (+ 1)) s From git at git.haskell.org Fri Jan 23 22:42:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:24 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Ignore cabal sandbox fun (ca80162) Message-ID: <20150123224224.634D53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/ca8016238e5b6c779f59fe31dba57ef893b93d46 >--------------------------------------------------------------- commit ca8016238e5b6c779f59fe31dba57ef893b93d46 Author: Bryan O'Sullivan Date: Fri Jun 6 13:26:22 2014 -0700 Ignore cabal sandbox fun >--------------------------------------------------------------- ca8016238e5b6c779f59fe31dba57ef893b93d46 .gitignore | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.gitignore b/.gitignore index 0e04aef..11b4f34 100644 --- a/.gitignore +++ b/.gitignore @@ -3,4 +3,6 @@ cabal-dev dist dist-install ghc.mk +.cabal-sandbox +cabal.sandbox.config .hsenv From git at git.haskell.org Fri Jan 23 22:42:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:25 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Make sure the helper functions are inlined. (3e60f3a) Message-ID: <20150123224225.425883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/3e60f3aa337ddf670a3f20586353c539f6b49eb4 >--------------------------------------------------------------- commit 3e60f3aa337ddf670a3f20586353c539f6b49eb4 Author: Milan Straka Date: Mon Dec 15 08:15:42 2014 +0100 Make sure the helper functions are inlined. >--------------------------------------------------------------- 3e60f3aa337ddf670a3f20586353c539f6b49eb4 Data/Sequence.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index d85cab6..fa80b3f 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1391,8 +1391,11 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg (createThree (i+(3+3*(trees'-2))*s)) where createTwo j = Two (b j) (b (j + s)) + {-# INLINE createTwo #-} createThree j = Three (b j) (b (j + s)) (b (j + 2*s)) + {-# INLINE createThree #-} mb j = Node3 (3*s) (b j) (b (j + s)) (b (j + 2*s)) + {-# INLINE mb #-} -- Splitting From git at git.haskell.org Fri Jan 23 22:42:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:25 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #110 from int-e/bench (55f65cd) Message-ID: <20150123224225.884A73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/55f65cddc15bb30149795de2c5498e428381f2d2 >--------------------------------------------------------------- commit 55f65cddc15bb30149795de2c5498e428381f2d2 Merge: 924fafe 5364bea Author: Milan Straka Date: Mon Dec 22 17:56:05 2014 +0100 Merge pull request #110 from int-e/bench update benchmarks for criterion-1.0 >--------------------------------------------------------------- 55f65cddc15bb30149795de2c5498e428381f2d2 benchmarks/IntMap.hs | 6 ++---- benchmarks/IntSet.hs | 6 ++---- benchmarks/Makefile | 6 ++++-- benchmarks/Map.hs | 6 ++---- benchmarks/Sequence.hs | 7 ++++--- benchmarks/Set.hs | 6 ++---- 6 files changed, 16 insertions(+), 21 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:26 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Ignore Emacs files (7f9acc4) Message-ID: <20150123224226.6BF173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/7f9acc4751a6885f0426e32ba895b14aacc62c97 >--------------------------------------------------------------- commit 7f9acc4751a6885f0426e32ba895b14aacc62c97 Author: Bryan O'Sullivan Date: Fri Jun 6 14:24:18 2014 -0700 Ignore Emacs files >--------------------------------------------------------------- 7f9acc4751a6885f0426e32ba895b14aacc62c97 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 11b4f34..7b18bc1 100644 --- a/.gitignore +++ b/.gitignore @@ -6,3 +6,4 @@ ghc.mk .cabal-sandbox cabal.sandbox.config .hsenv +*~ From git at git.haskell.org Fri Jan 23 22:42:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:27 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Move the closing parent to a separate line. (97599c0) Message-ID: <20150123224227.47F7B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/97599c082e5388551d2f8f767045b807194083fa >--------------------------------------------------------------- commit 97599c082e5388551d2f8f767045b807194083fa Author: Milan Straka Date: Mon Dec 15 08:24:34 2014 +0100 Move the closing parent to a separate line. >--------------------------------------------------------------- 97599c082e5388551d2f8f767045b807194083fa benchmarks/Sequence.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index 8fd1fcf..8bc2d74 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -36,7 +36,8 @@ main = do [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (s10000, u10000) , bench "nf100" $ nf (uncurry S.zip) (s100, u100) , bench "nf10000" $ nf (uncurry S.zip) (s10000, u10000) - ] ] + ] + ] -- splitAt+append: repeatedly cut the sequence at a random point -- and rejoin the pieces in the opposite order. From git at git.haskell.org Fri Jan 23 22:42:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:27 +0000 (UTC) Subject: [commit: packages/containers] master: Make applicativeTree aim for safe digits (1e962fc) Message-ID: <20150123224227.91FA53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/1e962fc2772008512509955316fb4d6eab2766e3 >--------------------------------------------------------------- commit 1e962fc2772008512509955316fb4d6eab2766e3 Author: David Feuer Date: Wed Dec 24 22:03:29 2014 -0500 Make applicativeTree aim for safe digits As previously discussed, this gives the tree more flexibility and matches what other functions do. >--------------------------------------------------------------- 1e962fc2772008512509955316fb4d6eab2766e3 Data/Sequence.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 0a64c3e..c256a53 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -856,17 +856,14 @@ applicativeTree n mSize m = mSize `seq` case n of 4 -> deepA two emptyTree two 5 -> deepA three emptyTree two 6 -> deepA three emptyTree three - 7 -> deepA four emptyTree three - 8 -> deepA four emptyTree four _ -> case n `quotRem` 3 of (q,0) -> deepA three (applicativeTree (q - 2) mSize' n3) three - (q,1) -> deepA four (applicativeTree (q - 2) mSize' n3) three - (q,_) -> deepA four (applicativeTree (q - 2) mSize' n3) four + (q,1) -> deepA two (applicativeTree (q - 1) mSize' n3) two + (q,_) -> deepA three (applicativeTree (q - 1) mSize' n3) two where one = fmap One m two = liftA2 Two m m three = liftA3 Three m m m - four = liftA3 Four m m m <*> m deepA = liftA3 (Deep (n * mSize)) mSize' = 3 * mSize n3 = liftA3 (Node3 mSize') m m m @@ -2335,7 +2332,7 @@ unstableSortBy cmp (Seq xs) = toPQ cmp (\ (Elem x) -> PQueue x Nil) xs -- | fromList2, given a list and its length, constructs a completely --- balanced Seq whose elements are that list using the applicativeTree +-- balanced Seq whose elements are that list using the replicateA -- generalization. fromList2 :: Int -> [a] -> Seq a fromList2 n = execState (replicateA n (State ht)) From git at git.haskell.org Fri Jan 23 22:42:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:28 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Protect against Int overflow in concat (1d3b3fd) Message-ID: <20150123224228.771623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/1d3b3fd7f979d47bf9a4a170db85eb4cf334d5d0 >--------------------------------------------------------------- commit 1d3b3fd7f979d47bf9a4a170db85eb4cf334d5d0 Author: Bryan O'Sullivan Date: Fri Jun 6 14:24:38 2014 -0700 Protect against Int overflow in concat This partially fixes gh-22. >--------------------------------------------------------------- 1d3b3fd7f979d47bf9a4a170db85eb4cf334d5d0 tests/Regressions.hs | 23 +++++++++++++++++++++++ 1 file changed, 23 insertions(+) diff --git a/tests/Regressions.hs b/tests/Regressions.hs new file mode 100644 index 0000000..29c9f02 --- /dev/null +++ b/tests/Regressions.hs @@ -0,0 +1,23 @@ +import Control.Exception (SomeException, handle) +import Test.HUnit (assertBool, assertEqual, assertFailure) +import qualified Data.ByteString as B +import qualified Test.Framework as F +import qualified Test.Framework.Providers.HUnit as F + +-- Try to generate arguments to concat that are big enough to cause an +-- Int to overflow. +concat_overflow :: IO () +concat_overflow = + handle (\(_::SomeException) -> return ()) $ + B.concat (replicate lsize (B.replicate bsize 0)) `seq` + assertFailure "T.replicate should crash" + where + (lsize, bsize) | maxBound == (2147483647::Int) = (2^14, 2^18) + | otherwise = (2^34, 2^29) + +tests :: [F.Test] +tests = [ + F.testCase "concat_overflow" concat_overflow + ] + +main = F.defaultMain tests From git at git.haskell.org Fri Jan 23 22:42:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:29 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Remove unsafeCoerce, use only coerce on GHC 7.8 and later. (b38f240) Message-ID: <20150123224229.50E743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/b38f240ab4bec53c5f5800cc1b621a00b4604b2d >--------------------------------------------------------------- commit b38f240ab4bec53c5f5800cc1b621a00b4604b2d Author: Milan Straka Date: Mon Dec 15 09:02:37 2014 +0100 Remove unsafeCoerce, use only coerce on GHC 7.8 and later. Also, move the conditional compilation to a local where definition. On my GHC 7.6.3, there is no heap allocation in the cmm in fromFunction for the (Elem . f) closure, so there is no penalty of not using `coerce`. Nevertheless, GHC 7.8.3 and GHC-head (15 Dec 2014) do heap-allocate trivial closure for (Elem . f), so `coerce` helps. Back to GHC 7.6.3, I found that the following does not allocate in GHC 7.6.3: newtype Elem a = Elem a elemMap :: Int -> (Int -> b) -> [Elem b] elemMap s f = go (Elem . f) 0 where go :: (Int -> b) -> Int -> [b] go f i | i >= s = [] | otherwise = f i : go f (i+1) Nevertheless, the following does heap-allocate trivial closure for f: newtype Elem a = Elem a elemMap :: [Int] -> (Int -> b) -> [Elem b] elemMap xs f = go (Elem . f) xs where go :: (Int -> b) -> [Int] -> [b] go f [] = [] go f (x:xs) = f x : go f xs I am not sure what the difference is, but the current fromFunction does not allocate too (on 7.6.3). >--------------------------------------------------------------- b38f240ab4bec53c5f5800cc1b621a00b4604b2d Data/Sequence.hs | 21 +++++++++------------ 1 file changed, 9 insertions(+), 12 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index fa80b3f..4c281fc 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -181,14 +181,7 @@ import Data.Data #if __GLASGOW_HASKELL__ >= 708 import Data.Coerce import qualified GHC.Exts -#define COERCE coerce #else -#ifdef __GLASGOW_HASKELL__ -import qualified Unsafe.Coerce --- Note that by compiling this file with GHC 7.8 or later, we prove that --- it is safe to use COERCE with earlier GHC versions. -#define COERCE Unsafe.Coerce.unsafeCoerce -#endif #endif #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity(..)) @@ -1365,11 +1358,7 @@ mapWithIndex f' (Seq xs') = Seq $ mapWithIndexTree (\s (Elem a) -> Elem (f' s a) fromFunction :: Int -> (Int -> a) -> Seq a fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with negative len" | len == 0 = empty -#ifdef __GLASGOW_HASKELL__ - | otherwise = Seq $ create (COERCE f) 1 0 len -#else - | otherwise = Seq $ create (Elem . f) 1 0 len -#endif + | otherwise = Seq $ create (lift_elem f) 1 0 len where create :: (Int -> a) -> Int -> Int -> Int -> FingerTree a create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = i `seq` s `seq` case trees of @@ -1397,6 +1386,14 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg mb j = Node3 (3*s) (b j) (b (j + s)) (b (j + 2*s)) {-# INLINE mb #-} + lift_elem :: (Int -> a) -> (Int -> Elem a) +#if __GLASGOW_HASKELL__ >= 708 + lift_elem g = coerce g +#else + lift_elem g = Elem . g +#endif + {-# INLINE lift_elem #-} + -- Splitting -- | /O(log(min(i,n-i)))/. The first @i@ elements of a sequence. From git at git.haskell.org Fri Jan 23 22:42:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:29 +0000 (UTC) Subject: [commit: packages/containers] master: Clean up <*> development artifacts (f1e0f8e) Message-ID: <20150123224229.9A08B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/f1e0f8e2b5df2be6852fb35ff2dd9559aaa4c830 >--------------------------------------------------------------- commit f1e0f8e2b5df2be6852fb35ff2dd9559aaa4c830 Author: David Feuer Date: Sat Dec 27 21:35:36 2014 -0500 Clean up <*> development artifacts Some silly remnants of my thought process remained in the code. Remove them. >--------------------------------------------------------------- f1e0f8e2b5df2be6852fb35ff2dd9559aaa4c830 Data/Sequence.hs | 20 +++++++++++--------- 1 file changed, 11 insertions(+), 9 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 0a64c3e..34504f5 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -338,15 +338,18 @@ aptyMiddle firstf (Deep s (squashL pr prm) mm (squashR sfm sf))) (fmap (fmap lastf) sfm) --- At the bottom +-- At the bottom. Note that these appendTree0 calls are very cheap, because in +-- each case, one of the arguments is guaranteed to be Empty or Single. aptyMiddle firstf lastf map23 fs (Deep s pr m sf) - = (fmap (fmap firstf) m `snocTree` fmap firstf (digitToNode sf)) - `appendTree0` middle `appendTree0` - (fmap lastf (digitToNode pr) `consTree` fmap (fmap lastf) m) + = fmap (fmap firstf) m `appendTree0` + ((fmap firstf (digitToNode sf) + `consTree` middle) + `snocTree` fmap lastf (digitToNode pr)) + `appendTree0` fmap (fmap lastf) m where middle = case trimTree $ mapMulFT s (\(Elem f) -> fmap (fmap (map23 f)) converted) fs of (firstMapped, restMapped, lastMapped) -> Deep (size firstMapped + size restMapped + size lastMapped) @@ -469,17 +472,16 @@ rigidify Single{} = error "rigidify: singleton" -- | /O(log n)/ (incremental) Rejigger a finger tree so the digits are all ones -- and twos. thin :: Sized a => FingerTree a -> FingerTree a --- Note that 'thin' may call itself at most once before passing the job on to --- 'thin12'. 'thin12' will produce a 'Deep' constructor immediately before --- calling 'thin'. +-- Note that 'thin12' will produce a 'Deep' constructor immediately before +-- recursively calling 'thin'. thin Empty = Empty thin (Single a) = Single a thin t@(Deep s pr m sf) = case pr of One{} -> thin12 t Two{} -> thin12 t - Three a b c -> thin $ Deep s (One a) (node2 b c `consTree` m) sf - Four a b c d -> thin $ Deep s (Two a b) (node2 c d `consTree` m) sf + Three a b c -> thin12 $ Deep s (One a) (node2 b c `consTree` m) sf + Four a b c d -> thin12 $ Deep s (Two a b) (node2 c d `consTree` m) sf thin12 :: Sized a => FingerTree a -> FingerTree a thin12 (Deep s pr m sf at One{}) = Deep s pr (thin m) sf From git at git.haskell.org Fri Jan 23 22:42:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:30 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Drop trailing whitespace (f097086) Message-ID: <20150123224230.80CD63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/f097086c9061e81bef17d4505b405285624fd620 >--------------------------------------------------------------- commit f097086c9061e81bef17d4505b405285624fd620 Author: Bryan O'Sullivan Date: Fri Jun 6 14:41:38 2014 -0700 Drop trailing whitespace >--------------------------------------------------------------- f097086c9061e81bef17d4505b405285624fd620 Data/ByteString/Lazy.hs | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:31 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Add simple fromFunction benchmarks. (a556ef2) Message-ID: <20150123224231.56C273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/a556ef225952c27731a00b24b6417b6a057507ce >--------------------------------------------------------------- commit a556ef225952c27731a00b24b6417b6a057507ce Author: Milan Straka Date: Mon Dec 15 14:47:20 2014 +0100 Add simple fromFunction benchmarks. >--------------------------------------------------------------- a556ef225952c27731a00b24b6417b6a057507ce benchmarks/Sequence.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index 8bc2d74..b6b82fa 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -37,6 +37,13 @@ main = do , bench "nf100" $ nf (uncurry S.zip) (s100, u100) , bench "nf10000" $ nf (uncurry S.zip) (s10000, u10000) ] + , bgroup "fromFunction" + [ bench "ix10000/5000" $ nf (\s -> S.fromFunction s (+1) `S.index` (s `div` 2)) 10000 + , bench "nf10" $ nf (\s -> S.fromFunction s (+1)) 10 + , bench "nf100" $ nf (\s -> S.fromFunction s (+1)) 100 + , bench "nf1000" $ nf (\s -> S.fromFunction s (+1)) 1000 + , bench "nf10000" $ nf (\s -> S.fromFunction s (+1)) 10000 + ] ] -- splitAt+append: repeatedly cut the sequence at a random point From git at git.haskell.org Fri Jan 23 22:42:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:31 +0000 (UTC) Subject: [commit: packages/containers] master: Make `-Wall`-clean for base-4.8.0.0 (71f53cb) Message-ID: <20150123224231.A6CA63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/71f53cb8ea10cd2b50dbc0a7429e1f790fb62a0f >--------------------------------------------------------------- commit 71f53cb8ea10cd2b50dbc0a7429e1f790fb62a0f Author: Herbert Valerio Riedel Date: Sun Dec 28 09:36:44 2014 +0100 Make `-Wall`-clean for base-4.8.0.0 >--------------------------------------------------------------- 71f53cb8ea10cd2b50dbc0a7429e1f790fb62a0f Data/Graph.hs | 2 ++ Data/IntMap/Base.hs | 11 ++++++++--- Data/IntSet/Base.hs | 4 +++- Data/Map/Base.hs | 9 +++++++-- Data/Sequence.hs | 3 +++ Data/Set/Base.hs | 2 ++ Data/Tree.hs | 13 +++++++++---- 7 files changed, 34 insertions(+), 10 deletions(-) diff --git a/Data/Graph.hs b/Data/Graph.hs index 5f2bc15..c02b3e3 100644 --- a/Data/Graph.hs +++ b/Data/Graph.hs @@ -75,7 +75,9 @@ import qualified Data.IntSet as Set import Data.Tree (Tree(Node), Forest) -- std interfaces +#if !MIN_VERSION_base(4,8,0) import Control.Applicative +#endif import Control.DeepSeq (NFData(rnf)) import Data.Maybe import Data.Array diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index d25cb9e..e15ed76 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -216,16 +216,21 @@ module Data.IntMap.Base ( , highestBitMask ) where +#if MIN_VERSION_base(4,8,0) +import Control.Applicative ((<$>)) +#else import Control.Applicative (Applicative(pure, (<*>)), (<$>)) +import Data.Monoid (Monoid(..)) +import Data.Traversable (Traversable(traverse)) +import Data.Word (Word) +#endif + import Control.DeepSeq (NFData(rnf)) import Control.Monad (liftM) import Data.Bits import qualified Data.Foldable as Foldable import Data.Maybe (fromMaybe) -import Data.Monoid (Monoid(..)) -import Data.Traversable (Traversable(traverse)) import Data.Typeable -import Data.Word (Word) import Prelude hiding (lookup, map, filter, foldr, foldl, null) import Data.IntSet.Base (Key) diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 6ddd0fb..c89bd18 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -169,9 +169,11 @@ import Control.DeepSeq (NFData(rnf)) import Data.Bits import qualified Data.List as List import Data.Maybe (fromMaybe) +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (Monoid(..)) -import Data.Typeable import Data.Word (Word) +#endif +import Data.Typeable import Prelude hiding (filter, foldr, foldl, null, map) import Data.Utils.BitUtil diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 815e54b..965a258 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -270,12 +270,17 @@ module Data.Map.Base ( , filterLt ) where +#if MIN_VERSION_base(4,8,0) +import Control.Applicative ((<$>)) +#else import Control.Applicative (Applicative(..), (<$>)) +import Data.Monoid (Monoid(..)) +import Data.Traversable (Traversable(traverse)) +#endif + import Control.DeepSeq (NFData(rnf)) import Data.Bits (shiftL, shiftR) import qualified Data.Foldable as Foldable -import Data.Monoid (Monoid(..)) -import Data.Traversable (Traversable(traverse)) import Data.Typeable import Prelude hiding (lookup, map, filter, foldr, foldl, null) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 0a64c3e..6b11266 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -147,6 +147,9 @@ module Data.Sequence ( import Prelude hiding ( Functor(..), +#if MIN_VERSION_base(4,8,0) + Applicative, foldMap, Monoid, +#endif null, length, take, drop, splitAt, foldl, foldl1, foldr, foldr1, scanl, scanl1, scanr, scanr1, replicate, zip, zipWith, zip3, zipWith3, takeWhile, dropWhile, iterate, reverse, filter, mapM, sum, all) diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 0dbc569..e1ebad3 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -192,7 +192,9 @@ module Data.Set.Base ( import Prelude hiding (filter,foldl,foldr,null,map) import qualified Data.List as List import Data.Bits (shiftL, shiftR) +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (Monoid(..)) +#endif import qualified Data.Foldable as Foldable import Data.Typeable import Control.DeepSeq (NFData(rnf)) diff --git a/Data/Tree.hs b/Data/Tree.hs index 4ee935b..abc9902 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -34,13 +34,19 @@ module Data.Tree( unfoldTreeM_BF, unfoldForestM_BF, ) where +#if MIN_VERSION_base(4,8,0) +import Control.Applicative ((<$>)) +import Data.Foldable (toList) +#else import Control.Applicative (Applicative(..), (<$>)) -import Control.Monad (liftM) +import Data.Foldable (Foldable(foldMap), toList) import Data.Monoid (Monoid(..)) +import Data.Traversable (Traversable(traverse)) +#endif + +import Control.Monad (liftM) import Data.Sequence (Seq, empty, singleton, (<|), (|>), fromList, ViewL(..), ViewR(..), viewl, viewr) -import Data.Foldable (Foldable(foldMap), toList) -import Data.Traversable (Traversable(traverse)) import Data.Typeable import Control.DeepSeq (NFData(rnf)) @@ -52,7 +58,6 @@ import Data.Data (Data) import Data.Coerce #endif - -- | Multi-way trees, also known as /rose trees/. data Tree a = Node { rootLabel :: a, -- ^ label value From git at git.haskell.org Fri Jan 23 22:42:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:32 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Rename sumP to checkedSum, and export it (2530b1c) Message-ID: <20150123224232.89A193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/2530b1c28f15d0f320a84701bf507d5650de6098 >--------------------------------------------------------------- commit 2530b1c28f15d0f320a84701bf507d5650de6098 Author: Bryan O'Sullivan Date: Fri Jun 6 14:42:47 2014 -0700 Rename sumP to checkedSum, and export it >--------------------------------------------------------------- 2530b1c28f15d0f320a84701bf507d5650de6098 Data/ByteString/Internal.hs | 17 ++++++++++++++--- 1 file changed, 14 insertions(+), 3 deletions(-) diff --git a/Data/ByteString/Internal.hs b/Data/ByteString/Internal.hs index efdb7a6..15192c1 100644 --- a/Data/ByteString/Internal.hs +++ b/Data/ByteString/Internal.hs @@ -38,6 +38,7 @@ module Data.ByteString.Internal ( #if defined(__GLASGOW_HASKELL__) unsafePackAddress, #endif + checkedSum, -- * Low level imperative construction create, -- :: Int -> (Ptr Word8 -> IO ()) -> IO ByteString @@ -532,12 +533,21 @@ concat [] = mempty concat [bs] = bs concat bss0 = unsafeCreate totalLen $ \ptr -> go bss0 ptr where - totalLen = List.sum [ len | (PS _ _ len) <- bss0 ] + totalLen = checkedSum "concat" [ len | (PS _ _ len) <- bss0 ] go [] !_ = return () go (PS fp off len:bss) !ptr = do withForeignPtr fp $ \p -> memcpy ptr (p `plusPtr` off) len go bss (ptr `plusPtr` len) +-- | Add a list of non-negative numbers. Errors out on overflow. +checkedSum :: String -> [Int] -> Int +checkedSum fun = go 0 + where go !a (x:xs) + | ax >= 0 = go ax xs + | otherwise = overflowError fun + where ax = a + x + go a _ = a + ------------------------------------------------------------------------ -- | Conversion between 'Word8' and 'Char'. Should compile to a no-op. @@ -581,6 +591,9 @@ isSpaceChar8 c = c == '\xa0' {-# INLINE isSpaceChar8 #-} +overflowError :: String -> a +overflowError fun = error $ "Data.ByteString." ++ fun ++ ": size overflow" + ------------------------------------------------------------------------ -- | This \"function\" has a superficial similarity to 'unsafePerformIO' but @@ -620,7 +633,6 @@ inlinePerformIO = accursedUnutterablePerformIO {-# INLINE inlinePerformIO #-} {-# DEPRECATED inlinePerformIO "If you think you know what you are doing, use 'unsafePerformIO'. If you are sure you know what you are doing, use 'unsafeDupablePerformIO'. If you enjoy sharing an address space with a malevolent agent of chaos, try 'accursedUnutterablePerformIO'." #-} - -- --------------------------------------------------------------------- -- -- Standard C functions @@ -684,4 +696,3 @@ foreign import ccall unsafe "static fpstring.h fps_minimum" c_minimum foreign import ccall unsafe "static fpstring.h fps_count" c_count :: Ptr Word8 -> CULong -> Word8 -> IO CULong - From git at git.haskell.org Fri Jan 23 22:42:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:33 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Use a top-down version of fromList (51a1f7c) Message-ID: <20150123224233.5FA563A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/51a1f7c6670058ed4feefd1ef86170ddef173e63 >--------------------------------------------------------------- commit 51a1f7c6670058ed4feefd1ef86170ddef173e63 Author: David Feuer Date: Tue Dec 9 14:56:53 2014 -0500 Use a top-down version of fromList Ross Paterson came up with a version of fromList that avoids the tree rebuilding inherent in the `(|>)`-based approach. This version is somewhat strictified and rearranged. It reduces allocation substantially over the old version. Mutator time goes down too, but for some reason GC time rises to match it. >--------------------------------------------------------------- 51a1f7c6670058ed4feefd1ef86170ddef173e63 Data/Sequence.hs | 25 ++++++++++++++++++++++++- 1 file changed, 24 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 4c281fc..651dd5e 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1752,11 +1752,34 @@ findIndicesR p xs = foldlWithIndex g [] xs -- Lists ------------------------------------------------------------------------ +-- The implementation below, by Ross Paterson, avoids the rebuilding +-- the previous (|>)-based implementation suffered from. + -- | /O(n)/. Create a sequence from a finite list of elements. -- There is a function 'toList' in the opposite direction for all -- instances of the 'Foldable' class, including 'Seq'. fromList :: [a] -> Seq a -fromList = Data.List.foldl' (|>) empty +fromList xs = Seq $ mkTree 1 $ Data.List.map Elem xs + where + {-# SPECIALIZE mkTree :: Int -> [Elem a] -> FingerTree (Elem a) #-} + {-# SPECIALIZE mkTree :: Int -> [Node a] -> FingerTree (Node a) #-} + mkTree :: (Sized a) => Int -> [a] -> FingerTree a + mkTree s [] = s `seq` Empty + mkTree s [x1] = s `seq` Single x1 + mkTree s [x1, x2] = Deep (2*s) (One x1) Empty (One x2) + mkTree s [x1, x2, x3] = Deep (3*s) (One x1) Empty (Two x2 x3) + mkTree s (x1:x2:x3:xs) = s `seq` case getNodes (3*s) xs of + (ns, sf) -> m `seq` deep' (Three x1 x2 x3) m sf + where m = mkTree (3*s) ns + + deep' pr@(Three x1 _ _) m sf = Deep (3*size x1 + size m + size sf) pr m sf + + getNodes :: Int -> [a] -> ([Node a], Digit a) + getNodes s [x1] = s `seq` ([], One x1) + getNodes s [x1, x2] = s `seq` ([], Two x1 x2) + getNodes s [x1, x2, x3] = s `seq` ([], Three x1 x2 x3) + getNodes s (x1:x2:x3:xs) = s `seq` (Node3 s x1 x2 x3:ns, d) + where (ns, d) = getNodes s xs #if __GLASGOW_HASKELL__ >= 708 instance GHC.Exts.IsList (Seq a) where From git at git.haskell.org Fri Jan 23 22:42:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:33 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #119 from hvr/pr-base48 (a4df7f3) Message-ID: <20150123224233.B06623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/a4df7f35d859634f321c05f574e268a1c47792be >--------------------------------------------------------------- commit a4df7f35d859634f321c05f574e268a1c47792be Merge: 55f65cd 71f53cb Author: Milan Straka Date: Tue Dec 30 14:42:22 2014 +0100 Merge pull request #119 from hvr/pr-base48 Make `-Wall`-clean for base-4.8.0.0 >--------------------------------------------------------------- a4df7f35d859634f321c05f574e268a1c47792be Data/Graph.hs | 2 ++ Data/IntMap/Base.hs | 11 ++++++++--- Data/IntSet/Base.hs | 4 +++- Data/Map/Base.hs | 9 +++++++-- Data/Sequence.hs | 3 +++ Data/Set/Base.hs | 2 ++ Data/Tree.hs | 13 +++++++++---- 7 files changed, 34 insertions(+), 10 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:34 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Fix Int overflow in Lazy.toStrict (fbcc0af) Message-ID: <20150123224234.953DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/fbcc0afc65de06e5de0fe05054539452f59ffeb9 >--------------------------------------------------------------- commit fbcc0afc65de06e5de0fe05054539452f59ffeb9 Author: Bryan O'Sullivan Date: Fri Jun 6 14:43:15 2014 -0700 Fix Int overflow in Lazy.toStrict This is the final fix for gh-22. >--------------------------------------------------------------- fbcc0afc65de06e5de0fe05054539452f59ffeb9 Data/ByteString/Lazy.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/ByteString/Lazy.hs b/Data/ByteString/Lazy.hs index 52d1c0f..c761bdb 100644 --- a/Data/ByteString/Lazy.hs +++ b/Data/ByteString/Lazy.hs @@ -295,7 +295,7 @@ toStrict Empty = S.empty toStrict (Chunk c Empty) = c toStrict cs0 = S.unsafeCreate totalLen $ \ptr -> go cs0 ptr where - totalLen = foldlChunks (\a c -> a + S.length c) 0 cs0 + totalLen = S.checkedSum "Lazy.toStrict" . L.map S.length . toChunks $ cs0 go Empty !_ = return () go (Chunk (S.PS fp off len) cs) !destptr = From git at git.haskell.org Fri Jan 23 22:42:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:35 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Remove trailing whitespace. (a1d613b) Message-ID: <20150123224235.6722E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/a1d613b50c2e0e15e01159ab2fa1b377a49e2a38 >--------------------------------------------------------------- commit a1d613b50c2e0e15e01159ab2fa1b377a49e2a38 Author: Milan Straka Date: Mon Dec 15 17:30:58 2014 +0100 Remove trailing whitespace. >--------------------------------------------------------------- a1d613b50c2e0e15e01159ab2fa1b377a49e2a38 Data/Sequence.hs | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:35 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #116 from treeowl/balanceReplicate (e0cfb50) Message-ID: <20150123224235.B90813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/e0cfb504ce356f75e59ca2b392dee3f93eae0e4b >--------------------------------------------------------------- commit e0cfb504ce356f75e59ca2b392dee3f93eae0e4b Merge: a4df7f3 1e962fc Author: Milan Straka Date: Tue Dec 30 14:49:36 2014 +0100 Merge pull request #116 from treeowl/balanceReplicate Make applicativeTree aim for safe digits >--------------------------------------------------------------- e0cfb504ce356f75e59ca2b392dee3f93eae0e4b Data/Sequence.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:36 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Add regressions to test suite (d61dffb) Message-ID: <20150123224236.9E75D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/d61dffbd19cebd20b7c9cb9a8e50b3bfb1025748 >--------------------------------------------------------------- commit d61dffbd19cebd20b7c9cb9a8e50b3bfb1025748 Author: Bryan O'Sullivan Date: Fri Jun 6 14:43:53 2014 -0700 Add regressions to test suite >--------------------------------------------------------------- d61dffbd19cebd20b7c9cb9a8e50b3bfb1025748 bytestring.cabal | 20 +++++++++++++++++++- tests/bytestring-tests.cabal | 19 +++++++++++++++++++ 2 files changed, 38 insertions(+), 1 deletion(-) diff --git a/bytestring.cabal b/bytestring.cabal index d27ca48..663ee5e 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -153,6 +153,7 @@ test-suite prop-compiled TestFramework hs-source-dirs: . tests build-depends: base, ghc-prim, deepseq, random, directory, + test-framework, test-framework-quickcheck2, QuickCheck >= 2.3 && < 2.7 c-sources: cbits/fpstring.c include-dirs: include @@ -166,6 +167,24 @@ test-suite prop-compiled DeriveDataTypeable, BangPatterns, NamedFieldPuns +test-suite regressions + type: exitcode-stdio-1.0 + main-is: Regressions.hs + hs-source-dirs: . tests + build-depends: base, ghc-prim, deepseq, random, directory, + test-framework, test-framework-hunit, HUnit, + c-sources: cbits/fpstring.c + include-dirs: include + ghc-options: -fwarn-unused-binds + -fno-enable-rewrite-rules + -threaded -rtsopts + default-language: Haskell98 + -- older ghc had issues with language pragmas guarded by cpp + if impl(ghc < 7) + default-extensions: CPP, MagicHash, UnboxedTuples, + DeriveDataTypeable, BangPatterns, + NamedFieldPuns + test-suite test-builder type: exitcode-stdio-1.0 hs-source-dirs: . tests tests/builder @@ -197,4 +216,3 @@ test-suite test-builder include-dirs: include includes: fpstring.h install-includes: fpstring.h - diff --git a/tests/bytestring-tests.cabal b/tests/bytestring-tests.cabal index bddadde..d84fc6b 100644 --- a/tests/bytestring-tests.cabal +++ b/tests/bytestring-tests.cabal @@ -42,6 +42,25 @@ executable prop-compiled ScopedTypeVariables NamedFieldPuns +executable regressions + main-is: Regressions.hs + hs-source-dirs: . .. + build-depends: base, ghc-prim, deepseq, random, directory, + test-framework, test-framework-hunit, HUnit + c-sources: ../cbits/fpstring.c + include-dirs: ../include + cpp-options: -DHAVE_TEST_FRAMEWORK=1 + ghc-options: -fwarn-unused-binds + -fno-enable-rewrite-rules + -threaded -rtsopts + extensions: BangPatterns + UnliftedFFITypes, + MagicHash, + UnboxedTuples, + DeriveDataTypeable + ScopedTypeVariables + NamedFieldPuns + executable test-builder hs-source-dirs: . .. builder main-is: TestSuite.hs From git at git.haskell.org Fri Jan 23 22:42:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:37 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Use coerce for [a]->[Elem a] convertion in fromList. (9b37d5a) Message-ID: <20150123224237.6EDA23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/9b37d5a262e8070abce1f51d4913d9312a630acd >--------------------------------------------------------------- commit 9b37d5a262e8070abce1f51d4913d9312a630acd Author: Milan Straka Date: Mon Dec 15 17:37:18 2014 +0100 Use coerce for [a]->[Elem a] convertion in fromList. >--------------------------------------------------------------- 9b37d5a262e8070abce1f51d4913d9312a630acd Data/Sequence.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 1b6dea2..71ded95 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1759,7 +1759,7 @@ findIndicesR p xs = foldlWithIndex g [] xs -- There is a function 'toList' in the opposite direction for all -- instances of the 'Foldable' class, including 'Seq'. fromList :: [a] -> Seq a -fromList xs = Seq $ mkTree 1 $ Data.List.map Elem xs +fromList xs = Seq $ mkTree 1 $ map_elem xs where {-# SPECIALIZE mkTree :: Int -> [Elem a] -> FingerTree (Elem a) #-} {-# SPECIALIZE mkTree :: Int -> [Node a] -> FingerTree (Node a) #-} @@ -1781,6 +1781,14 @@ fromList xs = Seq $ mkTree 1 $ Data.List.map Elem xs getNodes s (x1:x2:x3:xs) = s `seq` (Node3 s x1 x2 x3:ns, d) where (ns, d) = getNodes s xs + map_elem :: [a] -> [Elem a] +#if __GLASGOW_HASKELL__ >= 708 + map_elem xs = coerce xs +#else + map_elem xs = Data.List.map Elem xs +#endif + {-# INLINE map_elem #-} + #if __GLASGOW_HASKELL__ >= 708 instance GHC.Exts.IsList (Seq a) where type Item (Seq a) = a From git at git.haskell.org Fri Jan 23 22:42:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:37 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #118 from treeowl/apcleanup (202e2f2) Message-ID: <20150123224237.C1DE13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/202e2f2a28d1d914d19e177bc4b6e64597cf62f2 >--------------------------------------------------------------- commit 202e2f2a28d1d914d19e177bc4b6e64597cf62f2 Merge: e0cfb50 f1e0f8e Author: Milan Straka Date: Tue Dec 30 14:55:09 2014 +0100 Merge pull request #118 from treeowl/apcleanup Clean up <*> development artifacts >--------------------------------------------------------------- 202e2f2a28d1d914d19e177bc4b6e64597cf62f2 Data/Sequence.hs | 20 +++++++++++--------- 1 file changed, 11 insertions(+), 9 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:38 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Remove trailing comma from build-depends (09edcd8) Message-ID: <20150123224238.A91173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/09edcd8feb0c1d8b49027b9177e4ac20f524a2b1 >--------------------------------------------------------------- commit 09edcd8feb0c1d8b49027b9177e4ac20f524a2b1 Author: Herbert Valerio Riedel Date: Sat Jun 7 08:47:27 2014 +0200 Remove trailing comma from build-depends This was introduced in d61dffbd19cebd20b7c9cb9a8e50b3bfb1025748 but sadly Cabal doesn't support trailing commas in build-depends just *yet* >--------------------------------------------------------------- 09edcd8feb0c1d8b49027b9177e4ac20f524a2b1 bytestring.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/bytestring.cabal b/bytestring.cabal index 663ee5e..6e14f6d 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -172,7 +172,7 @@ test-suite regressions main-is: Regressions.hs hs-source-dirs: . tests build-depends: base, ghc-prim, deepseq, random, directory, - test-framework, test-framework-hunit, HUnit, + test-framework, test-framework-hunit, HUnit c-sources: cbits/fpstring.c include-dirs: include ghc-options: -fwarn-unused-binds From git at git.haskell.org Fri Jan 23 22:42:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:39 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Comment various conditional imports. (9df67f5) Message-ID: <20150123224239.769113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/9df67f5121ef14c865b4fae9db96aebf083dfb6c >--------------------------------------------------------------- commit 9df67f5121ef14c865b4fae9db96aebf083dfb6c Author: Milan Straka Date: Mon Dec 15 17:57:20 2014 +0100 Comment various conditional imports. >--------------------------------------------------------------- 9df67f5121ef14c865b4fae9db96aebf083dfb6c Data/Sequence.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 71ded95..2e8f84c 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -172,17 +172,22 @@ import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', t import Data.Traversable import Data.Typeable +-- GHC specific stuff #ifdef __GLASGOW_HASKELL__ import GHC.Exts (build) import Text.Read (Lexeme(Ident), lexP, parens, prec, readPrec, readListPrec, readListPrecDefault) import Data.Data #endif + +-- Coercion on GHC 7.8+ #if __GLASGOW_HASKELL__ >= 708 import Data.Coerce import qualified GHC.Exts #else #endif + +-- Identity functor on base 4.8 (GHC 7.10+) #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity(..)) #endif From git at git.haskell.org Fri Jan 23 22:42:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:39 +0000 (UTC) Subject: [commit: packages/containers] master: Add warning about Seq size. (74afe96) Message-ID: <20150123224239.CC1F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/74afe969cc792ab30715f6ad7399bddb492a1b66 >--------------------------------------------------------------- commit 74afe969cc792ab30715f6ad7399bddb492a1b66 Author: David Feuer Date: Wed Dec 31 01:24:48 2014 -0500 Add warning about Seq size. >--------------------------------------------------------------- 74afe969cc792ab30715f6ad7399bddb492a1b66 Data/Map.hs | 4 ++++ Data/Map/Lazy.hs | 4 ++++ Data/Map/Strict.hs | 4 ++++ Data/Sequence.hs | 14 +++++++++++--- Data/Set.hs | 4 ++++ Data/Set/Base.hs | 4 ++++ 6 files changed, 31 insertions(+), 3 deletions(-) diff --git a/Data/Map.hs b/Data/Map.hs index 1281f2f..e4af46a 100644 --- a/Data/Map.hs +++ b/Data/Map.hs @@ -45,6 +45,10 @@ -- first argument are always preferred to the second, for example in -- 'union' or 'insert'. -- +-- /Warning/: The size of the map must not exceed @maxBound::Int at . Violation of +-- this condition is not detected and if the size limit is exceeded, its +-- behaviour is undefined. +-- -- Operation comments contain the operation time complexity in -- the Big-O notation (). ----------------------------------------------------------------------------- diff --git a/Data/Map/Lazy.hs b/Data/Map/Lazy.hs index 2705de5..17fa6fe 100644 --- a/Data/Map/Lazy.hs +++ b/Data/Map/Lazy.hs @@ -44,6 +44,10 @@ -- first argument are always preferred to the second, for example in -- 'union' or 'insert'. -- +-- /Warning/: The size of the map must not exceed @maxBound::Int at . Violation of +-- this condition is not detected and if the size limit is exceeded, its +-- behaviour is undefined. +-- -- Operation comments contain the operation time complexity in -- the Big-O notation (). ----------------------------------------------------------------------------- diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs index 7309041..623b1df 100644 --- a/Data/Map/Strict.hs +++ b/Data/Map/Strict.hs @@ -44,6 +44,10 @@ -- first argument are always preferred to the second, for example in -- 'union' or 'insert'. -- +-- /Warning/: The size of the map must not exceed @maxBound::Int at . Violation of +-- this condition is not detected and if the size limit is exceeded, its +-- behaviour is undefined. +-- -- Operation comments contain the operation time complexity in -- the Big-O notation (). -- diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 11f1880..21c54d3 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -16,7 +16,8 @@ -- Module : Data.Sequence -- Copyright : (c) Ross Paterson 2005 -- (c) Louis Wasserman 2009 --- (c) David Feuer, Ross Paterson, and Milan Straka 2014 +-- (c) Bertram Felgenhauer, David Feuer, Ross Paterson, and +-- Milan Straka 2014 -- License : BSD-style -- Maintainer : libraries at haskell.org -- Stability : experimental @@ -29,7 +30,7 @@ -- -- An amortized running time is given for each operation, with /n/ referring -- to the length of the sequence and /i/ being the integral index used by --- some operations. These bounds hold even in a persistent (shared) setting. +-- some operations. These bounds hold even in a persistent (shared) setting. -- -- The implementation uses 2-3 finger trees annotated with sizes, -- as described in section 4.2 of @@ -40,9 +41,16 @@ -- -- -- /Note/: Many of these operations have the same names as similar --- operations on lists in the "Prelude". The ambiguity may be resolved +-- operations on lists in the "Prelude". The ambiguity may be resolved -- using either qualification or the @hiding@ clause. -- +-- /Warning/: The size of a 'Seq' must not exceed @maxBound::Int at . Violation +-- of this condition is not detected and if the size limit is exceeded, the +-- behaviour of the sequence is undefined. This is unlikely to occur in most +-- applications, but some care may be required when using '><', '<*>', '*>', or +-- '>>', particularly repeatedly and particularly in combination with +-- 'replicate' or 'fromFunction'. +-- ----------------------------------------------------------------------------- module Data.Sequence ( diff --git a/Data/Set.hs b/Data/Set.hs index 37366fe..fd8c8b9 100644 --- a/Data/Set.hs +++ b/Data/Set.hs @@ -38,6 +38,10 @@ -- 'union' or 'insert'. Of course, left-biasing can only be observed -- when equality is an equivalence relation instead of structural -- equality. +-- +-- /Warning/: The size of the set must not exceed @maxBound::Int at . Violation of +-- this condition is not detected and if the size limit is exceeded, its +-- behaviour is undefined. ----------------------------------------------------------------------------- module Data.Set ( diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index e1ebad3..616d0eb 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -45,6 +45,10 @@ -- 'union' or 'insert'. Of course, left-biasing can only be observed -- when equality is an equivalence relation instead of structural -- equality. +-- +-- /Warning/: The size of the set must not exceed @maxBound::Int at . Violation of +-- this condition is not detected and if the size limit is exceeded, its +-- behaviour is undefined. ----------------------------------------------------------------------------- -- [Note: Using INLINABLE] From git at git.haskell.org Fri Jan 23 22:42:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:40 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Add new test-framework deps to TravisCI job (a832f99) Message-ID: <20150123224240.B4C813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/a832f991d575a399394be13c8494aabbca04abd1 >--------------------------------------------------------------- commit a832f991d575a399394be13c8494aabbca04abd1 Author: Herbert Valerio Riedel Date: Sat Jun 7 09:23:56 2014 +0200 Add new test-framework deps to TravisCI job >--------------------------------------------------------------- a832f991d575a399394be13c8494aabbca04abd1 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 413f89b..0fc37f1 100644 --- a/.travis.yml +++ b/.travis.yml @@ -23,7 +23,7 @@ before_install: install: - travis_retry cabal update # can't use "cabal install --only-dependencies --enable-tests" due to dep-cycle - - cabal install "QuickCheck >=2.4 && <2.7" "byteorder ==1.0.*" "dlist ==0.5.*" "mtl >=2.0 && <2.2" deepseq + - cabal install "QuickCheck >=2.4 && <2.7" "byteorder ==1.0.*" "dlist ==0.5.*" "mtl >=2.0 && <2.2" deepseq test-framework-hunit test-framework-quickcheck2 script: - cabal configure --enable-tests -v2 From git at git.haskell.org Fri Jan 23 22:42:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:41 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6, develop-0.6-questionable, master: Add Data.Sequence.fromArray. (52ba9e5) Message-ID: <20150123224241.7FB9C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branches: develop-0.6,develop-0.6-questionable,master Link : http://git.haskell.org/packages/containers.git/commitdiff/52ba9e5d9c85d4bd11236c1e43b4847a50a3b771 >--------------------------------------------------------------- commit 52ba9e5d9c85d4bd11236c1e43b4847a50a3b771 Author: Milan Straka Date: Mon Dec 15 17:58:46 2014 +0100 Add Data.Sequence.fromArray. Sugested by David Feuer in #88. The implementation on GHC uses GHC.Arr module and is considerably faster than on non-GHC compilers. >--------------------------------------------------------------- 52ba9e5d9c85d4bd11236c1e43b4847a50a3b771 Data/Sequence.hs | 19 +++++++++++++++++++ tests/seq-properties.hs | 6 ++++++ 2 files changed, 25 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 2e8f84c..690a9fe 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -62,6 +62,7 @@ module Data.Sequence ( (><), -- :: Seq a -> Seq a -> Seq a fromList, -- :: [a] -> Seq a fromFunction, -- :: Int -> (Int -> a) -> Seq a + fromArray, -- :: Ix i => Array i a -> Seq a -- ** Repetition replicate, -- :: Int -> a -> Seq a replicateA, -- :: Applicative f => Int -> f a -> f (Seq a) @@ -180,6 +181,13 @@ import Text.Read (Lexeme(Ident), lexP, parens, prec, import Data.Data #endif +-- Array stuff, with GHC.Arr on GHC +import Data.Array (Ix, Array) +import qualified Data.Array +#ifdef __GLASGOW_HASKELL__ +import qualified GHC.Arr +#endif + -- Coercion on GHC 7.8+ #if __GLASGOW_HASKELL__ >= 708 import Data.Coerce @@ -1399,6 +1407,17 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg #endif {-# INLINE lift_elem #-} +-- | /O(n)/. Create a sequence consisting of the elements of an 'Array'. +-- Note that the resulting sequence elements may be evaluated lazily (as on GHC), +-- so you must force the entire structure to be sure that the original array +-- can be garbage-collected. +fromArray :: Ix i => Array i a -> Seq a +#ifdef __GLASGOW_HASKELL__ +fromArray a = fromFunction (GHC.Arr.numElements a) (GHC.Arr.unsafeAt a) +#else +fromArray a = fromList2 (Data.Array.rangeSize (Data.Array.bounds a)) (Data.Array.elems a) +#endif + -- Splitting -- | /O(log(min(i,n-i)))/. The first @i@ elements of a sequence. diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index 14d5a5f..a64e66d 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -2,6 +2,7 @@ import Data.Sequence -- needs to be compiled with -DTESTING for use here import Control.Applicative (Applicative(..)) import Control.Arrow ((***)) +import Data.Array (listArray) import Data.Foldable (Foldable(..), toList, all, sum) import Data.Functor ((<$>), (<$)) import Data.Maybe @@ -37,6 +38,7 @@ main = defaultMain , testProperty "(><)" prop_append , testProperty "fromList" prop_fromList , testProperty "fromFunction" prop_fromFunction + , testProperty "fromArray" prop_fromArray , testProperty "replicate" prop_replicate , testProperty "replicateA" prop_replicateA , testProperty "replicateM" prop_replicateM @@ -275,6 +277,10 @@ prop_fromFunction :: [A] -> Bool prop_fromFunction xs = toList' (fromFunction (Prelude.length xs) (xs!!)) ~= xs +prop_fromArray :: [A] -> Bool +prop_fromArray xs = + toList' (fromArray (listArray (42, 42+Prelude.length xs-1) xs)) ~= xs + -- ** Repetition prop_replicate :: NonNegative Int -> A -> Bool From git at git.haskell.org Fri Jan 23 22:42:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:41 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #122 from treeowl/dangerdoc (d5f5582) Message-ID: <20150123224241.D66A43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/d5f5582709630c2a40ef998ffd727b8f739534df >--------------------------------------------------------------- commit d5f5582709630c2a40ef998ffd727b8f739534df Merge: 202e2f2 74afe96 Author: Milan Straka Date: Sun Jan 4 22:16:07 2015 +0100 Merge pull request #122 from treeowl/dangerdoc Add warning about Seq size. >--------------------------------------------------------------- d5f5582709630c2a40ef998ffd727b8f739534df Data/Map.hs | 4 ++++ Data/Map/Lazy.hs | 4 ++++ Data/Map/Strict.hs | 4 ++++ Data/Sequence.hs | 14 +++++++++++--- Data/Set.hs | 4 ++++ Data/Set/Base.hs | 4 ++++ 6 files changed, 31 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:42 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Enable ScopedTypeVariables for tests/Regressions (ec1d7c7) Message-ID: <20150123224242.BD0A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/ec1d7c7fb98d725447a185d79fca3ba70f89d405 >--------------------------------------------------------------- commit ec1d7c7fb98d725447a185d79fca3ba70f89d405 Author: Herbert Valerio Riedel Date: Sat Jun 7 09:36:32 2014 +0200 Enable ScopedTypeVariables for tests/Regressions Otherwise the module doesn't compile >--------------------------------------------------------------- ec1d7c7fb98d725447a185d79fca3ba70f89d405 tests/Regressions.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/tests/Regressions.hs b/tests/Regressions.hs index 29c9f02..a1b44cf 100644 --- a/tests/Regressions.hs +++ b/tests/Regressions.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE ScopedTypeVariables #-} + import Control.Exception (SomeException, handle) import Test.HUnit (assertBool, assertEqual, assertFailure) import qualified Data.ByteString as B From git at git.haskell.org Fri Jan 23 22:42:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:43 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6: Make types of the drawing functions more generic, i.e. Show s => Tree s instead of Tree String (7ab1c39) Message-ID: <20150123224243.868223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop-0.6 Link : http://git.haskell.org/packages/containers.git/commitdiff/7ab1c399726c5a4a562cff3f56017ff5852ac82e >--------------------------------------------------------------- commit 7ab1c399726c5a4a562cff3f56017ff5852ac82e Author: jonasc Date: Fri Aug 8 00:15:10 2014 +0200 Make types of the drawing functions more generic, i.e. Show s => Tree s instead of Tree String >--------------------------------------------------------------- 7ab1c399726c5a4a562cff3f56017ff5852ac82e Data/Tree.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/Data/Tree.hs b/Data/Tree.hs index 57a4324..1642c3b 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -113,15 +113,15 @@ instance NFData a => NFData (Tree a) where rnf (Node x ts) = rnf x `seq` rnf ts -- | Neat 2-dimensional drawing of a tree. -drawTree :: Tree String -> String +drawTree :: Show a => Tree a -> String drawTree = unlines . draw -- | Neat 2-dimensional drawing of a forest. -drawForest :: Forest String -> String +drawForest :: Show a => Forest a -> String drawForest = unlines . map drawTree -draw :: Tree String -> [String] -draw (Node x ts0) = x : drawSubTrees ts0 +draw :: Show a => Tree a -> [String] +draw (Node x ts0) = show x : drawSubTrees ts0 where drawSubTrees [] = [] drawSubTrees [t] = From git at git.haskell.org Fri Jan 23 22:42:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:43 +0000 (UTC) Subject: [commit: packages/containers] master: Add unnecessary call in fromArray to make (Ix i) constraint look needed. (6004065) Message-ID: <20150123224243.DF0863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/6004065c646a578fee51c8b6a35fb20514579507 >--------------------------------------------------------------- commit 6004065c646a578fee51c8b6a35fb20514579507 Author: Milan Straka Date: Sat Jan 10 14:25:35 2015 +0100 Add unnecessary call in fromArray to make (Ix i) constraint look needed. >--------------------------------------------------------------- 6004065c646a578fee51c8b6a35fb20514579507 Data/Sequence.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 21c54d3..b62b16a 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -186,6 +186,7 @@ import Data.Data -- Array stuff, with GHC.Arr on GHC import Data.Array (Ix, Array) +import qualified Data.Array #ifdef __GLASGOW_HASKELL__ import qualified GHC.Arr #endif @@ -1649,6 +1650,10 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg fromArray :: Ix i => Array i a -> Seq a #ifdef __GLASGOW_HASKELL__ fromArray a = fromFunction (GHC.Arr.numElements a) (GHC.Arr.unsafeAt a) + where + -- The following definition uses (Ix i) constraing, which is needed for the + -- other fromArray definition. + _ = Data.Array.rangeSize (Data.Array.bounds a) #else fromArray a = fromList2 (Data.Array.rangeSize (Data.Array.bounds a)) (Data.Array.elems a) #endif From git at git.haskell.org Fri Jan 23 22:42:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:44 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Enable --show-details=always (3115296) Message-ID: <20150123224244.C62633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/311529699495d45b06ffdfcf9f05419293cf217e >--------------------------------------------------------------- commit 311529699495d45b06ffdfcf9f05419293cf217e Author: Herbert Valerio Riedel Date: Sat Jun 7 09:54:16 2014 +0200 Enable --show-details=always ...so we can see better what actually goes wrong on failures >--------------------------------------------------------------- 311529699495d45b06ffdfcf9f05419293cf217e .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 0fc37f1..67126bd 100644 --- a/.travis.yml +++ b/.travis.yml @@ -28,7 +28,7 @@ install: script: - cabal configure --enable-tests -v2 - cabal build - - cabal test + - cabal test --show-details=always - cabal sdist # "cabal check" disabled due to -O2 warning - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; From git at git.haskell.org Fri Jan 23 22:42:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:45 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6-questionable: Added fixity declarations for member, notMember, union, and intersection. (de85ae9) Message-ID: <20150123224245.920B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop-0.6-questionable Link : http://git.haskell.org/packages/containers.git/commitdiff/de85ae9eccb84284873d419c899743a85bd4e66a >--------------------------------------------------------------- commit de85ae9eccb84284873d419c899743a85bd4e66a Author: Peter Selinger Date: Fri Jul 4 10:31:20 2014 -0300 Added fixity declarations for member, notMember, union, and intersection. Milan Straka: It is quite unlikely that this ever gets merged, as it can cause build failures (it broke the testing suite for example) and offers in my opinion little benefit. >--------------------------------------------------------------- de85ae9eccb84284873d419c899743a85bd4e66a Data/IntMap/Base.hs | 8 ++++++++ Data/IntSet/Base.hs | 7 +++++++ Data/Map/Base.hs | 8 ++++++++ Data/Set/Base.hs | 8 ++++++++ 4 files changed, 31 insertions(+) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index d5fd75a..2a912d9 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -451,6 +451,8 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the key not a member of the map? -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -459,6 +461,8 @@ member k = k `seq` go notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m +infix 4 notMember + -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. -- See Note: Local 'go' functions and capturing] @@ -874,6 +878,8 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 +infixl 5 union + -- | /O(n+m)/. The union with a combining function. -- -- > unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")] @@ -937,6 +943,8 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 +infixl 5 intersection + -- | /O(n+m)/. The intersection with a combining function. -- -- > intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA" diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 6333eea..f2dfb90 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -321,10 +321,14 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False +infix 4 member + -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -512,6 +516,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t +infixl 5 union {-------------------------------------------------------------------- Difference @@ -586,6 +591,8 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil +infixl 5 intersection + {-------------------------------------------------------------------- Subset --------------------------------------------------------------------} diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index e582e16..92ff096 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -466,6 +466,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- -- > notMember 5 (fromList [(5,'a'), (3,'b')]) == False @@ -479,6 +481,8 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. find :: Ord k => k -> Map k a -> a @@ -1241,6 +1245,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b hedgeUnion _ _ t1 Tip = t1 @@ -1361,6 +1367,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 7e792f4..0c4f62b 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -356,6 +356,8 @@ member = go {-# INLINE member #-} #endif +infix 4 member + -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool notMember a t = not $ member a t @@ -365,6 +367,8 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif +infix 4 notMember + -- | /O(log n)/. Find largest element smaller than the given one. -- -- > lookupLT 3 (fromList [3, 5]) == Nothing @@ -616,6 +620,8 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif +infixl 5 union + hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 hedgeUnion blo bhi Tip (Bin _ x l r) = link x (filterGt blo l) (filterLt bhi r) @@ -674,6 +680,8 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif +infixl 5 intersection + hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip hedgeInt _ _ Tip _ = Tip From git at git.haskell.org Fri Jan 23 22:42:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:45 +0000 (UTC) Subject: [commit: packages/containers] master: Remove unnecessary (Sized *) constraints. (5f519e6) Message-ID: <20150123224245.E94C13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/5f519e641aa7099c0dc6b12d3df08920e8496d04 >--------------------------------------------------------------- commit 5f519e641aa7099c0dc6b12d3df08920e8496d04 Author: Milan Straka Date: Sat Jan 10 14:29:34 2015 +0100 Remove unnecessary (Sized *) constraints. >--------------------------------------------------------------- 5f519e641aa7099c0dc6b12d3df08920e8496d04 Data/Sequence.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index b62b16a..491dd6d 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -640,13 +640,13 @@ deep :: Sized a => Digit a -> FingerTree (Node a) -> Digit a -> Finge deep pr m sf = Deep (size pr + size m + size sf) pr m sf {-# INLINE pullL #-} -pullL :: Sized a => Int -> FingerTree (Node a) -> Digit a -> FingerTree a +pullL :: Int -> FingerTree (Node a) -> Digit a -> FingerTree a pullL s m sf = case viewLTree m of Nothing2 -> digitToTree' s sf Just2 pr m' -> Deep s (nodeToDigit pr) m' sf {-# INLINE pullR #-} -pullR :: Sized a => Int -> Digit a -> FingerTree (Node a) -> FingerTree a +pullR :: Int -> Digit a -> FingerTree (Node a) -> FingerTree a pullR s pr m = case viewRTree m of Nothing2 -> digitToTree' s pr Just2 m' sf -> Deep s pr m' (nodeToDigit sf) @@ -1840,7 +1840,7 @@ initsNode (Node3 s a b c) = Node3 s (One a) (Two a b) (Three a b c) {-# SPECIALIZE tailsTree :: (FingerTree (Node a) -> Node b) -> FingerTree (Node a) -> FingerTree (Node b) #-} -- | Given a function to apply to tails of a tree, applies that function -- to every tail of the specified tree. -tailsTree :: (Sized a, Sized b) => (FingerTree a -> b) -> FingerTree a -> FingerTree b +tailsTree :: Sized a => (FingerTree a -> b) -> FingerTree a -> FingerTree b tailsTree _ Empty = Empty tailsTree f (Single x) = Single (f (Single x)) tailsTree f (Deep n pr m sf) = @@ -1855,7 +1855,7 @@ tailsTree f (Deep n pr m sf) = {-# SPECIALIZE initsTree :: (FingerTree (Node a) -> Node b) -> FingerTree (Node a) -> FingerTree (Node b) #-} -- | Given a function to apply to inits of a tree, applies that function -- to every init of the specified tree. -initsTree :: (Sized a, Sized b) => (FingerTree a -> b) -> FingerTree a -> FingerTree b +initsTree :: Sized a => (FingerTree a -> b) -> FingerTree a -> FingerTree b initsTree _ Empty = Empty initsTree f (Single x) = Single (f (Single x)) initsTree f (Deep n pr m sf) = From git at git.haskell.org Fri Jan 23 22:42:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:46 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Disable regression test and turn on test-framework (1cc7cfb) Message-ID: <20150123224246.CFBB33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/1cc7cfbf28f7b9c1ffdb9ab511a32be0e0194eb1 >--------------------------------------------------------------- commit 1cc7cfbf28f7b9c1ffdb9ab511a32be0e0194eb1 Author: Herbert Valerio Riedel Date: Sat Jun 7 11:48:44 2014 +0200 Disable regression test and turn on test-framework The regression test has been disabled because it seems to allocate way too much memory to be useful for CI purposes. Moreover, the other two test-suites have been changed to be build using test-framework which should have more well-behaved logging output suitable for Travis-CI >--------------------------------------------------------------- 1cc7cfbf28f7b9c1ffdb9ab511a32be0e0194eb1 bytestring.cabal | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/bytestring.cabal b/bytestring.cabal index 6e14f6d..73f9235 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -160,6 +160,7 @@ test-suite prop-compiled ghc-options: -fwarn-unused-binds -fno-enable-rewrite-rules -threaded -rtsopts + cpp-options: -DHAVE_TEST_FRAMEWORK=1 default-language: Haskell98 -- older ghc had issues with language pragmas guarded by cpp if impl(ghc < 7) @@ -168,6 +169,8 @@ test-suite prop-compiled NamedFieldPuns test-suite regressions + -- temporarily disabled as it allocates too much memory + buildable: False type: exitcode-stdio-1.0 main-is: Regressions.hs hs-source-dirs: . tests @@ -200,9 +203,14 @@ test-suite test-builder byteorder == 1.0.*, dlist == 0.5.*, directory, - mtl >= 2.0 && < 2.2 + mtl >= 2.0 && < 2.2, + HUnit, + test-framework, + test-framework-hunit, + test-framework-quickcheck2 ghc-options: -Wall -fwarn-tabs -threaded -rtsopts + cpp-options: -DHAVE_TEST_FRAMEWORK=1 default-language: Haskell98 -- older ghc had issues with language pragmas guarded by cpp From git at git.haskell.org Fri Jan 23 22:42:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:47 +0000 (UTC) Subject: [commit: packages/containers] develop-0.6-questionable: Fixed syntax of fixity declarations. (2bf686d) Message-ID: <20150123224247.9CA7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : develop-0.6-questionable Link : http://git.haskell.org/packages/containers.git/commitdiff/2bf686d3dd0706eef416590100f8d1ebaa3eb80b >--------------------------------------------------------------- commit 2bf686d3dd0706eef416590100f8d1ebaa3eb80b Author: Peter Selinger Date: Fri Jul 4 10:47:35 2014 -0300 Fixed syntax of fixity declarations. >--------------------------------------------------------------- 2bf686d3dd0706eef416590100f8d1ebaa3eb80b Data/IntMap/Base.hs | 8 ++++---- Data/IntSet/Base.hs | 8 ++++---- Data/Map/Base.hs | 8 ++++---- Data/Set/Base.hs | 8 ++++---- 4 files changed, 16 insertions(+), 16 deletions(-) diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index 2a912d9..8afb60c 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -451,7 +451,7 @@ member k = k `seq` go go (Tip kx _) = k == kx go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the key not a member of the map? -- @@ -461,7 +461,7 @@ infix 4 member notMember :: Key -> IntMap a -> Bool notMember k m = not $ member k m -infix 4 notMember +infix 4 `notMember` -- | /O(min(n,W))/. Lookup the value at a key in the map. See also 'Data.Map.lookup'. @@ -878,7 +878,7 @@ union :: IntMap a -> IntMap a -> IntMap a union m1 m2 = mergeWithKey' Bin const id id m1 m2 -infixl 5 union +infixl 5 `union` -- | /O(n+m)/. The union with a combining function. -- @@ -943,7 +943,7 @@ intersection :: IntMap a -> IntMap b -> IntMap a intersection m1 m2 = mergeWithKey' bin const (const Nil) (const Nil) m1 m2 -infixl 5 intersection +infixl 5 `intersection` -- | /O(n+m)/. The intersection with a combining function. -- diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index f2dfb90..bd78790 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -321,13 +321,13 @@ member x = x `seq` go go (Tip y bm) = prefixOf x == y && bitmapOf x .&. bm /= 0 go Nil = False -infix 4 member +infix 4 `member` -- | /O(min(n,W))/. Is the element not in the set? notMember :: Key -> IntSet -> Bool notMember k = not . member k -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -516,7 +516,7 @@ union t@(Bin _ _ _ _) Nil = t union (Tip kx bm) t = insertBM kx bm t union Nil t = t -infixl 5 union +infixl 5 `union` {-------------------------------------------------------------------- Difference @@ -591,7 +591,7 @@ intersection (Tip kx1 bm1) t2 = intersectBM t2 intersection Nil _ = Nil -infixl 5 intersection +infixl 5 `intersection` {-------------------------------------------------------------------- Subset diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 92ff096..ae291c7 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -466,7 +466,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the key not a member of the map? See also 'member'. -- @@ -481,7 +481,7 @@ notMember k m = not $ member k m {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. @@ -1245,7 +1245,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` -- left-biased hedge union hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Map a b -> Map a b -> Map a b @@ -1367,7 +1367,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord k => MaybeS k -> MaybeS k -> Map k a -> Map k b -> Map k a hedgeInt _ _ _ Tip = Tip diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 0c4f62b..732e973 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -356,7 +356,7 @@ member = go {-# INLINE member #-} #endif -infix 4 member +infix 4 `member` -- | /O(log n)/. Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool @@ -367,7 +367,7 @@ notMember a t = not $ member a t {-# INLINE notMember #-} #endif -infix 4 notMember +infix 4 `notMember` -- | /O(log n)/. Find largest element smaller than the given one. -- @@ -620,7 +620,7 @@ union t1 t2 = hedgeUnion NothingS NothingS t1 t2 {-# INLINABLE union #-} #endif -infixl 5 union +infixl 5 `union` hedgeUnion :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeUnion _ _ t1 Tip = t1 @@ -680,7 +680,7 @@ intersection t1 t2 = hedgeInt NothingS NothingS t1 t2 {-# INLINABLE intersection #-} #endif -infixl 5 intersection +infixl 5 `intersection` hedgeInt :: Ord a => MaybeS a -> MaybeS a -> Set a -> Set a -> Set a hedgeInt _ _ _ Tip = Tip From git at git.haskell.org Fri Jan 23 22:42:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:47 +0000 (UTC) Subject: [commit: packages/containers] master: Update .travis.yml per hvr's advice (d1c257a) Message-ID: <20150123224247.F04553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/d1c257aa1385ebe6801a296e5b5decfb3b6e84f3 >--------------------------------------------------------------- commit d1c257aa1385ebe6801a296e5b5decfb3b6e84f3 Author: David Feuer Date: Wed Jan 14 22:47:19 2015 -0500 Update .travis.yml per hvr's advice We want it to be able to build with 7.10 and head. >--------------------------------------------------------------- d1c257aa1385ebe6801a296e5b5decfb3b6e84f3 .travis.yml | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index 8af3116..9505f69 100644 --- a/.travis.yml +++ b/.travis.yml @@ -7,12 +7,13 @@ env: # no package for earlier cabal versions in the PPA - GHCVER=7.4.2 CABALVER=1.16 - GHCVER=7.6.3 CABALVER=1.16 - - GHCVER=7.8.2 CABALVER=1.18 - - GHCVER=head CABALVER=1.20 + - GHCVER=7.8.4 CABALVER=1.18 + - GHCVER=7.10.1 CABALVER=1.22 + - GHCVER=head CABALVER=head matrix: allow_failures: - - env: GHCVER=head CABALVER=1.20 + - env: GHCVER=head CABALVER=head # Note: the distinction between `before_install` and `install` is not # important. From git at git.haskell.org Fri Jan 23 22:42:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:48 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Use --show-details=streaming when available (a562ab2) Message-ID: <20150123224248.D8F493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/a562ab285eb8e9ffd51de104f88389ac125aa833 >--------------------------------------------------------------- commit a562ab285eb8e9ffd51de104f88389ac125aa833 Author: Herbert Valerio Riedel Date: Sat Jun 7 12:04:19 2014 +0200 Use --show-details=streaming when available Travis-CI assumes the build to be stuck if there's no output for several minutes. Which is a problem since the tests for bytestring take quite long. >--------------------------------------------------------------- a562ab285eb8e9ffd51de104f88389ac125aa833 .travis.yml | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 67126bd..1b738ab 100644 --- a/.travis.yml +++ b/.travis.yml @@ -28,7 +28,12 @@ install: script: - cabal configure --enable-tests -v2 - cabal build - - cabal test --show-details=always + # --show-details=streaming is available for CABALVER>=1.20 only + - if [ "$(echo -e "1.20\n$CABALVER" | sort -rV | head -n1)" = "$CABALVER" ]; then + cabal test --show-details=streaming; + else + cabal test --show-details=always; + fi - cabal sdist # "cabal check" disabled due to -O2 warning - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; From git at git.haskell.org Fri Jan 23 22:42:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:49 +0000 (UTC) Subject: [commit: packages/containers] master: Bump version number to 0.5.6.0 (b9e4e22) Message-ID: <20150123224249.A395F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/b9e4e22d6e37150dcf5c04e4c4beabfba5342576 >--------------------------------------------------------------- commit b9e4e22d6e37150dcf5c04e4c4beabfba5342576 Author: Johan Tibell Date: Mon Dec 15 19:57:52 2014 +0100 Bump version number to 0.5.6.0 >--------------------------------------------------------------- b9e4e22d6e37150dcf5c04e4c4beabfba5342576 containers.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/containers.cabal b/containers.cabal index ae7e247..bbf5913 100644 --- a/containers.cabal +++ b/containers.cabal @@ -1,5 +1,5 @@ name: containers -version: 0.5.5.1 +version: 0.5.6.0 license: BSD3 license-file: LICENSE maintainer: fox at ucw.cz From git at git.haskell.org Fri Jan 23 22:42:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:50 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #132 from treeowl/travis-update (25c3fee) Message-ID: <20150123224250.04D483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/25c3fee44aa39b17ac3e74382591260c5edce1fa >--------------------------------------------------------------- commit 25c3fee44aa39b17ac3e74382591260c5edce1fa Merge: 5f519e6 d1c257a Author: Milan Straka Date: Thu Jan 15 12:26:15 2015 +0100 Merge pull request #132 from treeowl/travis-update Update .travis.yml per hvr's advice >--------------------------------------------------------------- 25c3fee44aa39b17ac3e74382591260c5edce1fa .travis.yml | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:50 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Don't mention ISO-8859-1 in doc string for hGetContents (da4c7e9) Message-ID: <20150123224250.E1F043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/da4c7e9b0944a1c3b8e82652c155346f35128696 >--------------------------------------------------------------- commit da4c7e9b0944a1c3b8e82652c155346f35128696 Author: Thomas Miedema Date: Mon Jul 14 14:06:38 2014 +0200 Don't mention ISO-8859-1 in doc string for hGetContents Closes GHC #5861. >--------------------------------------------------------------- da4c7e9b0944a1c3b8e82652c155346f35128696 Data/ByteString.hs | 3 --- 1 file changed, 3 deletions(-) diff --git a/Data/ByteString.hs b/Data/ByteString.hs index 2df2e5c..b839150 100644 --- a/Data/ByteString.hs +++ b/Data/ByteString.hs @@ -1942,9 +1942,6 @@ illegalBufferSize handle fn sz = -- files > half of available memory, this may lead to memory exhaustion. -- Consider using 'readFile' in this case. -- --- As with 'hGet', the string representation in the file is assumed to --- be ISO-8859-1. --- -- The Handle is closed once the contents have been read, -- or if an exception is thrown. -- From git at git.haskell.org Fri Jan 23 22:42:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:51 +0000 (UTC) Subject: [commit: packages/containers] master: Add Ross Paterson to 2014 copyright statement (302d6b4) Message-ID: <20150123224251.ABD4C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/302d6b4839702ce6e18fd1908240b920efb1b04a >--------------------------------------------------------------- commit 302d6b4839702ce6e18fd1908240b920efb1b04a Author: David Feuer Date: Mon Dec 15 15:54:22 2014 -0500 Add Ross Paterson to 2014 copyright statement He wrote the first draft of the new `fromList` code. >--------------------------------------------------------------- 302d6b4839702ce6e18fd1908240b920efb1b04a Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 690a9fe..9a23f77 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -19,7 +19,7 @@ -- Module : Data.Sequence -- Copyright : (c) Ross Paterson 2005 -- (c) Louis Wasserman 2009 --- (c) David Feuer and Milan Straka 2014 +-- (c) David Feuer, Ross Paterson, and Milan Straka 2014 -- License : BSD-style -- Maintainer : libraries at haskell.org -- Stability : experimental From git at git.haskell.org Fri Jan 23 22:42:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:52 +0000 (UTC) Subject: [commit: packages/containers] master: Bump version number to 0.5.6.3 (fabde6b) Message-ID: <20150123224252.0CF703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/fabde6b6381e459a49dee4ba1ac8b96848348542 >--------------------------------------------------------------- commit fabde6b6381e459a49dee4ba1ac8b96848348542 Author: Milan Straka Date: Thu Jan 15 12:41:01 2015 +0100 Bump version number to 0.5.6.3 >--------------------------------------------------------------- fabde6b6381e459a49dee4ba1ac8b96848348542 containers.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/containers.cabal b/containers.cabal index c5d7523..d7db653 100644 --- a/containers.cabal +++ b/containers.cabal @@ -1,5 +1,5 @@ name: containers -version: 0.5.6.2 +version: 0.5.6.3 license: BSD3 license-file: LICENSE maintainer: fox at ucw.cz From git at git.haskell.org Fri Jan 23 22:42:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:52 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Fix typos: rename funtion to function (d4798e9) Message-ID: <20150123224252.EC1AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/d4798e97e7190e6784f0d24d2405c29662af0163 >--------------------------------------------------------------- commit d4798e97e7190e6784f0d24d2405c29662af0163 Author: Sean Leather Date: Thu Oct 23 23:02:51 2014 +0200 Fix typos: rename funtion to function >--------------------------------------------------------------- d4798e97e7190e6784f0d24d2405c29662af0163 Data/ByteString/Unsafe.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/Data/ByteString/Unsafe.hs b/Data/ByteString/Unsafe.hs index 7c0d0fb..bf0ed88 100644 --- a/Data/ByteString/Unsafe.hs +++ b/Data/ByteString/Unsafe.hs @@ -224,7 +224,7 @@ unsafePackCString cstr = do -- collected by Haskell. This operation has /O(1)/ complexity as we -- already know the final size, so no /strlen(3)/ is required. -- --- This funtion is /unsafe/. If the original @CStringLen@ is later +-- This function is /unsafe/. If the original @CStringLen@ is later -- modified, this change will be reflected in the resulting @ByteString@, -- breaking referential transparency. -- @@ -236,7 +236,7 @@ unsafePackCStringLen (ptr,len) = do -- | /O(n)/ Build a @ByteString@ from a malloced @CString at . This value will -- have a @free(3)@ finalizer associated to it. -- --- This funtion is /unsafe/. If the original @CString@ is later +-- This function is /unsafe/. If the original @CString@ is later -- modified, this change will be reflected in the resulting @ByteString@, -- breaking referential transparency. -- @@ -253,7 +253,7 @@ unsafePackMallocCString cstr = do -- | /O(n)/ Build a @ByteString@ from a malloced @CStringLen at . This -- value will have a @free(3)@ finalizer associated to it. -- --- This funtion is /unsafe/. If the original @CString@ is later +-- This function is /unsafe/. If the original @CString@ is later -- modified, this change will be reflected in the resulting @ByteString@, -- breaking referential transparency. -- From git at git.haskell.org Fri Jan 23 22:42:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:53 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #97 from treeowl/add-credit (33e65be) Message-ID: <20150123224253.B476A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/33e65bea1713e1720857fb1c1f982631b872913f >--------------------------------------------------------------- commit 33e65bea1713e1720857fb1c1f982631b872913f Merge: b9e4e22 302d6b4 Author: Milan Straka Date: Mon Dec 15 22:01:23 2014 +0100 Merge pull request #97 from treeowl/add-credit Add Ross Paterson to 2014 copyright statement >--------------------------------------------------------------- 33e65bea1713e1720857fb1c1f982631b872913f Data/Sequence.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:42:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:54 +0000 (UTC) Subject: [commit: packages/containers] master: Improve MIN_VERSION_base fall-back (3dddb04) Message-ID: <20150123224254.137413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/3dddb04bf514e37a87d7f8c5fd7ac58cda89d94f >--------------------------------------------------------------- commit 3dddb04bf514e37a87d7f8c5fd7ac58cda89d94f Author: David Feuer Date: Fri Jan 16 13:51:06 2015 -0500 Improve MIN_VERSION_base fall-back Guess the base library version based on `__GLASGOW_HASKELL__` when compiling without Cabal. >--------------------------------------------------------------- 3dddb04bf514e37a87d7f8c5fd7ac58cda89d94f include/containers.h | 27 +++++++++++++++++++++++---- 1 file changed, 23 insertions(+), 4 deletions(-) diff --git a/include/containers.h b/include/containers.h index ea895d1..b075799 100644 --- a/include/containers.h +++ b/include/containers.h @@ -51,11 +51,30 @@ /* * We use cabal-generated MIN_VERSION_base to adapt to changes of base. * Nevertheless, as a convenience, we also allow compiling without cabal by - * defining trivial MIN_VERSION_base if needed. + * defining an approximate MIN_VERSION_base if needed. The alternative version + * guesses the version of base using the version of GHC. This is usually + * sufficiently accurate. However, it completely ignores minor version numbers, + * and it makes the assumption that a pre-release version of GHC will ship with + * base libraries with the same version numbers as the final release. This + * assumption is violated in certain stages of GHC development, but in practice + * this should very rarely matter, and will not affect any released version. */ #ifndef MIN_VERSION_base -#define MIN_VERSION_base(major1,major2,minor) 0 +#if __GLASGOW_HASKELL__ >= 709 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=8))) +#elif __GLASGOW_HASKELL__ >= 707 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=7))) +#elif __GLASGOW_HASKELL__ >= 705 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=6))) +#elif __GLASGOW_HASKELL__ >= 703 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=5))) +#elif __GLASGOW_HASKELL__ >= 701 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=4))) +#elif __GLASGOW_HASKELL__ >= 700 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=3))) +#else +#define MIN_VERSION_base(major1,major2,minor) (0) #endif +#endif // MIN_VERSION_base was not defined - -#endif +#endif // This file was already included From git at git.haskell.org Fri Jan 23 22:42:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:55 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Merge pull request #31 from spl/patch-1 (f37493f) Message-ID: <20150123224255.00AB03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/f37493f330bb9e114101b6294a335bdd299259f0 >--------------------------------------------------------------- commit f37493f330bb9e114101b6294a335bdd299259f0 Merge: a562ab2 d4798e9 Author: Gregory Collins Date: Fri Oct 24 18:22:09 2014 +0200 Merge pull request #31 from spl/patch-1 Fix typos: rename funtion to function >--------------------------------------------------------------- f37493f330bb9e114101b6294a335bdd299259f0 Data/ByteString/Unsafe.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:55 +0000 (UTC) Subject: [commit: packages/containers] master: Fix warnings. (2bdc5f3) Message-ID: <20150123224255.BD5903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/2bdc5f38f740f43b49bad0a53c81b9d4a25a56bd >--------------------------------------------------------------- commit 2bdc5f38f740f43b49bad0a53c81b9d4a25a56bd Author: Milan Straka Date: Mon Dec 15 22:47:28 2014 +0100 Fix warnings. In getNodes, pass (a, [a]) instead of an [a] which we know is nonempty. This way we do not have to create void pattern-match case for empty list. Also use STRICT_x_OF_y macros instead of `seq`-ing in every pattern-match case. >--------------------------------------------------------------- 2bdc5f38f740f43b49bad0a53c81b9d4a25a56bd Data/Sequence.hs | 40 ++++++++++++++++++++++++---------------- 1 file changed, 24 insertions(+), 16 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 9a23f77..1f19c62 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -183,7 +183,6 @@ import Data.Data -- Array stuff, with GHC.Arr on GHC import Data.Array (Ix, Array) -import qualified Data.Array #ifdef __GLASGOW_HASKELL__ import qualified GHC.Arr #endif @@ -200,6 +199,15 @@ import qualified GHC.Exts import Data.Functor.Identity (Identity(..)) #endif + +-- Use macros to define strictness of functions. +-- STRICT_x_OF_y denotes an y-ary function strict in the x-th parameter. +-- We do not use BangPatterns, because they are not in any standard and we +-- want the compilers to be compiled by as many compilers as possible. +#define STRICT_1_OF_2(fn) fn arg _ | arg `seq` False = undefined +#define STRICT_1_OF_3(fn) fn arg _ _ | arg `seq` False = undefined + + infixr 5 `consTree` infixl 5 `snocTree` @@ -1783,27 +1791,27 @@ findIndicesR p xs = foldlWithIndex g [] xs -- There is a function 'toList' in the opposite direction for all -- instances of the 'Foldable' class, including 'Seq'. fromList :: [a] -> Seq a -fromList xs = Seq $ mkTree 1 $ map_elem xs +fromList = Seq . mkTree 1 . map_elem where {-# SPECIALIZE mkTree :: Int -> [Elem a] -> FingerTree (Elem a) #-} {-# SPECIALIZE mkTree :: Int -> [Node a] -> FingerTree (Node a) #-} mkTree :: (Sized a) => Int -> [a] -> FingerTree a - mkTree s [] = s `seq` Empty - mkTree s [x1] = s `seq` Single x1 + STRICT_1_OF_2(mkTree) + mkTree _ [] = Empty + mkTree _ [x1] = Single x1 mkTree s [x1, x2] = Deep (2*s) (One x1) Empty (One x2) mkTree s [x1, x2, x3] = Deep (3*s) (One x1) Empty (Two x2 x3) - mkTree s (x1:x2:x3:xs) = s `seq` case getNodes (3*s) xs of - (ns, sf) -> m `seq` deep' (Three x1 x2 x3) m sf - where m = mkTree (3*s) ns - - deep' pr@(Three x1 _ _) m sf = Deep (3*size x1 + size m + size sf) pr m sf - - getNodes :: Int -> [a] -> ([Node a], Digit a) - getNodes s [x1] = s `seq` ([], One x1) - getNodes s [x1, x2] = s `seq` ([], Two x1 x2) - getNodes s [x1, x2, x3] = s `seq` ([], Three x1 x2 x3) - getNodes s (x1:x2:x3:xs) = s `seq` (Node3 s x1 x2 x3:ns, d) - where (ns, d) = getNodes s xs + mkTree s (x1:x2:x3:x4:xs) = case getNodes (3*s) x4 xs of + (ns, sf) -> case mkTree (3*s) ns of + m -> m `seq` Deep (3*size x1 + size m + size sf) (Three x1 x2 x3) m sf + + getNodes :: Int -> a -> [a] -> ([Node a], Digit a) + STRICT_1_OF_3(getNodes) + getNodes _ x1 [] = ([], One x1) + getNodes _ x1 [x2] = ([], Two x1 x2) + getNodes _ x1 [x2, x3] = ([], Three x1 x2 x3) + getNodes s x1 (x2:x3:x4:xs) = (Node3 s x1 x2 x3:ns, d) + where (ns, d) = getNodes s x4 xs map_elem :: [a] -> [Elem a] #if __GLASGOW_HASKELL__ >= 708 From git at git.haskell.org Fri Jan 23 22:42:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:56 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #133 from treeowl/minversionbase (414bd0e) Message-ID: <20150123224256.1B0453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/414bd0e566a7025d24678bee556f610b1f5637f5 >--------------------------------------------------------------- commit 414bd0e566a7025d24678bee556f610b1f5637f5 Merge: fabde6b 3dddb04 Author: Milan Straka Date: Mon Jan 19 09:49:31 2015 +0100 Merge pull request #133 from treeowl/minversionbase Improve MIN_VERSION_base fall-back >--------------------------------------------------------------- 414bd0e566a7025d24678bee556f610b1f5637f5 include/containers.h | 27 +++++++++++++++++++++++---- 1 file changed, 23 insertions(+), 4 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:57 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Merge pull request #21 from Lemmih/master (39de720) Message-ID: <20150123224257.0C1553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/39de720ea653b3977a2404b6236c56431bccf4e3 >--------------------------------------------------------------- commit 39de720ea653b3977a2404b6236c56431bccf4e3 Merge: f37493f e97df17 Author: Duncan Coutts Date: Sun Nov 9 16:09:22 2014 +0000 Merge pull request #21 from Lemmih/master Use S.foldl' on each chunk when strictly folding a lazy bytestring. >--------------------------------------------------------------- 39de720ea653b3977a2404b6236c56431bccf4e3 Data/ByteString/Lazy.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:42:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:57 +0000 (UTC) Subject: [commit: packages/containers] master: Nuke include/Typeable.h, create include/containers.h instead. (b3257c8) Message-ID: <20150123224257.D3F113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/b3257c8b59a9f4dec03be19b6d2cd7a562691e04 >--------------------------------------------------------------- commit b3257c8b59a9f4dec03be19b6d2cd7a562691e04 Author: Milan Straka Date: Mon Dec 15 23:48:18 2014 +0100 Nuke include/Typeable.h, create include/containers.h instead. The "Typeable.h" collides with the header of same name in base. The new "containers.h" is now used in every Haskell source. It contains more stuff used across the containers codebase: - INSTANCE_TYPEABLE[0-2] (was in Typeable.h) - include MachDeps on __GLASGOW_HASKELL__ to define WORD_SIZE_IN_BITS - define STRICT_x_OF_y macros - define MIN_VERSION_base if not defined by cabal (during cabal-less build) >--------------------------------------------------------------- b3257c8b59a9f4dec03be19b6d2cd7a562691e04 Data/Graph.hs | 3 +++ Data/IntMap.hs | 3 +++ Data/IntMap/Base.hs | 15 ++--------- Data/IntMap/Lazy.hs | 3 +++ Data/IntMap/Strict.hs | 3 +++ Data/IntSet.hs | 3 +++ Data/IntSet/Base.hs | 25 +++---------------- Data/Map.hs | 3 +++ Data/Map/Base.hs | 20 +++------------ Data/Map/Lazy.hs | 3 +++ Data/Map/Strict.hs | 23 ++++------------- Data/Sequence.hs | 18 +++----------- Data/Set.hs | 3 +++ Data/Set/Base.hs | 19 +++----------- Data/Tree.hs | 9 ++----- Data/Utils/BitUtil.hs | 8 +++--- Data/Utils/StrictFold.hs | 3 +++ Data/Utils/StrictPair.hs | 3 +++ containers.cabal | 2 +- include/Typeable.h | 65 ------------------------------------------------ include/containers.h | 61 +++++++++++++++++++++++++++++++++++++++++++++ 21 files changed, 116 insertions(+), 179 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b3257c8b59a9f4dec03be19b6d2cd7a562691e04 From git at git.haskell.org Fri Jan 23 22:42:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:59 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Merge pull request #25 from thomie/T5861 (8faa3ab) Message-ID: <20150123224259.1672E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/8faa3ab90879a5a11acc939bffd063e717392319 >--------------------------------------------------------------- commit 8faa3ab90879a5a11acc939bffd063e717392319 Merge: 39de720 da4c7e9 Author: Duncan Coutts Date: Sun Nov 9 16:34:09 2014 +0000 Merge pull request #25 from thomie/T5861 Don't mention ISO-8859-1 in doc string for hGetContents >--------------------------------------------------------------- 8faa3ab90879a5a11acc939bffd063e717392319 Data/ByteString.hs | 3 --- 1 file changed, 3 deletions(-) From git at git.haskell.org Fri Jan 23 22:42:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:42:59 +0000 (UTC) Subject: [commit: packages/containers] master: Add the include dir also to tests. (040309f) Message-ID: <20150123224259.DA9A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/040309f6915306cc7aa7da02f144fe026e4fb6fe >--------------------------------------------------------------- commit 040309f6915306cc7aa7da02f144fe026e4fb6fe Author: Milan Straka Date: Tue Dec 16 00:24:50 2014 +0100 Add the include dir also to tests. This worked with Typeable because Typeable from `base` instead of `containers` was used. >--------------------------------------------------------------- 040309f6915306cc7aa7da02f144fe026e4fb6fe containers.cabal | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/containers.cabal b/containers.cabal index afd2e34..6c77693 100644 --- a/containers.cabal +++ b/containers.cabal @@ -85,6 +85,7 @@ Test-suite map-lazy-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -102,6 +103,7 @@ Test-suite map-strict-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -119,6 +121,7 @@ Test-suite set-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -136,6 +139,7 @@ Test-suite intmap-lazy-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -153,6 +157,7 @@ Test-suite intmap-strict-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -170,6 +175,7 @@ Test-suite intset-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -187,6 +193,7 @@ Test-suite deprecated-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -202,6 +209,7 @@ Test-suite seq-properties build-depends: base >= 4.2 && < 5, array, deepseq >= 1.2 && < 1.5, ghc-prim ghc-options: -O2 + include-dirs: include extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types build-depends: @@ -225,6 +233,7 @@ test-suite map-strictness-properties test-framework-quickcheck2 >= 0.2.9 ghc-options: -Wall + include-dirs: include test-suite intmap-strictness-properties hs-source-dirs: tests, . @@ -242,3 +251,4 @@ test-suite intmap-strictness-properties test-framework-quickcheck2 >= 0.2.9 ghc-options: -Wall + include-dirs: include From git at git.haskell.org Fri Jan 23 22:43:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:01 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Fix haddock references to the ASCII module (b060048) Message-ID: <20150123224301.1F38C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/b060048ab082cc362070ee4713848912c442d4ff >--------------------------------------------------------------- commit b060048ab082cc362070ee4713848912c442d4ff Author: Duncan Coutts Date: Sun Nov 9 16:58:04 2014 +0000 Fix haddock references to the ASCII module Spotted by ivanm. >--------------------------------------------------------------- b060048ab082cc362070ee4713848912c442d4ff Data/ByteString/Builder.hs | 15 ++++----------- Data/ByteString/Builder/ASCII.hs | 8 +++++++- 2 files changed, 11 insertions(+), 12 deletions(-) diff --git a/Data/ByteString/Builder.hs b/Data/ByteString/Builder.hs index 6ee44d0..9307872 100644 --- a/Data/ByteString/Builder.hs +++ b/Data/ByteString/Builder.hs @@ -226,15 +226,13 @@ module Data.ByteString.Builder , doubleLE -- ** Character encodings + -- | Conversion from 'Char' and 'String' into 'Builder's in various encodings. -- *** ASCII (Char7) -- | The ASCII encoding is a 7-bit encoding. The /Char7/ encoding implemented here -- works by truncating the Unicode codepoint to 7-bits, prefixing it -- with a leading 0, and encoding the resulting 8-bits as a single byte. - -- For the codepoints 0-127 this corresponds the ASCII encoding. In - -- "Data.ByteString.Builder.ASCII", we also provide efficient - -- implementations of ASCII-based encodings of numbers (e.g., decimal and - -- hexadecimal encodings). + -- For the codepoints 0-127 this corresponds the ASCII encoding. , char7 , string7 @@ -242,19 +240,14 @@ module Data.ByteString.Builder -- | The ISO/IEC 8859-1 encoding is an 8-bit encoding often known as Latin-1. -- The /Char8/ encoding implemented here works by truncating the Unicode codepoint -- to 8-bits and encoding them as a single byte. For the codepoints 0-255 this corresponds - -- to the ISO/IEC 8859-1 encoding. Note that you can also use - -- the functions from "Data.ByteString.Builder.ASCII", as the ASCII encoding - -- and ISO/IEC 8859-1 are equivalent on the codepoints 0-127. + -- to the ISO/IEC 8859-1 encoding. , char8 , string8 -- *** UTF-8 -- | The UTF-8 encoding can encode /all/ Unicode codepoints. We recommend -- using it always for encoding 'Char's and 'String's unless an application - -- really requires another encoding. Note that you can also use the - -- functions from "Data.ByteString.Builder.ASCII" for UTF-8 encoding, - -- as the ASCII encoding is equivalent to the UTF-8 encoding on the Unicode - -- codepoints 0-127. + -- really requires another encoding. , charUtf8 , stringUtf8 diff --git a/Data/ByteString/Builder/ASCII.hs b/Data/ByteString/Builder/ASCII.hs index ffd2ad7..e0d6bdf 100644 --- a/Data/ByteString/Builder/ASCII.hs +++ b/Data/ByteString/Builder/ASCII.hs @@ -14,7 +14,13 @@ -- module Data.ByteString.Builder.ASCII ( - -- ** ASCII text + -- ** Formatting numbers as text + -- | Formatting of numbers as ASCII text. + -- + -- Note that you can also use these functions for the ISO/IEC 8859-1 and + -- UTF-8 encodings, as the ASCII encoding is equivalent on the + -- codepoints 0-127. + -- *** Decimal numbers -- | Decimal encoding of numbers using ASCII encoded characters. int8Dec From git at git.haskell.org Fri Jan 23 22:43:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:01 +0000 (UTC) Subject: [commit: packages/containers] master: Disable coercion tests for the time being. (bc74f91) Message-ID: <20150123224301.E42983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/bc74f915a5c223ae976290161b1b2f4ef7ea5b41 >--------------------------------------------------------------- commit bc74f915a5c223ae976290161b1b2f4ef7ea5b41 Author: Milan Straka Date: Tue Dec 16 09:38:16 2014 +0100 Disable coercion tests for the time being. >--------------------------------------------------------------- bc74f915a5c223ae976290161b1b2f4ef7ea5b41 tests-ghc/all.T | 5 ----- tests-ghc/unreliable/README | 2 ++ tests-ghc/{all.T => unreliable/coerce_tests} | 7 ------- tests-ghc/{ => unreliable}/mapcoerceintmap.hs | 0 tests-ghc/{ => unreliable}/mapcoerceintmap.stdout | 0 tests-ghc/{ => unreliable}/mapcoerceintmapstrict.hs | 0 tests-ghc/{ => unreliable}/mapcoerceintmapstrict.hs.stdout | 0 tests-ghc/{ => unreliable}/mapcoercemap.hs | 0 tests-ghc/{ => unreliable}/mapcoercemap.stdout | 0 tests-ghc/{ => unreliable}/mapcoerceseq.hs | 0 tests-ghc/{ => unreliable}/mapcoerceseq.stdout | 0 tests-ghc/{ => unreliable}/mapcoercesmap.hs | 0 tests-ghc/{ => unreliable}/mapcoercesmap.stdout | 0 13 files changed, 2 insertions(+), 12 deletions(-) diff --git a/tests-ghc/all.T b/tests-ghc/all.T index eba1dcc..b7887dc 100644 --- a/tests-ghc/all.T +++ b/tests-ghc/all.T @@ -5,8 +5,3 @@ test('datamap001', normal, compile_and_run, ['-package containers']) test('datamap002', normal, compile_and_run, ['-package containers']) test('dataintset001', normal, compile_and_run, ['-package containers']) test('sequence001', normal, compile_and_run, ['-package containers']) -test('mapcoerceseq', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) -test('mapcoercemap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) -test('mapcoercesmap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) -test('mapcoerceintmap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) -test('mapcoerceintmapstrict', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) diff --git a/tests-ghc/unreliable/README b/tests-ghc/unreliable/README new file mode 100644 index 0000000..23240fe --- /dev/null +++ b/tests-ghc/unreliable/README @@ -0,0 +1,2 @@ +These coerce tests depend on whether RULES are fired or not, +so adding them to general GHC suite might cause testing failures. diff --git a/tests-ghc/all.T b/tests-ghc/unreliable/coerce_tests similarity index 55% copy from tests-ghc/all.T copy to tests-ghc/unreliable/coerce_tests index eba1dcc..5cc72d0 100644 --- a/tests-ghc/all.T +++ b/tests-ghc/unreliable/coerce_tests @@ -1,10 +1,3 @@ -# This is a test script for use with GHC's testsuite framework, see -# http://darcs.haskell.org/testsuite - -test('datamap001', normal, compile_and_run, ['-package containers']) -test('datamap002', normal, compile_and_run, ['-package containers']) -test('dataintset001', normal, compile_and_run, ['-package containers']) -test('sequence001', normal, compile_and_run, ['-package containers']) test('mapcoerceseq', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) test('mapcoercemap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) test('mapcoercesmap', when(compiler_ge('ghc','7.9')), compile_and_run, ['-package containers']) diff --git a/tests-ghc/mapcoerceintmap.hs b/tests-ghc/unreliable/mapcoerceintmap.hs similarity index 100% rename from tests-ghc/mapcoerceintmap.hs rename to tests-ghc/unreliable/mapcoerceintmap.hs diff --git a/tests-ghc/mapcoerceintmap.stdout b/tests-ghc/unreliable/mapcoerceintmap.stdout similarity index 100% rename from tests-ghc/mapcoerceintmap.stdout rename to tests-ghc/unreliable/mapcoerceintmap.stdout diff --git a/tests-ghc/mapcoerceintmapstrict.hs b/tests-ghc/unreliable/mapcoerceintmapstrict.hs similarity index 100% rename from tests-ghc/mapcoerceintmapstrict.hs rename to tests-ghc/unreliable/mapcoerceintmapstrict.hs diff --git a/tests-ghc/mapcoerceintmapstrict.hs.stdout b/tests-ghc/unreliable/mapcoerceintmapstrict.hs.stdout similarity index 100% rename from tests-ghc/mapcoerceintmapstrict.hs.stdout rename to tests-ghc/unreliable/mapcoerceintmapstrict.hs.stdout diff --git a/tests-ghc/mapcoercemap.hs b/tests-ghc/unreliable/mapcoercemap.hs similarity index 100% rename from tests-ghc/mapcoercemap.hs rename to tests-ghc/unreliable/mapcoercemap.hs diff --git a/tests-ghc/mapcoercemap.stdout b/tests-ghc/unreliable/mapcoercemap.stdout similarity index 100% rename from tests-ghc/mapcoercemap.stdout rename to tests-ghc/unreliable/mapcoercemap.stdout diff --git a/tests-ghc/mapcoerceseq.hs b/tests-ghc/unreliable/mapcoerceseq.hs similarity index 100% rename from tests-ghc/mapcoerceseq.hs rename to tests-ghc/unreliable/mapcoerceseq.hs diff --git a/tests-ghc/mapcoerceseq.stdout b/tests-ghc/unreliable/mapcoerceseq.stdout similarity index 100% rename from tests-ghc/mapcoerceseq.stdout rename to tests-ghc/unreliable/mapcoerceseq.stdout diff --git a/tests-ghc/mapcoercesmap.hs b/tests-ghc/unreliable/mapcoercesmap.hs similarity index 100% rename from tests-ghc/mapcoercesmap.hs rename to tests-ghc/unreliable/mapcoercesmap.hs diff --git a/tests-ghc/mapcoercesmap.stdout b/tests-ghc/unreliable/mapcoercesmap.stdout similarity index 100% rename from tests-ghc/mapcoercesmap.stdout rename to tests-ghc/unreliable/mapcoercesmap.stdout From git at git.haskell.org Fri Jan 23 22:43:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:03 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x, master: Fix documented complexity of unsafePackMallocCStringLen (9f0ee6b) Message-ID: <20150123224303.286F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branches: 0.10.4.x,master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/9f0ee6bf37d3a3c64c9461fb60541ed47c043d25 >--------------------------------------------------------------- commit 9f0ee6bf37d3a3c64c9461fb60541ed47c043d25 Author: Duncan Coutts Date: Sun Nov 9 18:44:08 2014 +0000 Fix documented complexity of unsafePackMallocCStringLen It is indeed O(1). Spotted by polarina. >--------------------------------------------------------------- 9f0ee6bf37d3a3c64c9461fb60541ed47c043d25 Data/ByteString/Unsafe.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/ByteString/Unsafe.hs b/Data/ByteString/Unsafe.hs index bf0ed88..cc0522a 100644 --- a/Data/ByteString/Unsafe.hs +++ b/Data/ByteString/Unsafe.hs @@ -250,7 +250,7 @@ unsafePackMallocCString cstr = do len <- c_strlen cstr return $! PS fp 0 (fromIntegral len) --- | /O(n)/ Build a @ByteString@ from a malloced @CStringLen at . This +-- | /O(1)/ Build a @ByteString@ from a malloced @CStringLen at . This -- value will have a @free(3)@ finalizer associated to it. -- -- This function is /unsafe/. If the original @CString@ is later From git at git.haskell.org Fri Jan 23 22:43:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:03 +0000 (UTC) Subject: [commit: packages/containers] master: Remove circular `toList` definition. (446e295) Message-ID: <20150123224303.EC2BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/446e295ee0db08bb10f6e5dca6f930669b565ffc >--------------------------------------------------------------- commit 446e295ee0db08bb10f6e5dca6f930669b565ffc Author: Milan Straka Date: Tue Dec 16 11:11:07 2014 +0100 Remove circular `toList` definition. When writing this, I assumed we have explicit `toList` as we have in other containers. We do not have `toList`, and even if we did, the code would not compile, as the two `toList`s (ours and `Foldable`) would collide. >--------------------------------------------------------------- 446e295ee0db08bb10f6e5dca6f930669b565ffc Data/Sequence.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 800ec46..b540978 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -247,8 +247,6 @@ instance Foldable Seq where {-# INLINE length #-} null = null {-# INLINE null #-} - toList = toList - {-# INLINE toList #-} #endif instance Traversable Seq where From git at git.haskell.org Fri Jan 23 22:43:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:05 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x: Revert API additions so we can make a bug-fix only release (26839ac) Message-ID: <20150123224305.36EF23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : 0.10.4.x Link : http://git.haskell.org/packages/bytestring.git/commitdiff/26839acdd06b33290c483b46ef6ad7fa21aa9151 >--------------------------------------------------------------- commit 26839acdd06b33290c483b46ef6ad7fa21aa9151 Author: Duncan Coutts Date: Sun Nov 9 21:53:44 2014 +0000 Revert API additions so we can make a bug-fix only release This lets us make a 0.10.4.x release rather than having to go straight to 0.10.6.0. A 0.10.6.0 release will follow for ghc-7.10 with some API additions. >--------------------------------------------------------------- 26839acdd06b33290c483b46ef6ad7fa21aa9151 Data/ByteString.hs | 73 +++++++++++++++++++-------------------- Data/ByteString/Char8.hs | 8 ++--- Data/ByteString/Internal.hs | 28 ++++++--------- Data/ByteString/Lazy.hs | 20 ++++++++--- Data/ByteString/Short/Internal.hs | 8 ++--- Data/ByteString/Unsafe.hs | 6 ++-- 6 files changed, 70 insertions(+), 73 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 26839acdd06b33290c483b46ef6ad7fa21aa9151 From git at git.haskell.org Fri Jan 23 22:43:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:05 +0000 (UTC) Subject: [commit: packages/containers] master: Import only used class methods of Foldable. (6b026a7) Message-ID: <20150123224305.F358E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/6b026a7a730569d21b27ad2a8c18961cd8662a35 >--------------------------------------------------------------- commit 6b026a7a730569d21b27ad2a8c18961cd8662a35 Author: Milan Straka Date: Tue Dec 16 14:12:37 2014 +0100 Import only used class methods of Foldable. On GHC 7.8, the Foldable class contains also null and length, which conflicts with Data.Sequence{null,length}. >--------------------------------------------------------------- 6b026a7a730569d21b27ad2a8c18961cd8662a35 tests/seq-properties.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index a64e66d..4cf0876 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -3,7 +3,7 @@ import Data.Sequence -- needs to be compiled with -DTESTING for use here import Control.Applicative (Applicative(..)) import Control.Arrow ((***)) import Data.Array (listArray) -import Data.Foldable (Foldable(..), toList, all, sum) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1), toList, all, sum) import Data.Functor ((<$>), (<$)) import Data.Maybe import Data.Monoid (Monoid(..)) From git at git.haskell.org Fri Jan 23 22:43:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:07 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x: Add link to this target for source repo (5a60134) Message-ID: <20150123224307.421743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : 0.10.4.x Link : http://git.haskell.org/packages/bytestring.git/commitdiff/5a60134b00ff3ebb2db1e9ab3be802f4dea758f6 >--------------------------------------------------------------- commit 5a60134b00ff3ebb2db1e9ab3be802f4dea758f6 Author: Duncan Coutts Date: Sun Nov 9 22:00:16 2014 +0000 Add link to this target for source repo >--------------------------------------------------------------- 5a60134b00ff3ebb2db1e9ab3be802f4dea758f6 bytestring.cabal | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/bytestring.cabal b/bytestring.cabal index 73f9235..5deed76 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -64,6 +64,12 @@ source-repository head type: git location: https://github.com/haskell/bytestring +source-repository this + type: git + location: https://github.com/haskell/bytestring + branch: 0.10.4.x + tag: 0.10.4.1 + flag integer-simple description: Use the simple integer library instead of GMP default: False From git at git.haskell.org Fri Jan 23 22:43:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:08 +0000 (UTC) Subject: [commit: packages/containers] master: It is perfectly fine to import class methods... (d288dc7) Message-ID: <20150123224308.08D1E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/d288dc750949e476af221a832dea8d8c053808a4 >--------------------------------------------------------------- commit d288dc750949e476af221a832dea8d8c053808a4 Author: Milan Straka Date: Tue Dec 16 14:16:20 2014 +0100 It is perfectly fine to import class methods... ...without specifying the class, see Haskell 2010 5.2.1. That allows us to get rid of some conditional includes. Nevetheless, we still conditionally include foldr', as we do not use it for base <4.8. >--------------------------------------------------------------- d288dc750949e476af221a832dea8d8c053808a4 Data/Sequence.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index b540978..7d31f79 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -158,14 +158,9 @@ import Control.DeepSeq (NFData(rnf)) import Control.Monad (MonadPlus(..), ap) import Data.Monoid (Monoid(..)) import Data.Functor (Functor(..)) -#if MIN_VERSION_base(4,8,0) -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr', toList)) -#else -#if MIN_VERSION_base(4,6,0) -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl'), toList) -#else import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), foldl', toList) -#endif +#if MIN_VERSION_base(4,8,0) +import Data.Foldable (foldr') #endif import Data.Traversable import Data.Typeable From git at git.haskell.org Fri Jan 23 22:43:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:09 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x: Add a changelog (7d8d3b4) Message-ID: <20150123224309.4C06D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : 0.10.4.x Link : http://git.haskell.org/packages/bytestring.git/commitdiff/7d8d3b46e51cfd2c5fdb7292d60a25f0cee34744 >--------------------------------------------------------------- commit 7d8d3b46e51cfd2c5fdb7292d60a25f0cee34744 Author: Duncan Coutts Date: Sun Nov 9 22:02:02 2014 +0000 Add a changelog And drop Don as a listed maintainer. >--------------------------------------------------------------- 7d8d3b46e51cfd2c5fdb7292d60a25f0cee34744 Changelog.md | 11 +++++++++++ bytestring.cabal | 3 +-- 2 files changed, 12 insertions(+), 2 deletions(-) diff --git a/Changelog.md b/Changelog.md new file mode 100644 index 0000000..e9e805c --- /dev/null +++ b/Changelog.md @@ -0,0 +1,11 @@ + +0.10.5.x (current development version) + * Rename inlinePerformIO so people don't misuse it + +0.10.4.1 Duncan Coutts Nov 2014 + + * Fix integer overflow in concatenation functions + * Fix strictness of lazy bytestring foldl' + * Numerous minor documentation fixes + * Various testsuite improvements + diff --git a/bytestring.cabal b/bytestring.cabal index 5deed76..12ea707 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -51,8 +51,7 @@ Copyright: Copyright (c) Don Stewart 2005-2009, Author: Don Stewart, Duncan Coutts -Maintainer: Don Stewart , - Duncan Coutts +Maintainer: Duncan Coutts Homepage: https://github.com/haskell/bytestring Bug-reports: https://github.com/haskell/bytestring/issues Tested-With: GHC==7.8.1, GHC==7.6.3, GHC==7.4.2, GHC==7.0.4, GHC==6.12.3 From git at git.haskell.org Fri Jan 23 22:43:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:10 +0000 (UTC) Subject: [commit: packages/containers] master: Add forgotten foldMap to the imports. (4a6bbb1) Message-ID: <20150123224310.0F8A63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/4a6bbb14e6d982825235a521510afd55c565cc59 >--------------------------------------------------------------- commit 4a6bbb14e6d982825235a521510afd55c565cc59 Author: Milan Straka Date: Tue Dec 16 14:32:23 2014 +0100 Add forgotten foldMap to the imports. The foldMap is in Prelude on base 4.8, that is why I missed it. >--------------------------------------------------------------- 4a6bbb14e6d982825235a521510afd55c565cc59 tests/seq-properties.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index 4cf0876..4f4f468 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -3,7 +3,7 @@ import Data.Sequence -- needs to be compiled with -DTESTING for use here import Control.Applicative (Applicative(..)) import Control.Arrow ((***)) import Data.Array (listArray) -import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1), toList, all, sum) +import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap), toList, all, sum) import Data.Functor ((<$>), (<$)) import Data.Maybe import Data.Monoid (Monoid(..)) From git at git.haskell.org Fri Jan 23 22:43:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:11 +0000 (UTC) Subject: [commit: packages/bytestring] 0.10.4.x: Improve the author credits (030f566) Message-ID: <20150123224311.55E2F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : 0.10.4.x Link : http://git.haskell.org/packages/bytestring.git/commitdiff/030f5669bcb48285a9b19577e05da854c762b907 >--------------------------------------------------------------- commit 030f5669bcb48285a9b19577e05da854c762b907 Author: Duncan Coutts Date: Sun Nov 9 22:05:52 2014 +0000 Improve the author credits The fusion system was never actually used. Credit Simon Meier for the builder stuff. >--------------------------------------------------------------- 030f5669bcb48285a9b19577e05da854c762b907 README.md | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index f329a8e..b1e7948 100644 --- a/README.md +++ b/README.md @@ -33,6 +33,6 @@ cabal test `ByteString` was derived from the GHC `PackedString` library, originally written by Bryan O'Sullivan, and then by Simon Marlow. It was adapted and greatly extended for darcs by David Roundy and -others. Don Stewart cleaned up and further extended the implementation. -Duncan Coutts wrote much of the `.Lazy` code. Don, Duncan and Roman -Leshchinskiy wrote the fusion system. +others. Don Stewart and Duncan Coutts cleaned up and further extended +the implementation and added the `.Lazy` code. Simon Meier contributed +the `Builder` feature. From git at git.haskell.org Fri Jan 23 22:43:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:12 +0000 (UTC) Subject: [commit: packages/containers] master: Bump version number to 0.5.6.1 (ddf4e4a) Message-ID: <20150123224312.163073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/ddf4e4a7abbfb81161251437a6a5bbe8167a7cde >--------------------------------------------------------------- commit ddf4e4a7abbfb81161251437a6a5bbe8167a7cde Author: Milan Straka Date: Tue Dec 16 14:41:17 2014 +0100 Bump version number to 0.5.6.1 >--------------------------------------------------------------- ddf4e4a7abbfb81161251437a6a5bbe8167a7cde containers.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/containers.cabal b/containers.cabal index 6c77693..169507a 100644 --- a/containers.cabal +++ b/containers.cabal @@ -1,5 +1,5 @@ name: containers -version: 0.5.6.0 +version: 0.5.6.1 license: BSD3 license-file: LICENSE maintainer: fox at ucw.cz From git at git.haskell.org Fri Jan 23 22:43:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:13 +0000 (UTC) Subject: [commit: packages/bytestring] master: Add a changelog (5475757) Message-ID: <20150123224313.61D463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/547575709eeb723c12574452dc5da1184e08d5e5 >--------------------------------------------------------------- commit 547575709eeb723c12574452dc5da1184e08d5e5 Author: Duncan Coutts Date: Sun Nov 9 22:02:02 2014 +0000 Add a changelog And drop Don as a listed maintainer. >--------------------------------------------------------------- 547575709eeb723c12574452dc5da1184e08d5e5 Changelog.md | 11 +++++++++++ bytestring.cabal | 3 +-- 2 files changed, 12 insertions(+), 2 deletions(-) diff --git a/Changelog.md b/Changelog.md new file mode 100644 index 0000000..e9e805c --- /dev/null +++ b/Changelog.md @@ -0,0 +1,11 @@ + +0.10.5.x (current development version) + * Rename inlinePerformIO so people don't misuse it + +0.10.4.1 Duncan Coutts Nov 2014 + + * Fix integer overflow in concatenation functions + * Fix strictness of lazy bytestring foldl' + * Numerous minor documentation fixes + * Various testsuite improvements + diff --git a/bytestring.cabal b/bytestring.cabal index 73f9235..022bc6b 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -51,8 +51,7 @@ Copyright: Copyright (c) Don Stewart 2005-2009, Author: Don Stewart, Duncan Coutts -Maintainer: Don Stewart , - Duncan Coutts +Maintainer: Duncan Coutts Homepage: https://github.com/haskell/bytestring Bug-reports: https://github.com/haskell/bytestring/issues Tested-With: GHC==7.8.1, GHC==7.6.3, GHC==7.4.2, GHC==7.0.4, GHC==6.12.3 From git at git.haskell.org Fri Jan 23 22:43:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:14 +0000 (UTC) Subject: [commit: packages/containers] master: Fix efficiency claim for zipWith. (107ec12) Message-ID: <20150123224314.1EDCD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/107ec12d17aa98d8fd552276b81a94fe6f44224b >--------------------------------------------------------------- commit 107ec12d17aa98d8fd552276b81a94fe6f44224b Author: David Feuer Date: Thu Dec 18 11:19:53 2014 -0500 Fix efficiency claim for zipWith. >--------------------------------------------------------------- 107ec12d17aa98d8fd552276b81a94fe6f44224b Data/Sequence.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 7d31f79..7675698 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1872,9 +1872,9 @@ reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) -- them up further and zip them with their matching pieces can be delayed until -- they're actually needed. We do the same thing for Digits (splitting into -- between one and four pieces) and Nodes (splitting into two or three). The --- ultimate result is that we can index, or split at, any location in zs in --- O(log(min{i,n-i})) time *immediately*, with only a constant-factor slowdown --- as thunks are forced along the path. +-- ultimate result is that we can index into, or split at, any location in zs +-- in O((log(min{i,n-i}))^2) time *immediately*, while still being able to +-- force all the thunks in O(n) time. -- -- Benchmark info, and alternatives: -- From git at git.haskell.org Fri Jan 23 22:43:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:14 +0000 (UTC) Subject: [commit: packages/binary] tag 'binary-0.7.2.3-release' created Message-ID: <20150123224314.85D123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary New tag : binary-0.7.2.3-release Referencing: 7f715867a1620ee50e30b7657a766b7421ce5f68 From git at git.haskell.org Fri Jan 23 22:43:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:15 +0000 (UTC) Subject: [commit: packages/bytestring] master: Improve the author credits (87aa6ee) Message-ID: <20150123224315.6CE4F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/87aa6ee7f5ad07944295dff4e746a88ec2a44b96 >--------------------------------------------------------------- commit 87aa6ee7f5ad07944295dff4e746a88ec2a44b96 Author: Duncan Coutts Date: Sun Nov 9 22:05:52 2014 +0000 Improve the author credits The fusion system was never actually used. Credit Simon Meier for the builder stuff. >--------------------------------------------------------------- 87aa6ee7f5ad07944295dff4e746a88ec2a44b96 README.md | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index f329a8e..b1e7948 100644 --- a/README.md +++ b/README.md @@ -33,6 +33,6 @@ cabal test `ByteString` was derived from the GHC `PackedString` library, originally written by Bryan O'Sullivan, and then by Simon Marlow. It was adapted and greatly extended for darcs by David Roundy and -others. Don Stewart cleaned up and further extended the implementation. -Duncan Coutts wrote much of the `.Lazy` code. Don, Duncan and Roman -Leshchinskiy wrote the fusion system. +others. Don Stewart and Duncan Coutts cleaned up and further extended +the implementation and added the `.Lazy` code. Simon Meier contributed +the `Builder` feature. From git at git.haskell.org Fri Jan 23 22:43:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:16 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #101 from treeowl/zipdocfix (314f798) Message-ID: <20150123224316.28B123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/314f7983819861c68e77f0f5798c86812b23fa39 >--------------------------------------------------------------- commit 314f7983819861c68e77f0f5798c86812b23fa39 Merge: ddf4e4a 107ec12 Author: Milan Straka Date: Thu Dec 18 22:59:51 2014 +0100 Merge pull request #101 from treeowl/zipdocfix Fix efficiency claim for zipWith. >--------------------------------------------------------------- 314f7983819861c68e77f0f5798c86812b23fa39 Data/Sequence.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Jan 23 22:43:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:18 +0000 (UTC) Subject: [commit: packages/containers] master: Use fromList2 to implement fromListN in IsList (ace8f7f) Message-ID: <20150123224318.318A83A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/ace8f7fd88e5458a8401804e32a2d921d653fdfa >--------------------------------------------------------------- commit ace8f7fd88e5458a8401804e32a2d921d653fdfa Author: David Feuer Date: Fri Dec 19 15:09:03 2014 -0500 Use fromList2 to implement fromListN in IsList >--------------------------------------------------------------- ace8f7fd88e5458a8401804e32a2d921d653fdfa Data/Sequence.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 7d31f79..b216b12 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -1806,6 +1806,7 @@ fromList = Seq . mkTree 1 . map_elem instance GHC.Exts.IsList (Seq a) where type Item (Seq a) = a fromList = fromList + fromListN = fromList2 toList = toList #endif From git at git.haskell.org Fri Jan 23 22:43:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:19 +0000 (UTC) Subject: [commit: packages/bytestring] master: Add support for `deepseq-1.4.0.0` (30e135c) Message-ID: <20150123224319.845613A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/30e135c18f44567797b3a34af6d49ddd52cc6ea1 >--------------------------------------------------------------- commit 30e135c18f44567797b3a34af6d49ddd52cc6ea1 Author: Herbert Valerio Riedel Date: Fri Nov 14 17:33:35 2014 +0100 Add support for `deepseq-1.4.0.0` This change avoids relying on `rnf`'s default method implementation which has changed in `deepseq-1.4.0.0` NB: previously uploaded `bytestring` releases on Hackage need retroactive upper bounds on `deepseq` >--------------------------------------------------------------- 30e135c18f44567797b3a34af6d49ddd52cc6ea1 Data/ByteString/Internal.hs | 5 +++-- Data/ByteString/Short/Internal.hs | 3 ++- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/Data/ByteString/Internal.hs b/Data/ByteString/Internal.hs index 15192c1..703c136 100644 --- a/Data/ByteString/Internal.hs +++ b/Data/ByteString/Internal.hs @@ -94,7 +94,7 @@ import Foreign.C.Types (CInt, CSize, CULong) import Foreign.C.String (CString) import Data.Monoid (Monoid(..)) -import Control.DeepSeq (NFData) +import Control.DeepSeq (NFData(rnf)) #if MIN_VERSION_base(3,0,0) import Data.String (IsString(..)) @@ -212,7 +212,8 @@ instance Monoid ByteString where mappend = append mconcat = concat -instance NFData ByteString +instance NFData ByteString where + rnf (PS _ _ _) = () instance Show ByteString where showsPrec p ps r = showsPrec p (unpackChars ps) r diff --git a/Data/ByteString/Short/Internal.hs b/Data/ByteString/Short/Internal.hs index 9624de2..01630ef 100644 --- a/Data/ByteString/Short/Internal.hs +++ b/Data/ByteString/Short/Internal.hs @@ -136,7 +136,8 @@ instance Monoid ShortByteString where mappend = append mconcat = concat -instance NFData ShortByteString +instance NFData ShortByteString where + rnf (SBS !_) = () instance Show ShortByteString where showsPrec p ps r = showsPrec p (unpackChars ps) r From git at git.haskell.org Fri Jan 23 22:43:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:20 +0000 (UTC) Subject: [commit: packages/containers] master: Fix Arbitrary instance for FingerTree (0086aa7) Message-ID: <20150123224320.389233A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/0086aa753795237cec28be6d2a261708eb7dacf6 >--------------------------------------------------------------- commit 0086aa753795237cec28be6d2a261708eb7dacf6 Author: Ross Paterson Date: Fri Dec 19 23:24:20 2014 +0000 Fix Arbitrary instance for FingerTree The previous version never generated deep trees containing Empty. Also tweaked the size handling so that the tree size is closer to the specified size (though it can still run over a bit). >--------------------------------------------------------------- 0086aa753795237cec28be6d2a261708eb7dacf6 tests/seq-properties.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index 4f4f468..def17b3 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -112,7 +112,15 @@ instance (Arbitrary a, Sized a) => Arbitrary (FingerTree a) where arb :: (Arbitrary a, Sized a) => Int -> Gen (FingerTree a) arb 0 = return Empty arb 1 = Single <$> arbitrary - arb n = deep <$> arbitrary <*> arb (n `div` 2) <*> arbitrary + arb n = do + pr <- arbitrary + sf <- arbitrary + let n_pr = Prelude.length (toList pr) + let n_sf = Prelude.length (toList sf) + -- adding n `div` 7 ensures that n_m >= 0, and makes more Singles + let n_m = max (n `div` 7) ((n - n_pr - n_sf) `div` 3) + m <- arb n_m + return $ deep pr m sf shrink (Deep _ (One a) Empty (One b)) = [Single a, Single b] shrink (Deep _ pr m sf) = From git at git.haskell.org Fri Jan 23 22:43:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:21 +0000 (UTC) Subject: [commit: packages/bytestring] master: Merge pull request #34 from hvr/pr-deepseq-14 (7a7602a) Message-ID: <20150123224321.8EDA93A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/7a7602a142a1deae2e4f73782d88a91f39a0fa98 >--------------------------------------------------------------- commit 7a7602a142a1deae2e4f73782d88a91f39a0fa98 Merge: 27d597b 30e135c Author: Duncan Coutts Date: Fri Nov 14 16:43:53 2014 +0000 Merge pull request #34 from hvr/pr-deepseq-14 Add support for `deepseq-1.4.0.0` >--------------------------------------------------------------- 7a7602a142a1deae2e4f73782d88a91f39a0fa98 Data/ByteString/Internal.hs | 5 +++-- Data/ByteString/Short/Internal.hs | 3 ++- 2 files changed, 5 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Jan 23 22:43:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:22 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #108 from RossPaterson/master (54c3603) Message-ID: <20150123224322.420F23A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/54c36030839949659b9dd4d12b6e92ec22698d40 >--------------------------------------------------------------- commit 54c36030839949659b9dd4d12b6e92ec22698d40 Merge: 314f798 0086aa7 Author: Milan Straka Date: Sat Dec 20 00:50:39 2014 +0100 Merge pull request #108 from RossPaterson/master Fix Arbitrary instance for FingerTree >--------------------------------------------------------------- 54c36030839949659b9dd4d12b6e92ec22698d40 tests/seq-properties.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:43:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:17 +0000 (UTC) Subject: [commit: packages/bytestring] master: Bump to development version 0.10.5.0 (27d597b) Message-ID: <20150123224317.7BD093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/27d597bbec008e14ab8c7ac1c69ebd9c34f456f3 >--------------------------------------------------------------- commit 27d597bbec008e14ab8c7ac1c69ebd9c34f456f3 Author: Duncan Coutts Date: Sun Nov 9 22:10:44 2014 +0000 Bump to development version 0.10.5.0 We do have some API additions since 0.10.4.0 >--------------------------------------------------------------- 27d597bbec008e14ab8c7ac1c69ebd9c34f456f3 bytestring.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/bytestring.cabal b/bytestring.cabal index 022bc6b..794c9e2 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -1,5 +1,5 @@ Name: bytestring -Version: 0.10.4.1 +Version: 0.10.5.0 Synopsis: Fast, compact, strict and lazy byte strings with a list interface Description: An efficient compact, immutable byte string type (both strict and lazy) From git at git.haskell.org Fri Jan 23 22:43:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:23 +0000 (UTC) Subject: [commit: packages/bytestring] master: Update Safe Haskell tags on some modules (a399cdd) Message-ID: <20150123224323.990833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/a399cddc850f7cb1a6175d61f63379542b96d1f0 >--------------------------------------------------------------- commit a399cddc850f7cb1a6175d61f63379542b96d1f0 Author: David Terei Date: Fri Nov 21 13:15:32 2014 -0800 Update Safe Haskell tags on some modules >--------------------------------------------------------------- a399cddc850f7cb1a6175d61f63379542b96d1f0 Data/ByteString/Builder/Prim/ASCII.hs | 3 +++ Data/ByteString/Builder/Prim/Binary.hs | 3 +++ Data/ByteString/Builder/Prim/Internal/Base16.hs | 3 +++ Data/ByteString/Builder/Prim/Internal/Floating.hs | 3 +++ Data/ByteString/Builder/Prim/Internal/UncheckedShifts.hs | 3 +++ Data/ByteString/Unsafe.hs | 3 +++ 6 files changed, 18 insertions(+) diff --git a/Data/ByteString/Builder/Prim/ASCII.hs b/Data/ByteString/Builder/Prim/ASCII.hs index 9ed8316..9a5816d 100644 --- a/Data/ByteString/Builder/Prim/ASCII.hs +++ b/Data/ByteString/Builder/Prim/ASCII.hs @@ -1,4 +1,7 @@ {-# LANGUAGE ScopedTypeVariables, ForeignFunctionInterface #-} +#if __GLASGOW_HASKELL__ >= 701 +{-# LANGUAGE Trustworthy #-} +#endif -- | Copyright : (c) 2010 Jasper Van der Jeugt -- (c) 2010 - 2011 Simon Meier -- License : BSD3-style (see LICENSE) diff --git a/Data/ByteString/Builder/Prim/Binary.hs b/Data/ByteString/Builder/Prim/Binary.hs index e4b133b..136a75a 100644 --- a/Data/ByteString/Builder/Prim/Binary.hs +++ b/Data/ByteString/Builder/Prim/Binary.hs @@ -1,4 +1,7 @@ {-# LANGUAGE CPP, BangPatterns #-} +#if __GLASGOW_HASKELL__ >= 701 +{-# LANGUAGE Trustworthy #-} +#endif -- | Copyright : (c) 2010-2011 Simon Meier -- License : BSD3-style (see LICENSE) -- diff --git a/Data/ByteString/Builder/Prim/Internal/Base16.hs b/Data/ByteString/Builder/Prim/Internal/Base16.hs index 2965450..e27424f 100644 --- a/Data/ByteString/Builder/Prim/Internal/Base16.hs +++ b/Data/ByteString/Builder/Prim/Internal/Base16.hs @@ -1,4 +1,7 @@ {-# LANGUAGE CPP #-} +#if __GLASGOW_HASKELL__ >= 701 +{-# LANGUAGE Trustworthy #-} +#endif -- | -- Copyright : (c) 2011 Simon Meier -- License : BSD3-style (see LICENSE) diff --git a/Data/ByteString/Builder/Prim/Internal/Floating.hs b/Data/ByteString/Builder/Prim/Internal/Floating.hs index f33e63a..0fa85ca 100644 --- a/Data/ByteString/Builder/Prim/Internal/Floating.hs +++ b/Data/ByteString/Builder/Prim/Internal/Floating.hs @@ -1,4 +1,7 @@ {-# LANGUAGE ScopedTypeVariables #-} +#if __GLASGOW_HASKELL__ >= 701 +{-# LANGUAGE Trustworthy #-} +#endif -- | -- Copyright : (c) 2010 Simon Meier -- diff --git a/Data/ByteString/Builder/Prim/Internal/UncheckedShifts.hs b/Data/ByteString/Builder/Prim/Internal/UncheckedShifts.hs index 7673e9a..6d6908a 100644 --- a/Data/ByteString/Builder/Prim/Internal/UncheckedShifts.hs +++ b/Data/ByteString/Builder/Prim/Internal/UncheckedShifts.hs @@ -1,4 +1,7 @@ {-# LANGUAGE CPP, MagicHash #-} +#if __GLASGOW_HASKELL__ >= 703 +{-# LANGUAGE Unsafe #-} +#endif -- | -- Copyright : (c) 2010 Simon Meier -- diff --git a/Data/ByteString/Unsafe.hs b/Data/ByteString/Unsafe.hs index cc0522a..5ac9cc5 100644 --- a/Data/ByteString/Unsafe.hs +++ b/Data/ByteString/Unsafe.hs @@ -2,6 +2,9 @@ #if __GLASGOW_HASKELL__ {-# LANGUAGE MagicHash #-} #endif +#if __GLASGOW_HASKELL__ >= 703 +{-# LANGUAGE Unsafe #-} +#endif -- | -- Module : Data.ByteString.Unsafe From git at git.haskell.org Fri Jan 23 22:43:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:24 +0000 (UTC) Subject: [commit: packages/containers] master: Add tests for Applicative and Monad instances (0decaa1) Message-ID: <20150123224324.4A12E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/0decaa120039ff4bafbfd4cc62306925a2c31475 >--------------------------------------------------------------- commit 0decaa120039ff4bafbfd4cc62306925a2c31475 Author: David Feuer Date: Thu Dec 18 12:44:57 2014 -0500 Add tests for Applicative and Monad instances Unfortunately, these tests are rather slow, so I hid them behind a SLOW_TESTS macro. I don't know nearly enough about cabal to know how to arrange for tests to be run conditionally, so hopefully someone else can set that up properly. >--------------------------------------------------------------- 0decaa120039ff4bafbfd4cc62306925a2c31475 tests/seq-properties.hs | 28 ++++++++++++++++++++++++++++ 1 file changed, 28 insertions(+) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index def17b3..2b4774d 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -17,6 +17,9 @@ import qualified Prelude import qualified Data.List import Test.QuickCheck hiding ((><)) import Test.QuickCheck.Poly +#ifdef SLOW_TESTS +import Test.QuickCheck.Function +#endif import Test.Framework import Test.Framework.Providers.QuickCheck2 @@ -93,6 +96,11 @@ main = defaultMain , testProperty "zipWith3" prop_zipWith3 , testProperty "zip4" prop_zip4 , testProperty "zipWith4" prop_zipWith4 +#ifdef SLOW_TESTS + , testProperty "<*>" prop_ap + , testProperty "*>" prop_then + , testProperty ">>=" prop_bind +#endif ] ------------------------------------------------------------------------ @@ -588,6 +596,26 @@ prop_zipWith4 xs ys zs ts = toList' (zipWith4 f xs ys zs ts) ~= Data.List.zipWith4 f (toList xs) (toList ys) (toList zs) (toList ts) where f = (,,,) +-- Applicative operations + +#ifdef SLOW_TESTS +prop_ap :: Seq A -> Seq B -> Bool +prop_ap xs ys = + toList' ((,) <$> xs <*> ys) ~= ( (,) <$> toList xs <*> toList ys ) + +prop_then :: Seq A -> Seq B -> Bool +prop_then xs ys = + toList' (xs *> ys) ~= (toList xs *> toList ys) +#endif + +-- Monad operations + +#ifdef SLOW_TESTS +prop_bind :: Seq A -> Fun A (Seq B) -> Bool +prop_bind xs (Fun _ f) = + toList' (xs >>= f) ~= (toList xs >>= toList . f) +#endif + -- Simple test monad data M a = Action Int a From git at git.haskell.org Fri Jan 23 22:43:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:25 +0000 (UTC) Subject: [commit: packages/bytestring] master: Merge pull request #36 from dterei/more-safe-haskell (cf3af8f) Message-ID: <20150123224325.A584D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/cf3af8f521fd239cbe2559d74d2478ef55fdf041 >--------------------------------------------------------------- commit cf3af8f521fd239cbe2559d74d2478ef55fdf041 Merge: 7a7602a a399cdd Author: Duncan Coutts Date: Thu Dec 4 17:51:09 2014 +0000 Merge pull request #36 from dterei/more-safe-haskell Update Safe Haskell tags on some modules >--------------------------------------------------------------- cf3af8f521fd239cbe2559d74d2478ef55fdf041 Data/ByteString/Builder/Prim/ASCII.hs | 3 +++ Data/ByteString/Builder/Prim/Binary.hs | 3 +++ Data/ByteString/Builder/Prim/Internal/Base16.hs | 3 +++ Data/ByteString/Builder/Prim/Internal/Floating.hs | 3 +++ Data/ByteString/Builder/Prim/Internal/UncheckedShifts.hs | 3 +++ Data/ByteString/Unsafe.hs | 3 +++ 6 files changed, 18 insertions(+) From git at git.haskell.org Fri Jan 23 22:43:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:26 +0000 (UTC) Subject: [commit: packages/containers] master: Remove CPP (b2b55b0) Message-ID: <20150123224326.53D613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/b2b55b01aa985bb190a3f1580bf55eb2c83eb18f >--------------------------------------------------------------- commit b2b55b01aa985bb190a3f1580bf55eb2c83eb18f Author: David Feuer Date: Fri Dec 19 23:49:35 2014 -0500 Remove CPP >--------------------------------------------------------------- b2b55b01aa985bb190a3f1580bf55eb2c83eb18f tests/seq-properties.hs | 8 -------- 1 file changed, 8 deletions(-) diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs index 2b4774d..880d772 100644 --- a/tests/seq-properties.hs +++ b/tests/seq-properties.hs @@ -17,9 +17,7 @@ import qualified Prelude import qualified Data.List import Test.QuickCheck hiding ((><)) import Test.QuickCheck.Poly -#ifdef SLOW_TESTS import Test.QuickCheck.Function -#endif import Test.Framework import Test.Framework.Providers.QuickCheck2 @@ -96,11 +94,9 @@ main = defaultMain , testProperty "zipWith3" prop_zipWith3 , testProperty "zip4" prop_zip4 , testProperty "zipWith4" prop_zipWith4 -#ifdef SLOW_TESTS , testProperty "<*>" prop_ap , testProperty "*>" prop_then , testProperty ">>=" prop_bind -#endif ] ------------------------------------------------------------------------ @@ -598,7 +594,6 @@ prop_zipWith4 xs ys zs ts = -- Applicative operations -#ifdef SLOW_TESTS prop_ap :: Seq A -> Seq B -> Bool prop_ap xs ys = toList' ((,) <$> xs <*> ys) ~= ( (,) <$> toList xs <*> toList ys ) @@ -606,15 +601,12 @@ prop_ap xs ys = prop_then :: Seq A -> Seq B -> Bool prop_then xs ys = toList' (xs *> ys) ~= (toList xs *> toList ys) -#endif -- Monad operations -#ifdef SLOW_TESTS prop_bind :: Seq A -> Fun A (Seq B) -> Bool prop_bind xs (Fun _ f) = toList' (xs >>= f) ~= (toList xs >>= toList . f) -#endif -- Simple test monad From git at git.haskell.org Fri Jan 23 22:43:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:27 +0000 (UTC) Subject: [commit: packages/bytestring] master: Merge pull request #12 from DaveCTurner/master (eb4514e) Message-ID: <20150123224327.B32AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/eb4514e3f3ee150a39512e0d9b098fb1d010f47b >--------------------------------------------------------------- commit eb4514e3f3ee150a39512e0d9b098fb1d010f47b Merge: cf3af8f 8312989 Author: Duncan Coutts Date: Sun Dec 14 12:41:25 2014 +0000 Merge pull request #12 from DaveCTurner/master Added Data.ByteString.Lazy.elemIndexEnd implementation >--------------------------------------------------------------- eb4514e3f3ee150a39512e0d9b098fb1d010f47b Data/ByteString/Lazy.hs | 23 +++++++++++------------ tests/Properties.hs | 10 ++++++++++ 2 files changed, 21 insertions(+), 12 deletions(-) From git at git.haskell.org Fri Jan 23 22:43:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:28 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #102 from treeowl/validation (5482318) Message-ID: <20150123224328.5D2403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/5482318831df6f67bb3dffca98dfc72d1dcefc7a >--------------------------------------------------------------- commit 5482318831df6f67bb3dffca98dfc72d1dcefc7a Merge: 54c3603 b2b55b0 Author: Milan Straka Date: Sat Dec 20 12:59:45 2014 +0100 Merge pull request #102 from treeowl/validation Add tests for Applicative and Monad instances >--------------------------------------------------------------- 5482318831df6f67bb3dffca98dfc72d1dcefc7a tests/seq-properties.hs | 20 ++++++++++++++++++++ 1 file changed, 20 insertions(+) From git at git.haskell.org Fri Jan 23 22:43:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:29 +0000 (UTC) Subject: [commit: packages/bytestring] master: Replace explicit uses of seq with bang patterns (cf29654) Message-ID: <20150123224329.BF9973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/cf29654289198dc652f306b56812e2e4f22ed9ed >--------------------------------------------------------------- commit cf29654289198dc652f306b56812e2e4f22ed9ed Author: Duncan Coutts Date: Sun Dec 14 13:15:45 2014 +0000 Replace explicit uses of seq with bang patterns >--------------------------------------------------------------- cf29654289198dc652f306b56812e2e4f22ed9ed Data/ByteString.hs | 6 ++---- Data/ByteString/Lazy.hs | 15 +++++++-------- 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/Data/ByteString.hs b/Data/ByteString.hs index b839150..afe1442 100644 --- a/Data/ByteString.hs +++ b/Data/ByteString.hs @@ -1697,8 +1697,7 @@ hGetLine h = else haveBuf h_ buf 0 [] where - fill h_ at Handle__{haByteBuffer,haDevice} buf len xss = - len `seq` do + fill h_ at Handle__{haByteBuffer,haDevice} buf !len xss = do (r,buf') <- Buffered.fillReadBuffer haDevice buf if r == 0 then do writeIORef haByteBuffer buf{ bufR=0, bufL=0 } @@ -1757,8 +1756,7 @@ hGetLine h = wantReadableHandle "Data.ByteString.hGetLine" h $ \ handle_ -> do hGetLineBufferedLoop handle_ ref buf 0 [] hGetLineBufferedLoop handle_ ref - buf at Buffer{ bufRPtr=r, bufWPtr=w, bufBuf=raw } len xss = - len `seq` do + buf at Buffer{ bufRPtr=r, bufWPtr=w, bufBuf=raw } !len xss = do off <- findEOL r w raw let new_len = len + off - r xs <- mkPS raw r off diff --git a/Data/ByteString/Lazy.hs b/Data/ByteString/Lazy.hs index 2bb109d..26b5965 100644 --- a/Data/ByteString/Lazy.hs +++ b/Data/ByteString/Lazy.hs @@ -479,9 +479,8 @@ foldl f z = go z -- | 'foldl\'' is like 'foldl', but strict in the accumulator. foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a foldl' f z = go z - where go a _ | a `seq` False = undefined - go a Empty = a - go a (Chunk c cs) = go (S.foldl' f a c) cs + where go !a Empty = a + go !a (Chunk c cs) = go (S.foldl' f a c) cs {-# INLINE foldl' #-} -- | 'foldr', applied to a binary operator, a starting value @@ -610,7 +609,7 @@ scanl f z = snd . foldl k (z,singleton z) -- > iterate f x == [x, f x, f (f x), ...] -- iterate :: (Word8 -> Word8) -> Word8 -> ByteString -iterate f = unfoldr (\x -> case f x of x' -> x' `seq` Just (x', x')) +iterate f = unfoldr (\x -> case f x of !x' -> Just (x', x')) -- | @'repeat' x@ is an infinite ByteString, with @x@ the value of every -- element. @@ -918,10 +917,10 @@ elemIndexEnd :: Word8 -> ByteString -> Maybe Int64 elemIndexEnd w = elemIndexEnd' 0 where elemIndexEnd' _ Empty = Nothing - elemIndexEnd' n (Chunk c cs) = let - n' = n + S.length c - i = fmap (fromIntegral . (n +)) $ S.elemIndexEnd w c - in n' `seq` i `seq` elemIndexEnd' n' cs `mplus` i + elemIndexEnd' n (Chunk c cs) = + let !n' = n + S.length c + !i = fmap (fromIntegral . (n +)) $ S.elemIndexEnd w c + in elemIndexEnd' n' cs `mplus` i -- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning -- the indices of all elements equal to the query element, in ascending order. From git at git.haskell.org Fri Jan 23 22:43:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:30 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #107 from treeowl/fromListN (ae97ceb) Message-ID: <20150123224330.66F023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/ae97ceb44766fb5e78f23670e09a20a9625b0963 >--------------------------------------------------------------- commit ae97ceb44766fb5e78f23670e09a20a9625b0963 Merge: 5482318 ace8f7f Author: Milan Straka Date: Sat Dec 20 13:06:44 2014 +0100 Merge pull request #107 from treeowl/fromListN Use fromList2 to implement fromListN in IsList >--------------------------------------------------------------- ae97ceb44766fb5e78f23670e09a20a9625b0963 Data/Sequence.hs | 1 + 1 file changed, 1 insertion(+) From git at git.haskell.org Fri Jan 23 22:43:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:31 +0000 (UTC) Subject: [commit: packages/bytestring] master: We should not have exported breakByte, add a deprecation message (ee2b178) Message-ID: <20150123224331.CA1D93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/ee2b178f093c949c4eda934c9ae1a1b64ea19b67 >--------------------------------------------------------------- commit ee2b178f093c949c4eda934c9ae1a1b64ea19b67 Author: Duncan Coutts Date: Sun Dec 14 14:10:44 2014 +0000 We should not have exported breakByte, add a deprecation message >--------------------------------------------------------------- ee2b178f093c949c4eda934c9ae1a1b64ea19b67 Data/ByteString.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Data/ByteString.hs b/Data/ByteString.hs index afe1442..678fb26 100644 --- a/Data/ByteString.hs +++ b/Data/ByteString.hs @@ -929,6 +929,7 @@ breakByte c p = case elemIndex c p of Nothing -> (p,empty) Just n -> (unsafeTake n p, unsafeDrop n p) {-# INLINE breakByte #-} +{-# DEPRECATED breakByte "It is an internal function and should never have been exported. Use 'break (== x)' instead. (There are rewrite rules that handle this special case of 'break'.)" #-} -- | 'breakEnd' behaves like 'break' but from the end of the 'ByteString' -- From git at git.haskell.org Fri Jan 23 22:43:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:32 +0000 (UTC) Subject: [commit: packages/containers] master: Reimplement `<*>` (38b1b81) Message-ID: <20150123224332.6F9133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/38b1b81c8b5536525d0daad9bd8ee9821a3fb929 >--------------------------------------------------------------- commit 38b1b81c8b5536525d0daad9bd8ee9821a3fb929 Author: David Feuer Date: Thu Dec 18 16:31:10 2014 -0500 Reimplement `<*>` Use `coerce` for the `Functor` instance of `Elem` Using `fmap = coerce` for `Elem` speeds up `<*>` by somewhere around 20%. Benchmark results: OLD: benchmarking <*>/ix1000/500000 time 11.47 ms (11.37 ms .. 11.59 ms) 0.999 R? (0.998 R? .. 1.000 R?) mean 11.61 ms (11.52 ms .. 11.73 ms) std dev 279.9 ?s (209.5 ?s .. 385.6 ?s) benchmarking <*>/nf100/2500/rep time 8.530 ms (8.499 ms .. 8.568 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 8.511 ms (8.498 ms .. 8.528 ms) std dev 40.40 ?s (28.55 ?s .. 63.84 ?s) benchmarking <*>/nf100/2500/ff time 27.13 ms (26.16 ms .. 28.70 ms) 0.994 R? (0.988 R? .. 1.000 R?) mean 26.49 ms (26.29 ms .. 27.43 ms) std dev 697.1 ?s (153.0 ?s .. 1.443 ms) benchmarking <*>/nf500/500/rep time 8.421 ms (8.331 ms .. 8.491 ms) 0.991 R? (0.967 R? .. 1.000 R?) mean 8.518 ms (8.417 ms .. 9.003 ms) std dev 529.9 ?s (40.37 ?s .. 1.176 ms) variance introduced by outliers: 32% (moderately inflated) benchmarking <*>/nf500/500/ff time 33.71 ms (33.58 ms .. 33.86 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 33.69 ms (33.62 ms .. 33.76 ms) std dev 150.0 ?s (119.0 ?s .. 191.0 ?s) benchmarking <*>/nf2500/100/rep time 8.390 ms (8.259 ms .. 8.456 ms) 0.997 R? (0.992 R? .. 1.000 R?) mean 8.544 ms (8.441 ms .. 8.798 ms) std dev 402.6 ?s (21.25 ?s .. 714.9 ?s) variance introduced by outliers: 23% (moderately inflated) benchmarking <*>/nf2500/100/ff time 53.69 ms (53.33 ms .. 54.08 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 53.59 ms (53.38 ms .. 53.75 ms) std dev 341.2 ?s (231.7 ?s .. 473.9 ?s) NEW benchmarking <*>/ix1000/500000 time 2.688 ?s (2.607 ?s .. 2.798 ?s) 0.994 R? (0.988 R? .. 1.000 R?) mean 2.632 ?s (2.607 ?s .. 2.715 ?s) std dev 129.9 ns (65.93 ns .. 242.8 ns) variance introduced by outliers: 64% (severely inflated) benchmarking <*>/nf100/2500/rep time 8.371 ms (8.064 ms .. 8.535 ms) 0.983 R? (0.947 R? .. 1.000 R?) mean 8.822 ms (8.590 ms .. 9.463 ms) std dev 991.2 ?s (381.3 ?s .. 1.809 ms) variance introduced by outliers: 61% (severely inflated) benchmarking <*>/nf100/2500/ff time 22.84 ms (22.74 ms .. 22.94 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 22.78 ms (22.71 ms .. 22.86 ms) std dev 183.3 ?s (116.3 ?s .. 291.3 ?s) benchmarking <*>/nf500/500/rep time 8.320 ms (8.102 ms .. 8.514 ms) 0.995 R? (0.990 R? .. 0.999 R?) mean 8.902 ms (8.675 ms .. 9.407 ms) std dev 952.4 ?s (435.5 ?s .. 1.672 ms) variance introduced by outliers: 58% (severely inflated) benchmarking <*>/nf500/500/ff time 24.50 ms (24.41 ms .. 24.58 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 24.44 ms (24.41 ms .. 24.48 ms) std dev 75.08 ?s (50.16 ?s .. 111.3 ?s) benchmarking <*>/nf2500/100/rep time 8.419 ms (8.366 ms .. 8.458 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 8.571 ms (8.525 ms .. 8.670 ms) std dev 179.5 ?s (112.0 ?s .. 278.1 ?s) benchmarking <*>/nf2500/100/ff time 24.14 ms (24.07 ms .. 24.26 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 24.11 ms (24.07 ms .. 24.17 ms) std dev 103.8 ?s (68.34 ?s .. 142.0 ?s) >--------------------------------------------------------------- 38b1b81c8b5536525d0daad9bd8ee9821a3fb929 Data/Sequence.hs | 261 ++++++++++++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 258 insertions(+), 3 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 38b1b81c8b5536525d0daad9bd8ee9821a3fb929 From git at git.haskell.org Fri Jan 23 22:43:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:33 +0000 (UTC) Subject: [commit: packages/bytestring] master: Add required CPP language pragmas (0bfef87) Message-ID: <20150123224333.D36D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/0bfef878c5f39b49fa7de375b19087c6d40a0f7d >--------------------------------------------------------------- commit 0bfef878c5f39b49fa7de375b19087c6d40a0f7d Author: Duncan Coutts Date: Sun Dec 14 14:11:21 2014 +0000 Add required CPP language pragmas >--------------------------------------------------------------- 0bfef878c5f39b49fa7de375b19087c6d40a0f7d Data/ByteString/Builder/Prim/ASCII.hs | 1 + Data/ByteString/Builder/Prim/Internal/Floating.hs | 1 + 2 files changed, 2 insertions(+) diff --git a/Data/ByteString/Builder/Prim/ASCII.hs b/Data/ByteString/Builder/Prim/ASCII.hs index 9a5816d..62bd5be 100644 --- a/Data/ByteString/Builder/Prim/ASCII.hs +++ b/Data/ByteString/Builder/Prim/ASCII.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE ScopedTypeVariables, ForeignFunctionInterface #-} #if __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} diff --git a/Data/ByteString/Builder/Prim/Internal/Floating.hs b/Data/ByteString/Builder/Prim/Internal/Floating.hs index 0fa85ca..ad5fcff 100644 --- a/Data/ByteString/Builder/Prim/Internal/Floating.hs +++ b/Data/ByteString/Builder/Prim/Internal/Floating.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE ScopedTypeVariables #-} #if __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} From git at git.haskell.org Fri Jan 23 22:43:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:34 +0000 (UTC) Subject: [commit: packages/containers] master: Add Applicative benchmarks (8b47db3) Message-ID: <20150123224334.770F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/8b47db3af79c31fe5434e95143242a2ef3e1e184 >--------------------------------------------------------------- commit 8b47db3af79c31fe5434e95143242a2ef3e1e184 Author: David Feuer Date: Sat Dec 20 15:02:05 2014 -0500 Add Applicative benchmarks >--------------------------------------------------------------- 8b47db3af79c31fe5434e95143242a2ef3e1e184 benchmarks/Sequence.hs | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index b6b82fa..a152c3b 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -1,6 +1,7 @@ -- > ghc -DTESTING --make -O2 -fforce-recomp -i.. Sequence.hs module Main where +import Control.Applicative import Control.DeepSeq import Criterion.Main import Data.List (foldl') @@ -44,6 +45,22 @@ main = do , bench "nf1000" $ nf (\s -> S.fromFunction s (+1)) 1000 , bench "nf10000" $ nf (\s -> S.fromFunction s (+1)) 10000 ] + , bgroup "<*>" + [ bench "ix1000/500000" $ + nf (\s -> ((+) <$> s <*> s) `S.index` (S.length s `div` 2)) (S.fromFunction 1000 (+1)) + , bench "nf100/2500/rep" $ + nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (100,2500) + , bench "nf100/2500/ff" $ + nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (100,2500) + , bench "nf500/500/rep" $ + nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (500,500) + , bench "nf500/500/ff" $ + nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (500,500) + , bench "nf2500/100/rep" $ + nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (2500,100) + , bench "nf2500/100/ff" $ + nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (2500,100) + ] ] -- splitAt+append: repeatedly cut the sequence at a random point From git at git.haskell.org Fri Jan 23 22:43:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:35 +0000 (UTC) Subject: [commit: packages/bytestring] master: Re-export isSuffixOf from D.B.L.Char8 (c3457d7) Message-ID: <20150123224335.DD1E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/c3457d7cbd54ec11d3f5a000801116466ac7f75e >--------------------------------------------------------------- commit c3457d7cbd54ec11d3f5a000801116466ac7f75e Author: Duncan Coutts Date: Sun Dec 14 14:12:47 2014 +0000 Re-export isSuffixOf from D.B.L.Char8 As requested in issue 30 >--------------------------------------------------------------- c3457d7cbd54ec11d3f5a000801116466ac7f75e Data/ByteString/Lazy/Char8.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/Data/ByteString/Lazy/Char8.hs b/Data/ByteString/Lazy/Char8.hs index 279902d..f737697 100644 --- a/Data/ByteString/Lazy/Char8.hs +++ b/Data/ByteString/Lazy/Char8.hs @@ -129,7 +129,7 @@ module Data.ByteString.Lazy.Char8 ( -- * Predicates isPrefixOf, -- :: ByteString -> ByteString -> Bool --- isSuffixOf, -- :: ByteString -> ByteString -> Bool + isSuffixOf, -- :: ByteString -> ByteString -> Bool -- * Searching ByteStrings @@ -197,7 +197,8 @@ module Data.ByteString.Lazy.Char8 ( import Data.ByteString.Lazy (fromChunks, toChunks, fromStrict, toStrict ,empty,null,length,tail,init,append,reverse,transpose,cycle - ,concat,take,drop,splitAt,intercalate,isPrefixOf,group,inits,tails,copy + ,concat,take,drop,splitAt,intercalate + ,isPrefixOf,isSuffixOf,group,inits,tails,copy ,hGetContents, hGet, hPut, getContents ,hGetNonBlocking, hPutNonBlocking ,putStr, hPutStr, interact) From git at git.haskell.org Fri Jan 23 22:43:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:36 +0000 (UTC) Subject: [commit: packages/containers] master: Exploit some invariants (41b7cb4) Message-ID: <20150123224336.7F75E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/41b7cb48a1f61911651fc4ea40ac552332de9e96 >--------------------------------------------------------------- commit 41b7cb48a1f61911651fc4ea40ac552332de9e96 Author: Bertram Felgenhauer Date: Sun Dec 21 16:37:11 2014 +0100 Exploit some invariants Consequently, get rid of ApState. This speeds up the immediate-indexing test substantially: Old: benchmarking <*>/ix1000/500000 time 2.688 ?s (2.607 ?s .. 2.798 ?s) 0.994 R? (0.988 R? .. 1.000 R?) mean 2.632 ?s (2.607 ?s .. 2.715 ?s) std dev 129.9 ns (65.93 ns .. 242.8 ns) variance introduced by outliers: 64% (severely inflated) New: benchmarking <*>/ix1000/500000 time 1.410 ?s (1.402 ?s .. 1.417 ?s) 1.000 R? (1.000 R? .. 1.000 R?) mean 1.417 ?s (1.411 ?s .. 1.425 ?s) std dev 21.45 ns (16.80 ns .. 31.73 ns) variance introduced by outliers: 14% (moderately inflated) >--------------------------------------------------------------- 41b7cb48a1f61911651fc4ea40ac552332de9e96 Data/Sequence.hs | 120 ++++++++++++++++++++++--------------------------------- 1 file changed, 47 insertions(+), 73 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 7a2de82..0a64c3e 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -277,7 +277,7 @@ apShort :: Seq (a -> b) -> Seq a -> Seq b apShort (Seq fs) xs = Seq $ case toList xs of [a,b] -> ap2FT fs (a,b) [a,b,c] -> ap3FT fs (a,b,c) - _ -> error "apShort: not 2-6" + _ -> error "apShort: not 2-3" ap2FT :: FingerTree (Elem (a->b)) -> (a,a) -> FingerTree (Elem b) ap2FT fs (x,y) = Deep (size fs * 2) @@ -298,104 +298,85 @@ ap3FT fs (x,y,z) = Deep (size fs * 3) -- <*> when the length of each argument is at least four. apty :: Seq (a -> b) -> Seq a -> Seq b apty (Seq fs) (Seq xs at Deep{}) = Seq $ - runApState (fmap firstf) (fmap lastf) fmap fs' (ApState xs' xs' xs') + Deep (s' * size fs) + (fmap (fmap firstf) pr') + (aptyMiddle (fmap firstf) (fmap lastf) fmap fs' xs') + (fmap (fmap lastf) sf') where (Elem firstf, fs', Elem lastf) = trimTree fs - xs' = rigidify xs + xs'@(Deep s' pr' _m' sf') = rigidify xs apty _ _ = error "apty: expects a Deep constructor" -data ApState a = ApState (FingerTree a) (FingerTree a) (FingerTree a) - --- | 'runApState' uses three copies of the @xs@ tree to produce the @fs<*>xs@ --- tree. It pulls left digits off the left tree, right digits off the right tree, --- and squashes down the other four digits. Once it gets to the bottom, it turns --- the middle tree into a 2-3 tree, applies 'mapMulFT' to produce the main body, --- and glues all the pieces together. -runApState +-- | 'aptyMiddle' does most of the hard work of computing @fs<*>xs at . +-- It produces the center part of a finger tree, with a prefix corresponding +-- to the prefix of @xs@ and a suffix corresponding to the suffix of @xs@ +-- omitted; the missing suffix and prefix are added by the caller. +-- For the recursive call, it squashes the prefix and the suffix into +-- the center tree. Once it gets to the bottom, it turns the tree into +-- a 2-3 tree, applies 'mapMulFT' to produce the main body, and glues all +-- the pieces together. +aptyMiddle :: Sized c => (c -> d) -> (c -> d) -> ((a -> b) -> c -> d) -> FingerTree (Elem (a -> b)) - -> ApState c - -> FingerTree d + -> FingerTree c + -> FingerTree (Node d) -- Not at the bottom yet -runApState firstf +aptyMiddle firstf lastf map23 fs - (ApState - (Deep sl - prl - (Deep sml prml mml sfml) - sfl) - (Deep sm - prm - (Deep _smm prmm mmm sfmm) - sfm) - (Deep sr - prr - (Deep smr prmr mmr sfmr) - sfr)) - = Deep (sl + sr + sm * size fs) - (fmap firstf prl) - (runApState (fmap firstf) + (Deep s pr (Deep sm prm mm sfm) sf) + = Deep (sm + s * (size fs + 1)) -- note: sm = s - size pr - size sf + (fmap (fmap firstf) prm) + (aptyMiddle (fmap firstf) (fmap lastf) (\f -> fmap (map23 f)) fs - nextState) - (fmap lastf sfr) - where nextState = - ApState - (Deep (sml + size sfl) prml mml (squashR sfml sfl)) - (Deep sm (squashL prm prmm) mmm (squashR sfmm sfm)) - (Deep (smr + size prr) (squashL prr prmr) mmr sfmr) + (Deep s (squashL pr prm) mm (squashR sfm sf))) + (fmap (fmap lastf) sfm) -- At the bottom -runApState firstf +aptyMiddle firstf lastf map23 fs - (ApState - (Deep sl prl ml sfl) - (Deep sm prm mm sfm) - (Deep sr prr mr sfr)) - = Deep (sl + sr + sm * size fs) - (fmap firstf prl) - ((fmap (fmap firstf) ml `snocTree` fmap firstf (digitToNode sfl)) - `appendTree0` middle `appendTree0` - (fmap lastf (digitToNode prr) `consTree` fmap (fmap lastf) mr)) - (fmap lastf sfr) - where middle = case trimTree $ mapMulFT sm (\(Elem f) -> fmap (fmap (map23 f)) converted) fs of + (Deep s pr m sf) + = (fmap (fmap firstf) m `snocTree` fmap firstf (digitToNode sf)) + `appendTree0` middle `appendTree0` + (fmap lastf (digitToNode pr) `consTree` fmap (fmap lastf) m) + where middle = case trimTree $ mapMulFT s (\(Elem f) -> fmap (fmap (map23 f)) converted) fs of (firstMapped, restMapped, lastMapped) -> Deep (size firstMapped + size restMapped + size lastMapped) (nodeToDigit firstMapped) restMapped (nodeToDigit lastMapped) - converted = case mm of - Empty -> Node2 sm lconv rconv - Single q -> Node3 sm lconv q rconv - Deep{} -> error "runApState: a tree is shallower than the middle tree" - lconv = digitToNode prm - rconv = digitToNode sfm + converted = case m of + Empty -> Node2 s lconv rconv + Single q -> Node3 s lconv q rconv + Deep{} -> error "aptyMiddle: impossible" + lconv = digitToNode pr + rconv = digitToNode sf -runApState _ _ _ _ _ = error "runApState: ApState must hold Deep finger trees of the same depth" +aptyMiddle _ _ _ _ _ = error "aptyMiddle: expected Deep finger tree" {-# SPECIALIZE - runApState + aptyMiddle :: (Node c -> d) -> (Node c -> d) -> ((a -> b) -> Node c -> d) -> FingerTree (Elem (a -> b)) - -> ApState (Node c) - -> FingerTree d + -> FingerTree (Node c) + -> FingerTree (Node d) #-} {-# SPECIALIZE - runApState + aptyMiddle :: (Elem c -> d) -> (Elem c -> d) -> ((a -> b) -> Elem c -> d) -> FingerTree (Elem (a -> b)) - -> ApState (Elem c) - -> FingerTree d + -> FingerTree (Elem c) + -> FingerTree (Node d) #-} digitToNode :: Sized a => Digit a -> Node a @@ -2096,16 +2077,9 @@ reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) -- Mapping with a splittable value ------------------------------------------------------------------------ --- For zipping, and probably also for (<*>), it is useful to build a result by +-- For zipping, it is useful to build a result by -- traversing a sequence while splitting up something else. For zipping, we --- traverse the first sequence while splitting up the second [and third [and --- fourth]]. For fs <*> xs, we hope to traverse --- --- > replicate (length fs * length xs) () --- --- while splitting something essentially equivalent to --- --- > fmap (\f -> fmap f xs) fs +-- traverse the first sequence while splitting up the second. -- -- What makes all this crazy code a good idea: -- @@ -2129,8 +2103,8 @@ reverseNode f (Node3 s a b c) = Node3 s (f c) (f b) (f a) -- they're actually needed. We do the same thing for Digits (splitting into -- between one and four pieces) and Nodes (splitting into two or three). The -- ultimate result is that we can index into, or split at, any location in zs --- in O((log(min{i,n-i}))^2) time *immediately*, while still being able to --- force all the thunks in O(n) time. +-- in polylogarithmic time *immediately*, while still being able to force all +-- the thunks in O(n) time. -- -- Benchmark info, and alternatives: -- From git at git.haskell.org Fri Jan 23 22:43:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:37 +0000 (UTC) Subject: [commit: packages/bytestring] master: Replace STRICT macros with bang patterns (fd022fe) Message-ID: <20150123224337.EDCCF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/fd022fed4c10bf4e05ee51ce98ee96a669c21eca >--------------------------------------------------------------- commit fd022fed4c10bf4e05ee51ce98ee96a669c21eca Author: Duncan Coutts Date: Sun Dec 14 14:43:48 2014 +0000 Replace STRICT macros with bang patterns >--------------------------------------------------------------- fd022fed4c10bf4e05ee51ce98ee96a669c21eca Data/ByteString.hs | 163 ++++++++++++++++-------------------------- Data/ByteString/Char8.hs | 20 ++---- Data/ByteString/Internal.hs | 10 --- Data/ByteString/Lazy.hs | 27 ++----- Data/ByteString/Lazy/Char8.hs | 14 +--- Data/ByteString/Unsafe.hs | 10 --- 6 files changed, 77 insertions(+), 167 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fd022fed4c10bf4e05ee51ce98ee96a669c21eca From git at git.haskell.org Fri Jan 23 22:43:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:38 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #104 from treeowl/ap (2546efe) Message-ID: <20150123224338.877CB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/2546efeadaca6c078b5ddc23557af71fd3d6966d >--------------------------------------------------------------- commit 2546efeadaca6c078b5ddc23557af71fd3d6966d Merge: ae97ceb 41b7cb4 Author: Milan Straka Date: Mon Dec 22 11:13:16 2014 +0100 Merge pull request #104 from treeowl/ap Make <*> fast >--------------------------------------------------------------- 2546efeadaca6c078b5ddc23557af71fd3d6966d Data/Sequence.hs | 257 ++++++++++++++++++++++++++++++++++++++++++++++--- benchmarks/Sequence.hs | 17 ++++ 2 files changed, 260 insertions(+), 14 deletions(-) From git at git.haskell.org Fri Jan 23 22:43:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:40 +0000 (UTC) Subject: [commit: packages/bytestring] master: Add -fwarn-tabs (7670357) Message-ID: <20150123224340.026F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/76703578c34a66bf4b11a1f99fbccd9a0d4afade >--------------------------------------------------------------- commit 76703578c34a66bf4b11a1f99fbccd9a0d4afade Author: Duncan Coutts Date: Sun Dec 14 14:44:26 2014 +0000 Add -fwarn-tabs >--------------------------------------------------------------- 76703578c34a66bf4b11a1f99fbccd9a0d4afade bytestring.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/bytestring.cabal b/bytestring.cabal index 794c9e2..a151269 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -120,7 +120,7 @@ library DeriveDataTypeable, BangPatterns, NamedFieldPuns - ghc-options: -Wall + ghc-options: -Wall -fwarn-tabs -O2 -fmax-simplifier-iterations=10 -fdicts-cheap From git at git.haskell.org Fri Jan 23 22:43:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:40 +0000 (UTC) Subject: [commit: packages/containers] master: Bump version number to 0.5.6.2 (924fafe) Message-ID: <20150123224340.8EE943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/924fafe1030301ee1d62d7acd576e86b50251157 >--------------------------------------------------------------- commit 924fafe1030301ee1d62d7acd576e86b50251157 Author: Milan Straka Date: Mon Dec 22 11:54:05 2014 +0100 Bump version number to 0.5.6.2 >--------------------------------------------------------------- 924fafe1030301ee1d62d7acd576e86b50251157 containers.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/containers.cabal b/containers.cabal index 169507a..c5d7523 100644 --- a/containers.cabal +++ b/containers.cabal @@ -1,5 +1,5 @@ name: containers -version: 0.5.6.1 +version: 0.5.6.2 license: BSD3 license-file: LICENSE maintainer: fox at ucw.cz From git at git.haskell.org Fri Jan 23 22:43:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:42 +0000 (UTC) Subject: [commit: packages/bytestring] master: Remove various old commented-out implementations (1a8ed9f) Message-ID: <20150123224342.0E3253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/1a8ed9f88b18744b3c5b057d3a58b6cb885a55fe >--------------------------------------------------------------- commit 1a8ed9f88b18744b3c5b057d3a58b6cb885a55fe Author: Duncan Coutts Date: Sun Dec 14 14:51:21 2014 +0000 Remove various old commented-out implementations >--------------------------------------------------------------- 1a8ed9f88b18744b3c5b057d3a58b6cb885a55fe Data/ByteString.hs | 117 ------------------------------------------ Data/ByteString/Lazy.hs | 10 ---- Data/ByteString/Lazy/Char8.hs | 7 --- 3 files changed, 134 deletions(-) diff --git a/Data/ByteString.hs b/Data/ByteString.hs index 73abe50..5240930 100644 --- a/Data/ByteString.hs +++ b/Data/ByteString.hs @@ -1044,39 +1044,6 @@ split w (PS x s l) = loop 0 {-# INLINE split #-} -{- --- slower. but stays inside Haskell. -split _ (PS _ _ 0) = [] -split (W8# w#) (PS fp off len) = splitWith' off len fp - where - splitWith' off' len' fp' = withPtr fp $ \p -> - splitLoop p 0 off' len' fp' - - splitLoop :: Ptr Word8 - -> Int -> Int -> Int - -> ForeignPtr Word8 - -> IO [ByteString] - - splitLoop p idx' off' len' fp' - | idx' >= len' = return [PS fp' off' idx'] - | otherwise = do - (W8# x#) <- peekElemOff p (off'+idx') - if word2Int# w# ==# word2Int# x# - then return (PS fp' off' idx' : - splitWith' (off'+idx'+1) (len'-idx'-1) fp') - else splitLoop p (idx'+1) off' len' fp' --} - -{- --- | Like 'splitWith', except that sequences of adjacent separators are --- treated as a single separator. eg. --- --- > tokens (=='a') "aabbaca" == ["bb","c"] --- -tokens :: (Word8 -> Bool) -> ByteString -> [ByteString] -tokens f = P.filter (not.null) . splitWith f -{-# INLINE tokens #-} --} -- | The 'group' function takes a ByteString and returns a list of -- ByteStrings such that the concatenation of the result is equal to the @@ -1187,15 +1154,6 @@ elemIndices w (PS x s l) = loop 0 in i : loop (i+1) {-# INLINE elemIndices #-} -{- --- much slower -elemIndices :: Word8 -> ByteString -> [Int] -elemIndices c ps = loop 0 ps - where loop _ ps' | null ps' = [] - loop n ps' | c == unsafeHead ps' = n : loop (n+1) (unsafeTail ps') - | otherwise = loop (n+1) (unsafeTail ps') --} - -- | count returns the number of times its argument appears in the ByteString -- -- > count = length . elemIndices @@ -1206,22 +1164,6 @@ count w (PS x s m) = accursedUnutterablePerformIO $ withForeignPtr x $ \p -> fmap fromIntegral $ c_count (p `plusPtr` s) (fromIntegral m) w {-# INLINE count #-} -{- --- --- around 30% slower --- -count w (PS x s m) = accursedUnutterablePerformIO $ withForeignPtr x $ \p -> - go (p `plusPtr` s) (fromIntegral m) 0 - where - go :: Ptr Word8 -> CSize -> Int -> IO Int - go p l i = do - q <- memchr p w l - if q == nullPtr - then return i - else do let k = fromIntegral $ q `minusPtr` p - go (q `plusPtr` 1) (l-k-1) (i+1) --} - -- | The 'findIndex' function takes a predicate and a 'ByteString' and -- returns the index of the first element in the ByteString -- satisfying the predicate. @@ -1310,16 +1252,6 @@ find f p = case findIndex f p of _ -> Nothing {-# INLINE find #-} -{- --- --- fuseable, but we don't want to walk the whole array. --- -find k = foldl findEFL Nothing - where findEFL a@(Just _) _ = a - findEFL _ c | k c = Just c - | otherwise = Nothing --} - -- | /O(n)/ The 'partition' function takes a predicate a ByteString and returns -- the pair of ByteStrings with elements which do and do not satisfy the -- predicate, respectively; i.e., @@ -1416,18 +1348,6 @@ findSubstring f i = listToMaybe (findSubstrings f i) {-# DEPRECATED findSubstring "findSubstring is deprecated in favour of breakSubstring." #-} -{- -findSubstring pat str = search 0 str - where - search n s - = let x = pat `isPrefixOf` s - in - if null s - then if x then Just n else Nothing - else if x then Just n - else search (n+1) (unsafeTail s) --} - -- | Find the indexes of all (possibly overlapping) occurances of a -- substring in a string. -- @@ -1445,29 +1365,6 @@ findSubstrings pat str {-# DEPRECATED findSubstrings "findSubstrings is deprecated in favour of breakSubstring." #-} -{- -{- This function uses the Knuth-Morris-Pratt string matching algorithm. -} - -findSubstrings pat@(PS _ _ m) str@(PS _ _ n) = search 0 0 - where - patc x = pat `unsafeIndex` x - strc x = str `unsafeIndex` x - - -- maybe we should make kmpNext a UArray before using it in search? - kmpNext = listArray (0,m) (-1:kmpNextL pat (-1)) - kmpNextL p _ | null p = [] - kmpNextL p j = let j' = next (unsafeHead p) j + 1 - ps = unsafeTail p - x = if not (null ps) && unsafeHead ps == patc j' - then kmpNext Array.! j' else j' - in x:kmpNextL ps j' - search i j = match ++ rest -- i: position in string, j: position in pattern - where match = if j == m then [(i - j)] else [] - rest = if i == n then [] else search (i+1) (next (strc i) j + 1) - next c j | j >= 0 && (j == m || c /= patc j) = next c (kmpNext Array.! j) - | otherwise = j --} - -- --------------------------------------------------------------------- -- Zipping @@ -1567,20 +1464,6 @@ sort (PS input s l) = unsafeCreate l $ \p -> allocaArray 256 $ \arr -> do pokeElemOff counts k (x + 1) go (i + 1) -{- -sort :: ByteString -> ByteString -sort (PS x s l) = unsafeCreate l $ \p -> withForeignPtr x $ \f -> do - memcpy p (f `plusPtr` s) l - c_qsort p l -- inplace --} - --- The 'sortBy' function is the non-overloaded version of 'sort'. --- --- Try some linear sorts: radix, counting --- Or mergesort. --- --- sortBy :: (Word8 -> Word8 -> Ordering) -> ByteString -> ByteString --- sortBy f ps = undefined -- --------------------------------------------------------------------- -- Low level constructors diff --git a/Data/ByteString/Lazy.hs b/Data/ByteString/Lazy.hs index 23ecf35..b001d7c 100644 --- a/Data/ByteString/Lazy.hs +++ b/Data/ByteString/Lazy.hs @@ -809,16 +809,6 @@ split w (Chunk c0 cs0) = comb [] (S.split w c0) cs0 comb acc (s:ss) cs = revChunks (s:acc) : comb [] ss cs {-# INLINE split #-} -{- --- | Like 'splitWith', except that sequences of adjacent separators are --- treated as a single separator. eg. --- --- > tokens (=='a') "aabbaca" == ["bb","c"] --- -tokens :: (Word8 -> Bool) -> ByteString -> [ByteString] -tokens f = L.filter (not.null) . splitWith f --} - -- | The 'group' function takes a ByteString and returns a list of -- ByteStrings such that the concatenation of the result is equal to the -- argument. Moreover, each sublist in the result contains only equal diff --git a/Data/ByteString/Lazy/Char8.hs b/Data/ByteString/Lazy/Char8.hs index d0d0790..0648949 100644 --- a/Data/ByteString/Lazy/Char8.hs +++ b/Data/ByteString/Lazy/Char8.hs @@ -759,13 +759,6 @@ unwords = intercalate (singleton ' ') -- Nothing, otherwise it just returns the int read, and the rest of the -- string. -{- --- Faster: - -data MaybeS = NothingS - | JustS {-# UNPACK #-} !Int {-# UNPACK #-} !ByteString --} - readInt :: ByteString -> Maybe (Int, ByteString) {-# INLINE readInt #-} readInt Empty = Nothing From git at git.haskell.org Fri Jan 23 22:43:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:42 +0000 (UTC) Subject: [commit: packages/containers] master: update benchmarks Makefile (5f9af63) Message-ID: <20150123224342.95D1D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/5f9af637de232236abf1890f1e05a3df4421ef15 >--------------------------------------------------------------- commit 5f9af637de232236abf1890f1e05a3df4421ef15 Author: Bertram Felgenhauer Date: Sun Dec 21 21:01:11 2014 +0100 update benchmarks Makefile >--------------------------------------------------------------- 5f9af637de232236abf1890f1e05a3df4421ef15 benchmarks/Makefile | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/benchmarks/Makefile b/benchmarks/Makefile index 1539a2a..aacccef 100644 --- a/benchmarks/Makefile +++ b/benchmarks/Makefile @@ -1,10 +1,12 @@ all: bench-%: %.hs force - ghc -O2 -DTESTING $< -i../$(TOP) -o $@ -outputdir tmp -rtsopts + ghc -O2 -DTESTING $< -I../include -i../$(TOP) -o $@ -outputdir tmp -rtsopts + +.PRECIOUS: bench-% bench-%.csv: bench-% - ./bench-$* $(BENCHMARK) -v -u bench-$*.csv + ./bench-$* "$(BENCHMARK)" -v1 --csv bench-$*.csv .PHONY: force clean veryclean force: From git at git.haskell.org Fri Jan 23 22:43:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:44 +0000 (UTC) Subject: [commit: packages/bytestring] master: Remove old fusion related stuff (ba75c25) Message-ID: <20150123224344.1AD3F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/ba75c258571fafa535021ae4fb17a9bf01887edf >--------------------------------------------------------------- commit ba75c258571fafa535021ae4fb17a9bf01887edf Author: Duncan Coutts Date: Sun Dec 14 14:55:14 2014 +0000 Remove old fusion related stuff We never used array fusion in a released version. >--------------------------------------------------------------- ba75c258571fafa535021ae4fb17a9bf01887edf tests/FusionBench.hs | 70 ----------- tests/FusionProperties.hs | 312 ---------------------------------------------- tests/Properties.hs | 251 +------------------------------------ tests/down-fuse.hs | 23 ---- tests/fuse.hs | 28 ----- 5 files changed, 1 insertion(+), 683 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ba75c258571fafa535021ae4fb17a9bf01887edf From git at git.haskell.org Fri Jan 23 22:43:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:44 +0000 (UTC) Subject: [commit: packages/containers] master: update benchmarks to work with criterion-1.0 (5364bea) Message-ID: <20150123224344.9F1A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/5364beaa69609ba3c0868cec4380b9c36105b740 >--------------------------------------------------------------- commit 5364beaa69609ba3c0868cec4380b9c36105b740 Author: Bertram Felgenhauer Date: Mon Dec 22 17:08:21 2014 +0100 update benchmarks to work with criterion-1.0 >--------------------------------------------------------------- 5364beaa69609ba3c0868cec4380b9c36105b740 benchmarks/IntMap.hs | 6 ++---- benchmarks/IntSet.hs | 6 ++---- benchmarks/Map.hs | 6 ++---- benchmarks/Sequence.hs | 7 ++++--- benchmarks/Set.hs | 6 ++---- 5 files changed, 12 insertions(+), 19 deletions(-) diff --git a/benchmarks/IntMap.hs b/benchmarks/IntMap.hs index 87465a7..38104c0 100644 --- a/benchmarks/IntMap.hs +++ b/benchmarks/IntMap.hs @@ -4,7 +4,6 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Config import Criterion.Main import Data.List (foldl') import qualified Data.IntMap as M @@ -13,9 +12,8 @@ import Prelude hiding (lookup) main = do let m = M.fromAscList elems :: M.IntMap Int - defaultMainWith - defaultConfig - (liftIO . evaluate $ rnf [m]) + evaluate $ rnf [m] + defaultMain [ bench "lookup" $ whnf (lookup keys) m , bench "insert" $ whnf (ins elems) M.empty , bench "insertWith empty" $ whnf (insWith elems) M.empty diff --git a/benchmarks/IntSet.hs b/benchmarks/IntSet.hs index 7c16c91..a768a32 100644 --- a/benchmarks/IntSet.hs +++ b/benchmarks/IntSet.hs @@ -5,7 +5,6 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Config import Criterion.Main import Data.List (foldl') import qualified Data.IntSet as S @@ -14,9 +13,8 @@ main = do let s = S.fromAscList elems :: S.IntSet s_even = S.fromAscList elems_even :: S.IntSet s_odd = S.fromAscList elems_odd :: S.IntSet - defaultMainWith - defaultConfig - (liftIO . evaluate $ rnf [s, s_even, s_odd]) + evaluate $ rnf [s, s_even, s_odd] + defaultMain [ bench "member" $ whnf (member elems) s , bench "insert" $ whnf (ins elems) S.empty , bench "map" $ whnf (S.map (+ 1)) s diff --git a/benchmarks/Map.hs b/benchmarks/Map.hs index d0d539a..60e7ace 100644 --- a/benchmarks/Map.hs +++ b/benchmarks/Map.hs @@ -4,7 +4,6 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Config import Criterion.Main import Data.List (foldl') import qualified Data.Map as M @@ -15,9 +14,8 @@ main = do let m = M.fromAscList elems :: M.Map Int Int m_even = M.fromAscList elems_even :: M.Map Int Int m_odd = M.fromAscList elems_odd :: M.Map Int Int - defaultMainWith - defaultConfig - (liftIO . evaluate $ rnf [m, m_even, m_odd]) + evaluate $ rnf [m, m_even, m_odd] + defaultMain [ bench "lookup absent" $ whnf (lookup evens) m_odd , bench "lookup present" $ whnf (lookup evens) m_even , bench "insert absent" $ whnf (ins elems_even) m_odd diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs index a152c3b..7ccede9 100644 --- a/benchmarks/Sequence.hs +++ b/benchmarks/Sequence.hs @@ -3,6 +3,7 @@ module Main where import Control.Applicative import Control.DeepSeq +import Control.Exception (evaluate) import Criterion.Main import Data.List (foldl') import qualified Data.Sequence as S @@ -14,19 +15,19 @@ main = do s100 = S.fromList [1..100] :: S.Seq Int s1000 = S.fromList [1..1000] :: S.Seq Int s10000 = S.fromList [1..10000] :: S.Seq Int - rnf [s10, s100, s1000, s10000] `seq` return () + evaluate $ rnf [s10, s100, s1000, s10000] let g = mkStdGen 1 let rlist n = map (`mod` (n+1)) (take 10000 (randoms g)) :: [Int] r10 = rlist 10 r100 = rlist 100 r1000 = rlist 1000 r10000 = rlist 10000 - rnf [r10, r100, r1000, r10000] `seq` return () + evaluate $ rnf [r10, r100, r1000, r10000] let u10 = S.replicate 10 () :: S.Seq () u100 = S.replicate 100 () :: S.Seq () u1000 = S.replicate 1000 () :: S.Seq () u10000 = S.replicate 10000 () :: S.Seq () - rnf [u10, u100, u1000, u10000] `seq` return () + evaluate $ rnf [u10, u100, u1000, u10000] defaultMain [ bgroup "splitAt/append" [ bench "10" $ nf (shuffle r10) s10 diff --git a/benchmarks/Set.hs b/benchmarks/Set.hs index e21001c..3a6e8aa 100644 --- a/benchmarks/Set.hs +++ b/benchmarks/Set.hs @@ -6,7 +6,6 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Config import Criterion.Main import Data.List (foldl') import qualified Data.Set as S @@ -15,9 +14,8 @@ main = do let s = S.fromAscList elems :: S.Set Int s_even = S.fromAscList elems_even :: S.Set Int s_odd = S.fromAscList elems_odd :: S.Set Int - defaultMainWith - defaultConfig - (liftIO . evaluate $ rnf [s, s_even, s_odd]) + evaluate $ rnf [s, s_even, s_odd] + defaultMain [ bench "member" $ whnf (member elems) s , bench "insert" $ whnf (ins elems) S.empty , bench "map" $ whnf (S.map (+ 1)) s From git at git.haskell.org Fri Jan 23 22:43:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:46 +0000 (UTC) Subject: [commit: packages/bytestring] master: Fix unfoldrN to call the predicate at most n times. (8c3c7f3) Message-ID: <20150123224346.250593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/8c3c7f34ddc03089b1150c7c188fcaf72ef483de >--------------------------------------------------------------- commit 8c3c7f34ddc03089b1150c7c188fcaf72ef483de Author: Duncan Coutts Date: Sun Dec 14 16:19:24 2014 +0000 Fix unfoldrN to call the predicate at most n times. As a consequence unfoldrN 0 (const Nothing) 0 is now ("", Just 0) where before it was ("", Nothing). The other tests still pass. This fixes issue #11. >--------------------------------------------------------------- 8c3c7f34ddc03089b1150c7c188fcaf72ef483de Data/ByteString.hs | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/Data/ByteString.hs b/Data/ByteString.hs index 5240930..acd0a0f 100644 --- a/Data/ByteString.hs +++ b/Data/ByteString.hs @@ -825,13 +825,13 @@ unfoldrN :: Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a) unfoldrN i f x0 | i < 0 = (empty, Just x0) | otherwise = unsafePerformIO $ createAndTrim' i $ \p -> go p x0 0 - where go !p !x !n = - case f x of - Nothing -> return (0, n, Nothing) - Just (w,x') - | n == i -> return (0, n, Just x) - | otherwise -> do poke p w - go (p `plusPtr` 1) x' (n+1) + where + go !p !x !n + | n == i = return (0, n, Just x) + | otherwise = case f x of + Nothing -> return (0, n, Nothing) + Just (w,x') -> do poke p w + go (p `plusPtr` 1) x' (n+1) {-# INLINE unfoldrN #-} -- --------------------------------------------------------------------- From git at git.haskell.org Fri Jan 23 22:43:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:46 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #110 from int-e/bench (55f65cd) Message-ID: <20150123224346.A62503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/55f65cddc15bb30149795de2c5498e428381f2d2 >--------------------------------------------------------------- commit 55f65cddc15bb30149795de2c5498e428381f2d2 Merge: 924fafe 5364bea Author: Milan Straka Date: Mon Dec 22 17:56:05 2014 +0100 Merge pull request #110 from int-e/bench update benchmarks for criterion-1.0 >--------------------------------------------------------------- 55f65cddc15bb30149795de2c5498e428381f2d2 benchmarks/IntMap.hs | 6 ++---- benchmarks/IntSet.hs | 6 ++---- benchmarks/Makefile | 6 ++++-- benchmarks/Map.hs | 6 ++---- benchmarks/Sequence.hs | 7 ++++--- benchmarks/Set.hs | 6 ++---- 6 files changed, 16 insertions(+), 21 deletions(-) From git at git.haskell.org Fri Jan 23 22:43:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:48 +0000 (UTC) Subject: [commit: packages/bytestring] master: Fix readFile for files with incorrectly reported file sizes (77cf05c) Message-ID: <20150123224348.306973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/77cf05cd85f1652975021f6fa28f6f95950587f4 >--------------------------------------------------------------- commit 77cf05cd85f1652975021f6fa28f6f95950587f4 Author: Duncan Coutts Date: Sun Dec 14 18:52:16 2014 +0000 Fix readFile for files with incorrectly reported file sizes This situation can arise when the file is changed concurrently with the file read, or for files where the OS reports the size as 0, such as for certain device file or proc virtual file system files. This should fix issue #10 >--------------------------------------------------------------- 77cf05cd85f1652975021f6fa28f6f95950587f4 Data/ByteString.hs | 77 +++++++++++++++++++++++++++++------------------------- 1 file changed, 42 insertions(+), 35 deletions(-) diff --git a/Data/ByteString.hs b/Data/ByteString.hs index acd0a0f..4932a54 100644 --- a/Data/ByteString.hs +++ b/Data/ByteString.hs @@ -237,15 +237,13 @@ import Control.Monad (when) import Foreign.C.String (CString, CStringLen) import Foreign.C.Types (CSize) +import Foreign.ForeignPtr (ForeignPtr, withForeignPtr, touchForeignPtr) #if MIN_VERSION_base(4,5,0) -import Foreign.ForeignPtr (ForeignPtr, newForeignPtr, withForeignPtr - ,touchForeignPtr) import Foreign.ForeignPtr.Unsafe(unsafeForeignPtrToPtr) #else -import Foreign.ForeignPtr (ForeignPtr, newForeignPtr, withForeignPtr - ,touchForeignPtr, unsafeForeignPtrToPtr) +import Foreign.ForeignPtr (unsafeForeignPtrToPtr) #endif -import Foreign.Marshal.Alloc (allocaBytes, mallocBytes, reallocBytes, finalizerFree) +import Foreign.Marshal.Alloc (allocaBytes) import Foreign.Marshal.Array (allocaArray) import Foreign.Ptr import Foreign.Storable (Storable(..)) @@ -1780,10 +1778,10 @@ illegalBufferSize handle fn sz = msg = fn ++ ": illegal ByteString size " ++ showsPrec 9 sz [] --- | Read entire handle contents strictly into a 'ByteString'. +-- | Read a handle's entire contents strictly into a 'ByteString'. -- --- This function reads chunks at a time, doubling the chunksize on each --- read. The final buffer is then realloced to the appropriate size. For +-- This function reads chunks at a time, increasing the chunk size on each +-- read. The final string is then realloced to the appropriate size. For -- files > half of available memory, this may lead to memory exhaustion. -- Consider using 'readFile' in this case. -- @@ -1791,27 +1789,32 @@ illegalBufferSize handle fn sz = -- or if an exception is thrown. -- hGetContents :: Handle -> IO ByteString -hGetContents h = always (hClose h) $ do -- strict, so hClose - let start_size = 1024 - p <- mallocBytes start_size - i <- hGetBuf h p start_size - if i < start_size - then do p' <- reallocBytes p i - fp <- newForeignPtr finalizerFree p' - return $! PS fp 0 i - else f p start_size - where - always = flip finally - f p s = do - let s' = 2 * s - p' <- reallocBytes p s' - i <- hGetBuf h (p' `plusPtr` s) s - if i < s - then do let i' = s + i - p'' <- reallocBytes p' i' - fp <- newForeignPtr finalizerFree p'' - return $! PS fp 0 i' - else f p' s' +hGetContents hnd = do + bs <- hGetContentsSizeHint hnd 1024 2048 + `finally` hClose hnd + -- don't waste too much space for small files: + if length bs < 900 + then return $! copy bs + else return bs + +hGetContentsSizeHint :: Handle + -> Int -- ^ first read size + -> Int -- ^ initial buffer size increment + -> IO ByteString +hGetContentsSizeHint hnd = + readChunks [] + where + readChunks chunks sz sz' = do + fp <- mallocByteString sz + readcount <- withForeignPtr fp $ \buf -> hGetBuf hnd buf sz + let chunk = PS fp 0 readcount + -- We rely on the hGetBuf behaviour (not hGetBufSome) where it reads up + -- to the size we ask for, or EOF. So short reads indicate EOF. + if readcount < sz && sz > 0 + then return $! concat (P.reverse (chunk : chunks)) + else readChunks (chunk : chunks) sz' ((sz+sz') `min` 32752) + -- we grow the buffer sizes, but not too huge + -- we concatenate in the end anyway -- | getContents. Read stdin strictly. Equivalent to hGetContents stdin -- The 'Handle' is closed after the contents have been read. @@ -1827,14 +1830,18 @@ getContents = hGetContents stdin interact :: (ByteString -> ByteString) -> IO () interact transformer = putStr . transformer =<< getContents --- | Read an entire file strictly into a 'ByteString'. This is far more --- efficient than reading the characters into a 'String' and then using --- 'pack'. It also may be more efficient than opening the file and --- reading it using 'hGet'. +-- | Read an entire file strictly into a 'ByteString'. -- readFile :: FilePath -> IO ByteString -readFile f = bracket (openBinaryFile f ReadMode) hClose - (\h -> hFileSize h >>= hGet h . fromIntegral) +readFile f = + bracket (openBinaryFile f ReadMode) hClose $ \h -> do + filesz <- hFileSize h + let readsz = (fromIntegral filesz `max` 0) + 1 + hGetContentsSizeHint h readsz (readsz `max` 255) + -- Our initial size is one bigger than the file size so that in the + -- typical case we will read the whole file in one go and not have + -- to allocate any more chunks. We'll still do the right thing if the + -- file size is 0 or is changed before we do the read. -- | Write a 'ByteString' to a file. writeFile :: FilePath -> ByteString -> IO () From git at git.haskell.org Fri Jan 23 22:43:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:48 +0000 (UTC) Subject: [commit: packages/containers] master: Make applicativeTree aim for safe digits (1e962fc) Message-ID: <20150123224348.AE8EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/1e962fc2772008512509955316fb4d6eab2766e3 >--------------------------------------------------------------- commit 1e962fc2772008512509955316fb4d6eab2766e3 Author: David Feuer Date: Wed Dec 24 22:03:29 2014 -0500 Make applicativeTree aim for safe digits As previously discussed, this gives the tree more flexibility and matches what other functions do. >--------------------------------------------------------------- 1e962fc2772008512509955316fb4d6eab2766e3 Data/Sequence.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 0a64c3e..c256a53 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -856,17 +856,14 @@ applicativeTree n mSize m = mSize `seq` case n of 4 -> deepA two emptyTree two 5 -> deepA three emptyTree two 6 -> deepA three emptyTree three - 7 -> deepA four emptyTree three - 8 -> deepA four emptyTree four _ -> case n `quotRem` 3 of (q,0) -> deepA three (applicativeTree (q - 2) mSize' n3) three - (q,1) -> deepA four (applicativeTree (q - 2) mSize' n3) three - (q,_) -> deepA four (applicativeTree (q - 2) mSize' n3) four + (q,1) -> deepA two (applicativeTree (q - 1) mSize' n3) two + (q,_) -> deepA three (applicativeTree (q - 1) mSize' n3) two where one = fmap One m two = liftA2 Two m m three = liftA3 Three m m m - four = liftA3 Four m m m <*> m deepA = liftA3 (Deep (n * mSize)) mSize' = 3 * mSize n3 = liftA3 (Node3 mSize') m m m @@ -2335,7 +2332,7 @@ unstableSortBy cmp (Seq xs) = toPQ cmp (\ (Elem x) -> PQueue x Nil) xs -- | fromList2, given a list and its length, constructs a completely --- balanced Seq whose elements are that list using the applicativeTree +-- balanced Seq whose elements are that list using the replicateA -- generalization. fromList2 :: Int -> [a] -> Seq a fromList2 n = execState (replicateA n (State ht)) From git at git.haskell.org Fri Jan 23 22:43:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:50 +0000 (UTC) Subject: [commit: packages/bytestring] master: Update changelog (cb85a53) Message-ID: <20150123224350.38C873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/cb85a5360bc540c88b3ae1886d07c741bec3cdaa >--------------------------------------------------------------- commit cb85a5360bc540c88b3ae1886d07c741bec3cdaa Author: Duncan Coutts Date: Sun Dec 14 18:53:50 2014 +0000 Update changelog >--------------------------------------------------------------- cb85a5360bc540c88b3ae1886d07c741bec3cdaa Changelog.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/Changelog.md b/Changelog.md index e9e805c..731256e 100644 --- a/Changelog.md +++ b/Changelog.md @@ -1,6 +1,11 @@ 0.10.5.x (current development version) + * Rename inlinePerformIO so people don't misuse it + * Fix a corner case in unfoldrN + * Export isSuffixOf from D.B.Lazy.Char8 + * Add D.B.Lazy.elemIndexEnd + * Fix readFile for files with incorrectly reported file size 0.10.4.1 Duncan Coutts Nov 2014 From git at git.haskell.org Fri Jan 23 22:43:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:50 +0000 (UTC) Subject: [commit: packages/containers] master: Clean up <*> development artifacts (f1e0f8e) Message-ID: <20150123224350.B7E333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/f1e0f8e2b5df2be6852fb35ff2dd9559aaa4c830 >--------------------------------------------------------------- commit f1e0f8e2b5df2be6852fb35ff2dd9559aaa4c830 Author: David Feuer Date: Sat Dec 27 21:35:36 2014 -0500 Clean up <*> development artifacts Some silly remnants of my thought process remained in the code. Remove them. >--------------------------------------------------------------- f1e0f8e2b5df2be6852fb35ff2dd9559aaa4c830 Data/Sequence.hs | 20 +++++++++++--------- 1 file changed, 11 insertions(+), 9 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 0a64c3e..34504f5 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -338,15 +338,18 @@ aptyMiddle firstf (Deep s (squashL pr prm) mm (squashR sfm sf))) (fmap (fmap lastf) sfm) --- At the bottom +-- At the bottom. Note that these appendTree0 calls are very cheap, because in +-- each case, one of the arguments is guaranteed to be Empty or Single. aptyMiddle firstf lastf map23 fs (Deep s pr m sf) - = (fmap (fmap firstf) m `snocTree` fmap firstf (digitToNode sf)) - `appendTree0` middle `appendTree0` - (fmap lastf (digitToNode pr) `consTree` fmap (fmap lastf) m) + = fmap (fmap firstf) m `appendTree0` + ((fmap firstf (digitToNode sf) + `consTree` middle) + `snocTree` fmap lastf (digitToNode pr)) + `appendTree0` fmap (fmap lastf) m where middle = case trimTree $ mapMulFT s (\(Elem f) -> fmap (fmap (map23 f)) converted) fs of (firstMapped, restMapped, lastMapped) -> Deep (size firstMapped + size restMapped + size lastMapped) @@ -469,17 +472,16 @@ rigidify Single{} = error "rigidify: singleton" -- | /O(log n)/ (incremental) Rejigger a finger tree so the digits are all ones -- and twos. thin :: Sized a => FingerTree a -> FingerTree a --- Note that 'thin' may call itself at most once before passing the job on to --- 'thin12'. 'thin12' will produce a 'Deep' constructor immediately before --- calling 'thin'. +-- Note that 'thin12' will produce a 'Deep' constructor immediately before +-- recursively calling 'thin'. thin Empty = Empty thin (Single a) = Single a thin t@(Deep s pr m sf) = case pr of One{} -> thin12 t Two{} -> thin12 t - Three a b c -> thin $ Deep s (One a) (node2 b c `consTree` m) sf - Four a b c d -> thin $ Deep s (Two a b) (node2 c d `consTree` m) sf + Three a b c -> thin12 $ Deep s (One a) (node2 b c `consTree` m) sf + Four a b c d -> thin12 $ Deep s (Two a b) (node2 c d `consTree` m) sf thin12 :: Sized a => FingerTree a -> FingerTree a thin12 (Deep s pr m sf at One{}) = Deep s pr (thin m) sf From git at git.haskell.org Fri Jan 23 22:43:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:52 +0000 (UTC) Subject: [commit: packages/bytestring] master: Bump version to 0.10.6.0 (fa7e1cc) Message-ID: <20150123224352.42DD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/fa7e1cc94982c0da85a022a501eadb1b347ea60c >--------------------------------------------------------------- commit fa7e1cc94982c0da85a022a501eadb1b347ea60c Author: Duncan Coutts Date: Thu Dec 18 19:30:16 2014 +0000 Bump version to 0.10.6.0 >--------------------------------------------------------------- fa7e1cc94982c0da85a022a501eadb1b347ea60c bytestring.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/bytestring.cabal b/bytestring.cabal index a151269..40fa4ad 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -1,5 +1,5 @@ Name: bytestring -Version: 0.10.5.0 +Version: 0.10.6.0 Synopsis: Fast, compact, strict and lazy byte strings with a list interface Description: An efficient compact, immutable byte string type (both strict and lazy) From git at git.haskell.org Fri Jan 23 22:43:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:52 +0000 (UTC) Subject: [commit: packages/containers] master: Make `-Wall`-clean for base-4.8.0.0 (71f53cb) Message-ID: <20150123224352.C46F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/71f53cb8ea10cd2b50dbc0a7429e1f790fb62a0f >--------------------------------------------------------------- commit 71f53cb8ea10cd2b50dbc0a7429e1f790fb62a0f Author: Herbert Valerio Riedel Date: Sun Dec 28 09:36:44 2014 +0100 Make `-Wall`-clean for base-4.8.0.0 >--------------------------------------------------------------- 71f53cb8ea10cd2b50dbc0a7429e1f790fb62a0f Data/Graph.hs | 2 ++ Data/IntMap/Base.hs | 11 ++++++++--- Data/IntSet/Base.hs | 4 +++- Data/Map/Base.hs | 9 +++++++-- Data/Sequence.hs | 3 +++ Data/Set/Base.hs | 2 ++ Data/Tree.hs | 13 +++++++++---- 7 files changed, 34 insertions(+), 10 deletions(-) diff --git a/Data/Graph.hs b/Data/Graph.hs index 5f2bc15..c02b3e3 100644 --- a/Data/Graph.hs +++ b/Data/Graph.hs @@ -75,7 +75,9 @@ import qualified Data.IntSet as Set import Data.Tree (Tree(Node), Forest) -- std interfaces +#if !MIN_VERSION_base(4,8,0) import Control.Applicative +#endif import Control.DeepSeq (NFData(rnf)) import Data.Maybe import Data.Array diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs index d25cb9e..e15ed76 100644 --- a/Data/IntMap/Base.hs +++ b/Data/IntMap/Base.hs @@ -216,16 +216,21 @@ module Data.IntMap.Base ( , highestBitMask ) where +#if MIN_VERSION_base(4,8,0) +import Control.Applicative ((<$>)) +#else import Control.Applicative (Applicative(pure, (<*>)), (<$>)) +import Data.Monoid (Monoid(..)) +import Data.Traversable (Traversable(traverse)) +import Data.Word (Word) +#endif + import Control.DeepSeq (NFData(rnf)) import Control.Monad (liftM) import Data.Bits import qualified Data.Foldable as Foldable import Data.Maybe (fromMaybe) -import Data.Monoid (Monoid(..)) -import Data.Traversable (Traversable(traverse)) import Data.Typeable -import Data.Word (Word) import Prelude hiding (lookup, map, filter, foldr, foldl, null) import Data.IntSet.Base (Key) diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs index 6ddd0fb..c89bd18 100644 --- a/Data/IntSet/Base.hs +++ b/Data/IntSet/Base.hs @@ -169,9 +169,11 @@ import Control.DeepSeq (NFData(rnf)) import Data.Bits import qualified Data.List as List import Data.Maybe (fromMaybe) +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (Monoid(..)) -import Data.Typeable import Data.Word (Word) +#endif +import Data.Typeable import Prelude hiding (filter, foldr, foldl, null, map) import Data.Utils.BitUtil diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 815e54b..965a258 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -270,12 +270,17 @@ module Data.Map.Base ( , filterLt ) where +#if MIN_VERSION_base(4,8,0) +import Control.Applicative ((<$>)) +#else import Control.Applicative (Applicative(..), (<$>)) +import Data.Monoid (Monoid(..)) +import Data.Traversable (Traversable(traverse)) +#endif + import Control.DeepSeq (NFData(rnf)) import Data.Bits (shiftL, shiftR) import qualified Data.Foldable as Foldable -import Data.Monoid (Monoid(..)) -import Data.Traversable (Traversable(traverse)) import Data.Typeable import Prelude hiding (lookup, map, filter, foldr, foldl, null) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 0a64c3e..6b11266 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -147,6 +147,9 @@ module Data.Sequence ( import Prelude hiding ( Functor(..), +#if MIN_VERSION_base(4,8,0) + Applicative, foldMap, Monoid, +#endif null, length, take, drop, splitAt, foldl, foldl1, foldr, foldr1, scanl, scanl1, scanr, scanr1, replicate, zip, zipWith, zip3, zipWith3, takeWhile, dropWhile, iterate, reverse, filter, mapM, sum, all) diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 0dbc569..e1ebad3 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -192,7 +192,9 @@ module Data.Set.Base ( import Prelude hiding (filter,foldl,foldr,null,map) import qualified Data.List as List import Data.Bits (shiftL, shiftR) +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (Monoid(..)) +#endif import qualified Data.Foldable as Foldable import Data.Typeable import Control.DeepSeq (NFData(rnf)) diff --git a/Data/Tree.hs b/Data/Tree.hs index 4ee935b..abc9902 100644 --- a/Data/Tree.hs +++ b/Data/Tree.hs @@ -34,13 +34,19 @@ module Data.Tree( unfoldTreeM_BF, unfoldForestM_BF, ) where +#if MIN_VERSION_base(4,8,0) +import Control.Applicative ((<$>)) +import Data.Foldable (toList) +#else import Control.Applicative (Applicative(..), (<$>)) -import Control.Monad (liftM) +import Data.Foldable (Foldable(foldMap), toList) import Data.Monoid (Monoid(..)) +import Data.Traversable (Traversable(traverse)) +#endif + +import Control.Monad (liftM) import Data.Sequence (Seq, empty, singleton, (<|), (|>), fromList, ViewL(..), ViewR(..), viewl, viewr) -import Data.Foldable (Foldable(foldMap), toList) -import Data.Traversable (Traversable(traverse)) import Data.Typeable import Control.DeepSeq (NFData(rnf)) @@ -52,7 +58,6 @@ import Data.Data (Data) import Data.Coerce #endif - -- | Multi-way trees, also known as /rose trees/. data Tree a = Node { rootLabel :: a, -- ^ label value From git at git.haskell.org Fri Jan 23 22:43:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:54 +0000 (UTC) Subject: [commit: packages/bytestring] master: hGet returns 'empty' not 'null' at EOF (8d512e1) Message-ID: <20150123224354.4C1743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/8d512e1c622cbe44976ca971af17911b0603edde >--------------------------------------------------------------- commit 8d512e1c622cbe44976ca971af17911b0603edde Author: David Turner Date: Fri Dec 19 15:26:30 2014 +0000 hGet returns 'empty' not 'null' at EOF >--------------------------------------------------------------- 8d512e1c622cbe44976ca971af17911b0603edde Data/ByteString.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/ByteString.hs b/Data/ByteString.hs index 4932a54..bf33a99 100644 --- a/Data/ByteString.hs +++ b/Data/ByteString.hs @@ -1713,7 +1713,7 @@ putStrLn = hPutStrLn stdout -- is far more efficient than reading the characters into a 'String' -- and then using 'pack'. First argument is the Handle to read from, -- and the second is the number of bytes to read. It returns the bytes --- read, up to n, or 'null' if EOF has been reached. +-- read, up to n, or 'empty' if EOF has been reached. -- -- 'hGet' is implemented in terms of 'hGetBuf'. -- From git at git.haskell.org Fri Jan 23 22:43:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:54 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #119 from hvr/pr-base48 (a4df7f3) Message-ID: <20150123224354.CECDA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/a4df7f35d859634f321c05f574e268a1c47792be >--------------------------------------------------------------- commit a4df7f35d859634f321c05f574e268a1c47792be Merge: 55f65cd 71f53cb Author: Milan Straka Date: Tue Dec 30 14:42:22 2014 +0100 Merge pull request #119 from hvr/pr-base48 Make `-Wall`-clean for base-4.8.0.0 >--------------------------------------------------------------- a4df7f35d859634f321c05f574e268a1c47792be Data/Graph.hs | 2 ++ Data/IntMap/Base.hs | 11 ++++++++--- Data/IntSet/Base.hs | 4 +++- Data/Map/Base.hs | 9 +++++++-- Data/Sequence.hs | 3 +++ Data/Set/Base.hs | 2 ++ Data/Tree.hs | 13 +++++++++---- 7 files changed, 34 insertions(+), 10 deletions(-) From git at git.haskell.org Fri Jan 23 22:43:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:56 +0000 (UTC) Subject: [commit: packages/bytestring] master: Eta expand continuation of empty (9b63d5f) Message-ID: <20150123224356.577F13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/9b63d5f10f7a9f914c74c85539ab6389f12b5bcd >--------------------------------------------------------------- commit 9b63d5f10f7a9f914c74c85539ab6389f12b5bcd Author: Ben Gamari Date: Thu Jan 15 11:54:21 2015 -0500 Eta expand continuation of empty >--------------------------------------------------------------- 9b63d5f10f7a9f914c74c85539ab6389f12b5bcd Data/ByteString/Builder/Internal.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/Data/ByteString/Builder/Internal.hs b/Data/ByteString/Builder/Internal.hs index e8617ef..d52c626 100644 --- a/Data/ByteString/Builder/Internal.hs +++ b/Data/ByteString/Builder/Internal.hs @@ -385,7 +385,11 @@ runBuilderWith (Builder b) = b -- only exported for use in rewriting rules. Use 'mempty' otherwise. {-# INLINE[1] empty #-} empty :: Builder -empty = Builder id +empty = Builder (\cont -> (\range -> cont range)) +-- This eta expansion (hopefully) allows GHC to worker-wrapper the +-- 'BufferRange' in the 'empty' base case of loops (since +-- worker-wrapper requires (TODO: verify this) that all paths match +-- against the wrapped argument. -- | Concatenate two 'Builder's. This function is only exported for use in rewriting -- rules. Use 'mappend' otherwise. From git at git.haskell.org Fri Jan 23 22:43:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:56 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #116 from treeowl/balanceReplicate (e0cfb50) Message-ID: <20150123224356.D8A093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/e0cfb504ce356f75e59ca2b392dee3f93eae0e4b >--------------------------------------------------------------- commit e0cfb504ce356f75e59ca2b392dee3f93eae0e4b Merge: a4df7f3 1e962fc Author: Milan Straka Date: Tue Dec 30 14:49:36 2014 +0100 Merge pull request #116 from treeowl/balanceReplicate Make applicativeTree aim for safe digits >--------------------------------------------------------------- e0cfb504ce356f75e59ca2b392dee3f93eae0e4b Data/Sequence.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) From git at git.haskell.org Fri Jan 23 22:43:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:58 +0000 (UTC) Subject: [commit: packages/bytestring] master: Merge pull request #40 from bgamari/builder-opt (c1960a9) Message-ID: <20150123224358.607683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/c1960a9a0f7c0c600cc0c21fb8aed76da45a42c8 >--------------------------------------------------------------- commit c1960a9a0f7c0c600cc0c21fb8aed76da45a42c8 Merge: fa7e1cc 9b63d5f Author: Duncan Coutts Date: Thu Jan 15 19:22:38 2015 +0000 Merge pull request #40 from bgamari/builder-opt Eta expand continuation of empty >--------------------------------------------------------------- c1960a9a0f7c0c600cc0c21fb8aed76da45a42c8 Data/ByteString/Builder/Internal.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:43:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:43:58 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #118 from treeowl/apcleanup (202e2f2) Message-ID: <20150123224358.E36143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/202e2f2a28d1d914d19e177bc4b6e64597cf62f2 >--------------------------------------------------------------- commit 202e2f2a28d1d914d19e177bc4b6e64597cf62f2 Merge: e0cfb50 f1e0f8e Author: Milan Straka Date: Tue Dec 30 14:55:09 2014 +0100 Merge pull request #118 from treeowl/apcleanup Clean up <*> development artifacts >--------------------------------------------------------------- 202e2f2a28d1d914d19e177bc4b6e64597cf62f2 Data/Sequence.hs | 20 +++++++++++--------- 1 file changed, 11 insertions(+), 9 deletions(-) From git at git.haskell.org Fri Jan 23 22:44:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:00 +0000 (UTC) Subject: [commit: packages/bytestring] master: Merge pull request #38 from DaveCTurner/patch-1 (08d5c3a) Message-ID: <20150123224400.6B12B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/08d5c3a80be94a9d7ef7731317dea79aaadbd2c4 >--------------------------------------------------------------- commit 08d5c3a80be94a9d7ef7731317dea79aaadbd2c4 Merge: c1960a9 8d512e1 Author: Duncan Coutts Date: Thu Jan 15 19:23:43 2015 +0000 Merge pull request #38 from DaveCTurner/patch-1 hGet returns 'empty' not 'null' at EOF >--------------------------------------------------------------- 08d5c3a80be94a9d7ef7731317dea79aaadbd2c4 Data/ByteString.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 22:44:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:00 +0000 (UTC) Subject: [commit: packages/containers] master: Add warning about Seq size. (74afe96) Message-ID: <20150123224400.ED2993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/74afe969cc792ab30715f6ad7399bddb492a1b66 >--------------------------------------------------------------- commit 74afe969cc792ab30715f6ad7399bddb492a1b66 Author: David Feuer Date: Wed Dec 31 01:24:48 2014 -0500 Add warning about Seq size. >--------------------------------------------------------------- 74afe969cc792ab30715f6ad7399bddb492a1b66 Data/Map.hs | 4 ++++ Data/Map/Lazy.hs | 4 ++++ Data/Map/Strict.hs | 4 ++++ Data/Sequence.hs | 14 +++++++++++--- Data/Set.hs | 4 ++++ Data/Set/Base.hs | 4 ++++ 6 files changed, 31 insertions(+), 3 deletions(-) diff --git a/Data/Map.hs b/Data/Map.hs index 1281f2f..e4af46a 100644 --- a/Data/Map.hs +++ b/Data/Map.hs @@ -45,6 +45,10 @@ -- first argument are always preferred to the second, for example in -- 'union' or 'insert'. -- +-- /Warning/: The size of the map must not exceed @maxBound::Int at . Violation of +-- this condition is not detected and if the size limit is exceeded, its +-- behaviour is undefined. +-- -- Operation comments contain the operation time complexity in -- the Big-O notation (). ----------------------------------------------------------------------------- diff --git a/Data/Map/Lazy.hs b/Data/Map/Lazy.hs index 2705de5..17fa6fe 100644 --- a/Data/Map/Lazy.hs +++ b/Data/Map/Lazy.hs @@ -44,6 +44,10 @@ -- first argument are always preferred to the second, for example in -- 'union' or 'insert'. -- +-- /Warning/: The size of the map must not exceed @maxBound::Int at . Violation of +-- this condition is not detected and if the size limit is exceeded, its +-- behaviour is undefined. +-- -- Operation comments contain the operation time complexity in -- the Big-O notation (). ----------------------------------------------------------------------------- diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs index 7309041..623b1df 100644 --- a/Data/Map/Strict.hs +++ b/Data/Map/Strict.hs @@ -44,6 +44,10 @@ -- first argument are always preferred to the second, for example in -- 'union' or 'insert'. -- +-- /Warning/: The size of the map must not exceed @maxBound::Int at . Violation of +-- this condition is not detected and if the size limit is exceeded, its +-- behaviour is undefined. +-- -- Operation comments contain the operation time complexity in -- the Big-O notation (). -- diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 11f1880..21c54d3 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -16,7 +16,8 @@ -- Module : Data.Sequence -- Copyright : (c) Ross Paterson 2005 -- (c) Louis Wasserman 2009 --- (c) David Feuer, Ross Paterson, and Milan Straka 2014 +-- (c) Bertram Felgenhauer, David Feuer, Ross Paterson, and +-- Milan Straka 2014 -- License : BSD-style -- Maintainer : libraries at haskell.org -- Stability : experimental @@ -29,7 +30,7 @@ -- -- An amortized running time is given for each operation, with /n/ referring -- to the length of the sequence and /i/ being the integral index used by --- some operations. These bounds hold even in a persistent (shared) setting. +-- some operations. These bounds hold even in a persistent (shared) setting. -- -- The implementation uses 2-3 finger trees annotated with sizes, -- as described in section 4.2 of @@ -40,9 +41,16 @@ -- -- -- /Note/: Many of these operations have the same names as similar --- operations on lists in the "Prelude". The ambiguity may be resolved +-- operations on lists in the "Prelude". The ambiguity may be resolved -- using either qualification or the @hiding@ clause. -- +-- /Warning/: The size of a 'Seq' must not exceed @maxBound::Int at . Violation +-- of this condition is not detected and if the size limit is exceeded, the +-- behaviour of the sequence is undefined. This is unlikely to occur in most +-- applications, but some care may be required when using '><', '<*>', '*>', or +-- '>>', particularly repeatedly and particularly in combination with +-- 'replicate' or 'fromFunction'. +-- ----------------------------------------------------------------------------- module Data.Sequence ( diff --git a/Data/Set.hs b/Data/Set.hs index 37366fe..fd8c8b9 100644 --- a/Data/Set.hs +++ b/Data/Set.hs @@ -38,6 +38,10 @@ -- 'union' or 'insert'. Of course, left-biasing can only be observed -- when equality is an equivalence relation instead of structural -- equality. +-- +-- /Warning/: The size of the set must not exceed @maxBound::Int at . Violation of +-- this condition is not detected and if the size limit is exceeded, its +-- behaviour is undefined. ----------------------------------------------------------------------------- module Data.Set ( diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index e1ebad3..616d0eb 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -45,6 +45,10 @@ -- 'union' or 'insert'. Of course, left-biasing can only be observed -- when equality is an equivalence relation instead of structural -- equality. +-- +-- /Warning/: The size of the set must not exceed @maxBound::Int at . Violation of +-- this condition is not detected and if the size limit is exceeded, its +-- behaviour is undefined. ----------------------------------------------------------------------------- -- [Note: Using INLINABLE] From git at git.haskell.org Fri Jan 23 22:44:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:03 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #122 from treeowl/dangerdoc (d5f5582) Message-ID: <20150123224403.0181F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/d5f5582709630c2a40ef998ffd727b8f739534df >--------------------------------------------------------------- commit d5f5582709630c2a40ef998ffd727b8f739534df Merge: 202e2f2 74afe96 Author: Milan Straka Date: Sun Jan 4 22:16:07 2015 +0100 Merge pull request #122 from treeowl/dangerdoc Add warning about Seq size. >--------------------------------------------------------------- d5f5582709630c2a40ef998ffd727b8f739534df Data/Map.hs | 4 ++++ Data/Map/Lazy.hs | 4 ++++ Data/Map/Strict.hs | 4 ++++ Data/Sequence.hs | 14 +++++++++++--- Data/Set.hs | 4 ++++ Data/Set/Base.hs | 4 ++++ 6 files changed, 31 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Jan 23 22:44:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:05 +0000 (UTC) Subject: [commit: packages/containers] master: Add unnecessary call in fromArray to make (Ix i) constraint look needed. (6004065) Message-ID: <20150123224405.08CEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/6004065c646a578fee51c8b6a35fb20514579507 >--------------------------------------------------------------- commit 6004065c646a578fee51c8b6a35fb20514579507 Author: Milan Straka Date: Sat Jan 10 14:25:35 2015 +0100 Add unnecessary call in fromArray to make (Ix i) constraint look needed. >--------------------------------------------------------------- 6004065c646a578fee51c8b6a35fb20514579507 Data/Sequence.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index 21c54d3..b62b16a 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -186,6 +186,7 @@ import Data.Data -- Array stuff, with GHC.Arr on GHC import Data.Array (Ix, Array) +import qualified Data.Array #ifdef __GLASGOW_HASKELL__ import qualified GHC.Arr #endif @@ -1649,6 +1650,10 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg fromArray :: Ix i => Array i a -> Seq a #ifdef __GLASGOW_HASKELL__ fromArray a = fromFunction (GHC.Arr.numElements a) (GHC.Arr.unsafeAt a) + where + -- The following definition uses (Ix i) constraing, which is needed for the + -- other fromArray definition. + _ = Data.Array.rangeSize (Data.Array.bounds a) #else fromArray a = fromList2 (Data.Array.rangeSize (Data.Array.bounds a)) (Data.Array.elems a) #endif From git at git.haskell.org Fri Jan 23 22:44:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:06 +0000 (UTC) Subject: [commit: packages/bytestring] master's head updated: Merge pull request #38 from DaveCTurner/patch-1 (08d5c3a) Message-ID: <20150123224406.2AE2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring Branch 'master' now includes: 1f9a3a1 new APIs from Pugs: idx, lineIdxs, packChar, elems 6d4cf90 Added more documentation to betweenLines. bfd349a Changed FastFastString to FastPackedString in some error messages. deb0e46 Include index and string length in index and indexWord8 error messages. a272568 Added copy function. c5f683f Added QuickCheck property for copy. 9474a49 Added inits and tails, with QuickCheck properties. a540a51 Added isSubstringOf, findSubstring and findSubstrings, with QuickCheck property. Implemented using the Knuth-Morris-Pratt algorithm. dc8d7e9 Some clean-up of findSubstrings. 178a1dd Splitting lines with CRLF fde3fb9 Add replicate. been hanging around in hmp3 for a while 703b121 add some new functions. and use inlinePerformIO, courtesy Simon M 616c7bc Faster map, factor out cbits, and general cleanup 2472930 mergeo c9f9432 Make no-mmap the default 19aadae Tweak some functions, based on benchmarks d0a7235 tweak c981e16 benchmark tweaks 3e20f36 typo in cabal file 5a3b30e And also test Data.PackedString while we're here 7b78404 and flush c1ad58d more flushing 4921ec8 Some tests won't run in the benchmark ab27092 benchmark results 658bbc5 And bump version 2c1aa8c And benchmark against previous version c06335f comment only 670ad36 Replace C maximum and minimum with fast Haskell versions e337942 Also run benchmarks by default b641fc6 BSD license everything. Remove some more cbits e35498a Comments, and clean up a warning 52f60d8 Use plusPtr, instead of advancePtr, as Bulat suggested ba5cc13 update benchmark results with non-cbit code fdb9390 Squash space leak in findIndicies f33f91c typo in STRICT1 macro 81c26f8 Update bench times with new fast elemIndicies 602881f mention speed of box the benchmarking was done on 720a302 Add SCC tags to Bench.hs, so we can optimise on space too 0272fd7 More efficient tails and much better elemIndices on space and tiem 0af4b9f Add filterChar, a space and time efficient version of filter . (==), + properties cad2a5b elemIndices benches updated 7ca5914 Tweak Bench.hs 95c2ea1 1G stress test results 59c7ac2 and results for 0.5G strs d0460ec typo 8f55718 USE_MMAP should wrap some cbits too 7b6c506 And guard the .h file , just for good measure a2932ce Restore fast C versions of maximum and minimum. But make them optional 621fb7a +unsafeIndex, and Simon's 'split', which has nicer algorithmic properties 157b3c1 Merge Simon's QC tests with our own. Combine all testing into 'make' target e9523c3 hmm. can't use -Defs in cbits, for current cabal, at least 2b0ef36 Clean up todo lsit 1bdcbd1 More emphasis on Word8. 986707f More docs 7da8c03 Bump version bd5c752 1 less todo 44c1a30 doc tweaks 03df26c wibbles 7c6b651 Return rest of string in readInt 3d360b8 And update qc test 097150c Benchmark for ghc 6.6 71305af Fix compiling for GHC 6.5 4cbc1e0 HEADS UP: Module renamed: Data.ByteString c4c094a getLine, getContents, faster elemIndices and lineIndices 844c496 more benchmarks, more properties aa8cba1 Merge splitWith and breakAll. splitWith is faster. Hence encode words as tokens isSpace 7f3f681 Update speed c9c8614 Faster version of 'split' 84000f3 Update timings 7cd4d62 Reexport ByteString through FastPackedString. Solves versioning issues. Idea from Einar 8bf1b77 Add join2, a specialised join. And a ByteString getArgs (!) 1ba2c76 Docs only 73308dd Add wc -l benchmark 9161cbe Export unsafeIndexWord8. Sometimes useful be4fa54 wibble 1dd7b8a Add bytestring putStr and putStrLn. Just synonyms d350ebb Add zip, zipWith, unzip + QC properties 780913b Benchmark zip and zipWith 482a72f Add revcomp benchmark 5a03914 Comments and cleanup 948b21e 5x faster replicate. Uses memset 6930e7f More benchmarks d3d9afa Most of the todos are done ba0319b Bump version ebd90fb benchmark 4347862 And also make a legacy synonym for FastString. Einar's idea again 0dfd75b Move options back into pragma. Helps standalone use. b54a570 Docs, and 'construct' is now called 'packCStringFinalizer' f7b877e Add notElem + QC property 515a3a5 Add filterNotChar == filter . (/=) , but 5x faster 0800d9d whitespace only 81458f8 space leak squashed in elemIndexLast 7ccd18c Much more efficient breakLast 5e5f970 Add bench case for elemIndexLast 5040bb5 HEADS UP : split Word8 and Char between Data.ByteString and Data.PackedString.Latin1 10d901d HEADS UP: the split is now : Data.ByteString and Data.ByteString.Char, the latter provides Char ops (and exports pure ByteString ops too) 18c9acf typo 3e479df typo e34e449 complexity wrong in packChar/Byte 870a179 Also export IO functions through Data.ByteString.Char b08d519 typo ebb519f filterChar * and friends aren't using predicates, pointed out by Duncan dc26ca7 typo 4f1e432 typo ad2c639 Inline pragmas speed up some things 01c29e7 complexity annotations fece71a tweak inlines, based on empirical studies ee1b13a Add some #ifdefs for GHC specific things e38cbad HEADS UP: Data.ByteString.Char -> Data.ByteString.Latin1. All functions needing Char.* now in Latin1. 1ac0cb6 Better comments. 100% faster isSuffixOf (only look at the end of the string), and 30% faster append (don't use concat, just memcpy) c28f981 Also move readInt* into Latin1.hs. It drops spaces. b9b7af4 wibble 9e020ea Can't append in one memcpy. Bad on memory pressure 3397941 Update bench mark times a3f38e9 Benchmakr Char and Word8 layer simultaneously cb81626 No need for separate Byte column. they run at the same speed 0b6bfd3 strictness on split doubles speed 28e4c98 comment only dfbe46c comment 8202887 wibble b8b6b83 Ok. Finally. John, Einar and I all prefer ByteString.Char8. So that's what it is. Don't make any claims about latin1 or encodings or nought. 9bbed39 Implement count :: Word8 -> ByteString -> Int. Makes for 1 liner filterChar, and 3 x faster too. Idea from Ketil e8c12f4 Export packAddress* via Char8 too 19dc69a Use Foreign.Concurrent.newForeignPtr whenever using GHC. Means ByteString now runs interpreted in ghci successfully 5f60a82 Add QC properties for (w2c . c2w) == id , and (c2w . w2c) == id 7a4bed3 comment only af442f4 A more elegant 'count' ce1731f Use memcmp for compareBytes. It really is 4x faster now I check 54ceebb And use faster (?) Char8 pack, after consultation with Einar 46fff40 update benchmarks. looks good 95e80d6 Use Ketil's idea for a custom Word8 isSapce 8a254b3 point free Char8 makes the code simpler 426170c comment only 6a7a56d bump version 201e25b comment only 15daeef hGetNonBlock is glasgow-specific d18bc46 Fix portability to hugs. Only a few cppism and a pattern type annotation had crept in. b9424fd Make Quick.hs hugs friendly db24189 comment on pack's performance 523b919 space only fdd841f Fix minor bug in splitWith on hugs only e8c1c14 Use Simon's qc framework. more amenable to testsuite error diffs fd76a0a typo 48bcb8f comment b579c05 AudreyT's copyCStringLen patch c29225b Add cbits version of count, around 30% over memchr version fcd1432 typo 6ca11b5 Fix indenting for YHC 73f5e60 Unnecessary header import ec9e7a5 HEADS UP: remove mmapFile for now. Not portable enough. Enable cbits by default for hugs and ghc b911d08 Notes about porting to yhc and nhc edebcfe comments only 3ae785c Fix rounding-pasto error causing string truncation in hGetLine aa01d97 Add spellcheck test from packedstring 46b76d4 More info on running the testsuite 2c5c7b6 Fix foldr1 in Data.ByteString and Data.ByteString.Char8 dd51fa8 More foldl1/foldr1 properties, thanks to sjanssen 0fb73f8 Add group and groupBy. Suggested by conversation between sjanssen and petekaz on #haskell 3887603 And quickcheck and benchmark them c30df57 Another benchmark 004c130 Another groupBy test. Suggested by sjanssen 9848554 Bit faster if we filter before we map d2af22c Fix groupBy to match Data.List.groupBy. 7bcaf68 Add -fglasgow-exts to OPTIONS_GHC f6f6964 comments only 28b992e Migrate to counting sort. 1f0fa7a Benchmarks for the new sort. 56e53f5 couple of wibbles. and remove the stdlib header. not needed at all now d6ad48b sort goes from 13.9s to 0.16s over 20M. update benchmark numbers bd6f4ec todo is empty now ef5cbd4 have linesort run in 'make' under tests/ too 14a6d8b clean up makefile e44e278 Array fusion for maps. We can now fuse map f (map g (map h ... ) into map (f . g . h ..) More functional array fusion to come. a5a1eea Add test for map fusion d598761 A better fusion test a084e72 Add gloop, a generic bytestring loop operator, and another RULE fd15070 simpler not elem c0f9fcd Some short cut cases in eq and cmp. Suggested by dcoutts, ndm and musasabi f18dfa0 Full array fusion for pipelines of maps and filters 45a3e39 Add array fusion version of foldl. 7b10a75 Fix build on hugs fde6eb2 Oh. oops. \a0 should be in the isSpace function. spotted by QuickCheck 76efd07 comment only ede400e generalise some tests 087f721 Use simple, 3x faster concat. Plus QC properties. Suggested by sjanssen and dcoutts 7473f73 Do realloc on the Haskell heap. And add a really tough stress test d21a37d RULE to rewrite length . lines -> count 60612c0 Misc wibbles 844214f wibble a5b9af9 Remove some dead code 71c4b43 dcoutt's packByte bug squashed 47c23e3 Squish orphan rules warning 21aa2a0 Add inline/unsafe bug test 2cebdbd steal some more properties from the ndp quickchecks e0039af Start on fps 0.7 7b06786 untab 1b22799 Much improved find and findIndex. Idea from sjanssen. + QC properties 5f0e191 filterF is fast enough now we can defined filterNotByte in terms of it dbfd6a3 Fix import syntax for hugs. From sven panne ade2948 Fix all uses for Int that should be CInt or CSize in ffi imports. Spotted by Igloo, dcoutts c07011c update timings b499779 Import nicer loop/loop fusion rule from ghc-ndp 63864ec Fix stack leak in split on > 60M strings 8999bb7 Try same fix for stack overflow in elemIndices 764aaa8 Give unlines a chance to handle 0.5G 13a3e5f Help out splitWith a bit 60566dd Fix for picky CPP 01cafa8 hide INLINE [1] from non-ghc compilers. pointed out by Einar 04f87bc Critical INLINE on words exposes splitWith and halves running time 4f1108c Better results on big arrays db321fc Reorder memory writes for better cache locality. 014feab Surely the error function should not be inlined. 352a0ba Generalise the type of unfoldrN 6f145b9 merge-o 5b315d5 Add foldl', and thus a fusion rule for length . {map,filter,fold}, that avoids creating an array at all if the end of the pipeline is a 'length' reduction a0f4a54 Missing RULES pragma. doh e6a9f25 An Int constraint on the fusion rule can't hurt 5714348 clearer RULE names 24aa034 Test length/loop fusion 26c4272 Disable length/loop fusion for the time begin. Too many allocs 0ba8574 Partial implementation of Data.ByteString.Lazy 507fe45 More ByteString.Lazy updates 0e80679 group, join & indexing functions for .Lazy 793f858 Factor error functions & strings. 0f70003 Export a couple of things needed by Lazy.hs and Char8.hs c018ddc -Wall police 5942797 More blurb on Lazy.hs a6b9b3a Bug in foldr (it was folding from the left) spotted by QuickCheck 28ff585 Handle negative indices to take correctly. Spotted by QuickCheck 1fd1e67 Add Lazy.filter 77457be whitespace only ed8a704 Add QuickCheck properties for Data.ByteString.Lazy. Try runhaskell Lazy.hs in tests/ 8ac4b82 Fix deriving Show for hugs, now QC/Lazy tests pass on hugs too aed142b Also compile the QC/Lazy tests. Good for your stress e8b1fa8 A better Arbitrary instance 0e75785 Change a couple more Int to CInt. Fixes compare on 64bit arches. 619d36c Fix reverse and reverse QC check 41e31a0 Optimise foldr1 foldl1 cases by relying on invariant 5fd7e40 More Lazy updates. bdb59e2 Test a smaller range of Word8 in Lazy,hs, hoping to hit pivot elements more often. Clean up Quick.hs eb3dca3 Comment out splitWith until we work out how to do it. 67a9972 QC properties for find, findIndex/find, elem, notElem, filterByte, filterNotByte edf009e HEADS UP: Add lazy IO functions. Haskell breaks the 4G barrier! 7aebe35 Add IO with tunable chunk size 0cca072 Add a Lazy.hs IO benchmark e014bb4 make haddock happy 106ac9e Fix Int/Int64 types in Lazy tests a7d56fa Fix and tidy split & slitWith 657edfc Add invariant checking and prop_split to QC tests of Lazy 6b6087b Do our own realloc, and thus generate() can use the Haskell heap. Makes abotu 10% for reduction functions that use generate a7783a1 whitespace fe6ca78 Tweak test 438b9cb Fix type of snoc in docs b7e5cf7 Add an alternative framework for QCing the Lazy module 6471146 Add some zipping ops to .Lazy 9d0ee20 Increase default chunksize to 128k, assuming everyone's cache is at least this big. 6ff5940 More useful lazyio.hs 84c57b5 Handle invariant failures in init and concatMap 48b70f3 Add new tests to testsuite da78888 new realloc helps timings 53a573b Add isPrefixOf to Lazy 4ec8f29 Add QC test for isPrefixOf a311ea9 -Wall police. Manually fuse filter (not.null) . map f. More comments 59c5c11 more tests 20790a9 more tests 769d735 Bump down default chunk size to 64k. Should be enough room for other programs de276e1 dead code elimination d89f66e Add 'make plot' target in tests/ that draws pretty graphs of Lazy vs Vanilla bytestrings 0e700f6 Disable group/groupBy. There's a bug. Spotted by ADEpt. I dislike this function anyway. Too inefficient ;) 5e687e4 Make "mycheck" generate different randoms each run. Moved test helpers common to both testsuites to separate module. cc22442 Merge ADEpts patch 49af360 Missing --make in tests/ 5bf5bbf Probably fix for group/groupBy 6f22d7b change code to make comment unnecessary 6553da1 Remove special cases from split/splitWith. This improves the performance of L.split. For some reason L.splitWith is much slower than P.spltWith where as L.split is only marginally slower than P.split. 32acc3e Add group & groupBy to benchmark The lazy version performs reasonably well. 302caa3 disable groupBy for now. Note bug in groupBy (/=) when chunk size is 1 byte 5130d5e -Wall police, and tweak Lazy.hs db21e25 Reorder Bench.hs slightly dade9de Tweak the graph output slightly 2dcdc54 Fix sily copy'n'paste bug in Lazy.groupBy c70e7fb Fix -Wall groupBy warnings and re-enable groupBy benchmark 116ba7a mapF -> map', filterF -> filter' 93893c1 tweak tests 191a625 Comment about the shift/peek::Word32 approach being slower 7cb7c36 Move -fno-warn-orphans into OPTIONS pragma d6683f9 Tweak bench output 6ef68ff Handle n <= 0 cases for unfoldr and replicate. Spotted by QC 2ed2fb5 Handle n < 0 in drop and splitAt. Spotted by QC. 47cb4da Lots more QC tests using the new framework 39ed4c1 Add 'make fast' test target, just runs the QC tests 4 ways d43ba5c bug in comment 39f8b07 More QuickChecks 5d842dd More messing in the tests/ de50e72 INLINE on Lazy.find,findIndex squashes whatever was happening, and they now run at ByteString speeds fbb21d1 INLINE also fixes splitWith 409688f Since we can't fuse Lazy.map or Lazy.filter, use the fast P.map' and P.filter' 39e9ff5 Clarify performance of lazy, now we've squashed the leaks 5258db4 Add lazy foldl', with QC and benchmarks 55ebf8a Comment out unimplemented things 3bd80c4 Note that groupBy is still broken on defaultChunkSize=1 62e2396 Fix Lazy.groupBy again The problem was happening for operators that are not equivalence relations eg (<). One bug was that it was using the operator the wrong way wround. The more subtle problem was that it was using the final element in the group to compare against rather than the first as Data.List.groupBy does. For example groupBy (<) [0,10,5] = [[0,10,5]] rather than [[0,10],[5]] this is because we compare 0 & 5 rather than 10 & 5 since the first element in the group is the one that is used as the representative element. 03ef076 Whitespace changes e69bb20 Add unsafeTake and unsafeDrop These versions assume the n is in the bounds of the bytestring, saving two comparison tests. Then use them in varous places where we think this holds. These cases need double checking (and there are a few remaining internal uses of take / drop that might be possible to convert). Not exported for the moment. 4eb89f6 Eliminate special case in findIndex since it's handled anyway. defbd23 More effecient findIndexOrEnd based on the impl of findIndex e33c22c copyCString* in IO, and fix buglet in splitAt (degenerate cases the wrong way around) 5a3ebc9 assertion test wrong way around. spotted by hugs (!) 6a7c420 Use readFile, it'll avoid realloc issues fb9e23b Comment on when to use readFile over hGetContents 9f5671f Export unsafeTake and unsafeDrop 4325aef Make Lazy.replicate more efficient for large inputs c398265 Add lazy hGetLines to Data.ByteString d22b560 Add test for hGetLines. A faster, lazier wc -l 0c72a33 Comment b8b88fc tweak e5182d5 Fix invariant violation in new replicate 097bd22 asthetic tweaks to bench code, also add B.findIndexOrEnd a36ea23 Use Lazy.replicate in Lazy.filterByte 1ff1260 Make sure to optimise the cbits aeedd0b Add files to help us compare the api of list vs. fps 6919b5b Add iterate, repeat & cycle to .Lazy These are more infinite list functions using sjanssen's trick. Also add a smaller chunk size for use with these functions to make it a bit less wasteful of space (currently 4k vs 64k). 0780594 Handle merge e96bb33 And make Duncan's patches type check 871266e Add foldl1' d1118a9 More Properties.hs 9b8cc7d Update api diff 630739d Make the api easier to diff (try vimdiff *.api) 60a1e69 Comment fix. 3864856 Data.ByteString.Internal Contains functions which might be useful in several modules, but aren't appropriate to expose to users of ByteString. For example: inlinePerformIO; various C functions. 1f81030 Add fuseable scanl, scanl1 + properties 7c01d4e Clean up api list c03b740 export scanEFL 93e79b4 Merge Quick.hs into Properties.hs, the grand, unified properties list c677899 And clean up makefile. Add make fast target, for a quick, quick check 6d95a27 And make Interal.hs hugs-friendly ef1fe9e Update readme to reflect new test structure 4f4c664 Comment on the inappropriatness of concatMap on ByteStrings 898ba3c Spotted another chance to use unsafeTake,Drop (in groupBy) f983e12 Sadly cc-options get applied to .hs files too which will break things. Such aggressive gcc flags are only appopriate for the fpstring.c module. Incidentally, -optc-O2 will also break on some arches due to mangler issues. d611123 Add Lazy.interact ac257c4 Use List function rather than inlined definition. (And this time it type-checks!) 5a2f1f4 Hide Prelude.interact.. 8b85599 Tweak api 7aa7c2b Move c2w, w2c into Internal, now Data.ByteString.Lazy.Char8 needs them too 7ece59b Move more Char8 things into Internal.hs e729786 Add Data.ByteString.Lazy.Char8 6cae62e Whitespace only 10cc6e5 Plot with boxes. Clearer d6a750f Add SCC pragmas so make prof keeps working 701937a Minor doc tidyup. Use haddock markup better. Remove untrue comment about CStrings in .Lazy. Note dons as author of .Lazy too. 8c5c0a5 Simplify the join() implementation. Spotted by Duncan. d382afb Add a TODO list of things duncan and I talked about on irc 917b833 More stuff to do ea4872e Abolish elems. It's name implied it was unpack, but its type didn't. it made no sense 782192d wibble in todo list 6b591c2 In the search for a more orthogonal api, we kill breakFirst/breakLast, which were of dubious value. 2cafe9e elemIndexLast -> elemIndexEnd 315cdc4 pack{Byte,Char} -> singleton. As per fptools convention 169fdb2 Start a bit on the null terminated string property 698fa97 Tweak todo 81b2612 Reorder the export lists to better match the Data.List api If this seems a good idea, I'll do it for the .Char8 modules too. 62669b3 Comment only. 781e0f7 Another comment. e73d499 Add unfoldr to ByteString and .Char8 A preliminary implementation of unfoldr. Things that still need to be done: 1. Tests for unfoldr. 2. unfoldr currently reallocates a new buffer twice the size of the old one, dcoutts has suggested an approach using concat. We need to compare the performance of these two approaches. 3. unfoldr for .Lazy. 9d8ad14 Merge dcoutt's and sjanssens's patch dfa86c4 Change the implementation of the unfoldr(N) functions. Use a more compact implementation for unfoldrN and change it's behaviour to only return Just in the case that it actually 'overflowed' the N, so the boundary case of unfolding exactly N gives Nothing. This also helps with maintaining the invariant in .Lazy Implement unfoldrr and Lazy.unfoldr in terms of unfoldrN. Use fibonacci growth for the chunk size in unfoldr and simple quadratic growth for Lazy.unfoldr and in the latter case an upper bound on the chunk size. upper cdc2537 Doh! revert change to type used during debugging. a1493e6 Implement mapAccumL and reimplement mapIndexed using loopU Not fully tested yet. 9bbdc07 Implement coalescing in cons Not perf tested yet. The coalescing threshold needs testing to find the ideal value. f2b04e5 Rearange export lists for the .Char8 modules and minor tidyups for the exprt lists of the other two modules. f171627 instance Monoid ByteString b670ef0 Swap the result tuple in loopU because it's obviously the wrong way round! ;-) 245fdaa Add loopU for lazy ByteStrings This reuses much of the fusion machinery from the ByteString module so we only need to add loopU and the loop/loop fusion RULE. f98a041 Use loopU to make several ByteString.Lazy funcions fusable This is really just an experiment, though the QC tests still seem to be working, and the fuse test indicates that the fusion RULES are working. d643b04 export mapAccumEFL, mapIndexEFL for use in .Lazy 8ca4f38 Add Lazy.inits and tails, including QC tests f252ebf Add Lazy.foldl1' And fix docs for foldl' 41bff3f Documentation fix. f274442 Remove the api files, we know what's missing now 17b17c2 Disable coalescing cons. Its too strict. Add QC test for diverging cons. 44abde3 Add properties for unfoldr, mapAccumL and foldl1' 9a2dc40 Make hugs happy ee2cff6 Further simplify the instances for ModeledBy e42c66c Dont need undecidable instances, just overlapping ones af239b0 Lots of commentary on how the model checking quickchecks works 02bdf26 unfoldr is done. push of todo list 09c41e3 Use the NatTrans class from Gofer to write a generic Model instance for types of kind * -> * 19e0156 Note that foldl . map with lazy fusion seems to run slower. foldl'.map seems fine though 4e443d1 Export some more fusion utilities, so we can QC them 167a525 Convert all RULES into QC properties, and check them 7d564eb And QC tests reveal my hacking lines/count rule was wrong if there's no \n in the string. Disable it. 2eccd39 Make hugs happy 2776fa3 Add breakEnd, (== spanEnd (not.p)). Like break, but from the end of the string b7387ec Move the ByteString representation and low-level bits to a Base module Also move the array fusion code. Patch up the import/exports for the other modules. f67f57a Make fuseEFL use a StrictPair for much better fusion performance With this change the fusion of fold . map runs about 40 times quicker since the extra strictness allows ghc to avoid allocting lazy pairs. 5292e59 Prevent fuseEFL from getting inlined too early. This is a patch from ndp upstream. deae39d Trivial doc fix/tidy. f1f86f4 Do not need -fffi on any module except Internal 5ed8e02 Re-enable all the fusion tests. Yay, fusion is no longer slower. 92d6996 Update the fusion properties 0d298fd Add (commented out) wrapper/loop version of loopU including the loop/loop wrapper elimination RULE 0b877cf wibbles 54cd59a Abolish .Internal. Move fusion stuff into .Fusion. And internal stuff into .Base e45460d comment wibbles 5479525 More extensive use of strict pairs, from the ndp branch 00ece53 Make hugs happy 74d80bb Reinstante coalescing cons with a bigger warning about its strictness Also remove lazy cons QC test. Fix untrue comment on replicate. 48cb990 Tiny doc addition b542235 Cleanup of existing Fusion code and wdges of new code for a new method. Rename NoAL -> NoAcc. Remove the noAL value, just use the constructor everywhere. rename type EFL to AccEFL and add several other special cases. Don't parameterise AccEFL by the in and out types, it's always Word8 Since we don't have so many 'Word8's all over the place we don't need the type W = Word8 short hand any more. cd167ec Enable and export the alternative array fusion system. It's not being used yet in ByteString but it can be tested seperately. It needs a very recent version of ghc-6.5 (May 25 or later) for the RULES matching to work reliably. b08de33 Add a couple TODO items to think about c049a85 Typo in comment 32293b3 Typo fix. 018b622 Heads up. unsafe* now moved to .Base e887494 Make haddock happy fb9c474 Move rules and loopU for lazy strings into Fusion.hs too d174a2c Simplify type of loopL 5a400cf Remove duplicated RULES 2ba790c Fix nasty bug in doDownLoop Copy'n'paste bug. I wasn't calculating the new size of the array correctly which caused the array copying code to segfault. a5d3384 Remove big useless comment. We've debugged that problem now. 7ab76b5 Update type of copyCString,copyCStringLen in export list comment 63f5fe9 Make ByteString use the new fusion framework That is the V2 fusion framework. 6998110 Fix to use the V2 fusion api properly (hangover from testing the V3 api) 67c87a3 Another TODO item 15a7209 Wibble. And fix bug in fuseMapMapEFL, spotted by QuickCheck e43ab40 Add QC properties for all v2 rules. Disable down/* */down rules for now 0ec2603 Split up the list of tests to make QCing quicker Also add 'module Main where' so everything is exported which also makes QCing individual tests or groups of easier because we can do it in GHCi. 511f31f Fix down/down loop fusion bug We have to keep track of the offset as well as just the length of the part of th dest array that has been filled in. 210c656 Don't use inlinePerformIO for loopWrapper due to danger of sharing We really really don't want the dest array to be shared between two loops so use unsafePerformIO rather than inlinePerformIO. We're really depending pretty heavily on GHC optimiser semantics here. This fixes all the QC down loop fusion properties when compiled with -O. b417c54 Specify type for 'run', makes hugs happy df6c198 Use unsafePerformIO on all functions that allocate. Hopefully avoids sharing issues 2432192 Fix bug in Lazy.scanl (bizarrely, imo, Haskell's scan returns a list one element longer than the input list) 6def52b Three (!) pastos in scanr, scanr1. QuickCheck people! 43c6de1 . Add tests that fusion is working in up/down/map/filter cases. . Clean up QuickCheckUtils a bit. . Add some commentary to the rules 00bebfd Wibbles/ cleanup in Fusion.hs. Add a marginally faster doMapLoop (only carry one offset) 2c23181 Add length/loop* fusion, with quickchecked properties. Worth ~10% speedup 5c2d306 makefile wibble 59bdb4d wibbles 360fd6a wibbles 9ab7341 typo cf8297c whitespace only 1c797d7 wibble 0aa0c75 Add minimum/maximum fusion too. But disable for now, its still at least 50% down on the C functions ca49272 Actually, reenable rules for maximum/minimum. Only around 10% worse in stable. Should be ok in the head. c9ca626 Add properties for wrapper elimination and associativity of sequence b363bbd Generate random up/down loops, for tougher testing of associativity and wraper elim d37ded1 whitespace, and don't flip args in fuseMapMap. 952abb3 Add fusion properties for all noAcc forms ffe7441 missing cpp pragma in tests/ 9fd7507 And make QC properties for map/map fusion match the flipped args 6e87064 Lazy.hGetNonBlocking b3063e3 wibble dbaa49c Add a fusion bench mark. Great results 111da3d And add some big pipelines to illustrate the O(n) versus O(1) overhead fusion gives us d13c61f Add cpp to switch between v1 and v2 fusion. Enables us to run benchmarks both ways 75dd83f Tweak copyright on Lazy.hs. the university of glasgow wasn't involved. 77d72b0 notice 1 extra byte was allocated on empty and on singleton e493aba Comments on what happens in empty string cases for head, tail etc. Prompted by ndm 98a0ab9 cpp in QuickCheckUtils.hs to handle missing functor instances 625804b add make hugs target 18847af Add mallocByteStringWith. 334f1b5 generate -> createAndResize. Old name was silly. f9b2e0f tweak makefile for wc a31b144 comments and todos, only 7282744 Wrong test in hGetN, spotted by bringert 73dcc5e clean up notNull functions e392fcb Changed all functions in Lazy and Lazy.Char8 which deal with indices and lengths to use Int64. (All except mapIndexed that is, I leave the magic to dons). 1e4528e A couple TODO isses to think about 59f701e Use mallocForeignPtrBytes rather than mallocForeignPtrArray Since we're always using bytes anyway, saves te comopiler having to specialise the sizeOf (undefined :: Word8). 1833a24 Add assertions to null & length Assert that the length is not negative. In the case that the assertion is disabled, consider negative lengths as null. 26e8bc9 Use bracket in readFile, just like we do for writeFile cfb8df1 Add assertaions to unsafeHead, unsafeTail and unsafeIndex 60d9c8e make hGetN and hGetNonBlockingN strict we can't do lazy IO except for hGetContents which reads the whole file and can semi-close the handle. also make hGetNonBlockingN take a maximum size so it matches the version from Data.ByteString. 71c1a26 Merge 548a7ca Remove pointless special case from hPut f728f47 put all the foreign imports in IO rather than pure This makes the unsafeness more explicit. We were mostly using them in an IO context anyway. Where we do need to use them in a pure context I've added unsafePerformIO b98e061 Reorgaise and rename low level ByteString generators rename create to unsafeCreate since it's not in IO rename mallocByteStringWith to create rename createAndResize to createAndTrim add createAndTrim' as a generalisation remove mallocByteString 4ff9cd7 Fix type of pack in hugs 7e1075a remove skipIndex. Use one of the elimination forms instead 4f2c700 Add appendFile for both strict and lazy 69a4c8f whitespace, wibble c0720fe Cleanup QCs to make them more presentable 3de7b52 Comments on the difficulty of moving compareN/eqN into a single class 4ca3eb7 Update sum test bb35978 Test described on haskell-cafe@ a9cbc81 Also export appendFile via Char8.hs 57736a5 Add cpp to switch between the 4 forms of fusion possibilities we currently have. Makes benchmarks much easier to generate 9307970 Bench wibbles c101fce todo item. 32b8007 make it possible to do fusion profiling too 63cb7cd Add more strictness in the results of several functions Not sure if it actually help but it looks sensible. caaf1a4 Make the code stle for head consistent with tail 6883f23 Make readChunks strict in a more obvious way dd1c02e Add more strictness in the results of a few Char8 functions 0b93975 Add experimental Haskell impls of of readInt for Char8 and Lazy.Char8 Seems to work but not fully QC'ed (indeed no QC tests added yet) However it gets the same results for the sumfile test so it's probably ok... c017dc8 Experimental reimplementation of Lazy.Char8.lines for improved performance Not fully QC'ed but does work with sumfile. Quite a bit faster but significantly more complex (ie a page long rathe than 5 lines) 211c496 QuickChecks for new readInt impl. And comments, -Wall police 8c68f2f Remove half-completed, commented out readint 9b3de58 Add QC properties for lines b053d80 wibbles 5a22e28 HEADS UP: remove null termination pseudo-property a172f7a some todo issues dealt with c094919 Remove cpp in tests, makes hugs happy 38de4ff tweak readme c453a14 make it easier to experimentally benchmark different chunk sizes ef4142c tweak 6168ac2 Have 'darcs test' run a quick version of the QCs 7a31d3c Use -optc-O1 in .Lazy*, -optc-O2 breaks with gcc 4.0.4. Spotted by Audrey 398740e Add support for tuned foreign pointer implementation b011854 investigated, patched, done with foreign ptr tuning 89057e8 Remove test that depends on TH. Rarely used. Not maintained 4e1be24 Update testsuite instructions e91d2d1 update list of things that are run on 'make everything' 7ee9a4d More readme tweaks cc3f6b3 wibble fa1edb8 Start documenting how to do this handle flushing/copying trick 3f4fc55 couple of todo/comments only 4873f11 some more todos fca6a4b Run each benchmark several times Requires changing the 'F' stuff so that it doesn't memoise. Rearange the fusion tests into up,down and noAcc groups. Currently run each test 11 times so we can use 10 runs (after discarding the first run) ff6ed37 todos 8940338 add better hPutStrLn, avoids locking the handle twice on small strings. Suggested by Bulat d11989b Comment on the include-dirs relative path issue 37c1d78 unsafe* shouldn't be exported from Char8 134f7f0 hGetLines should be exported via char8 too 7dd1d36 Prepare for merging back into bsae/ 971e486 faster 'darcs check' 7271765 make hugs happy 5b712c4 Prefix C calls in fpstring.[hc] with fps_ e91b0f4 resync Lazy.Char8 and Lazy 66fb6d4 and fix import Prelude hiding list 107c58d Add model checking property for mapAccumR 894a06c more export wibbles 1046b62 wibble 8acf611 comments in .cabal file 0527446 note that bench is temporarily broken. 5284bd8 wibble in test d3845cb wibble b8235fc update docs 2797e1c doc fix 1dd6afc Add target 'prop-opt', after uncovering as-yet-unfound bug in -O -frules-on 4319232 Also export appendFile via Lazy.Char8 861bec1 Dirty the cache before each run and reorder the GC & delay b869807 Fix copy'n'pasto in SCC name b74a034 Re-export appendFile and import hGetNonBlocking(N). d743cbc move unsafeUseAsCString* into Base.hs. Sync Char8 and normal ByteStrings 2638b40 Add zipWith', a speclialised zipWith. And QC properties for the zip family f56dc18 and add a zipwith specialisation test a72b40a missing #ifdef __GLASGOW_HASKELL__ in Lazy.Char8 83e3e34 use just -O2 aa46c20 no -optc-O2, breaks too often 93938e0 better zipwith spec test. more notes 0d102d2 Disable unpack/build fusion for now. It interacts badly with new rules stuff in ghc 6.5 d4192b5 Fix unpackFoldr bug, twas the seq in the acc which breaks with rules 8cda65d Further comment on seq and build/foldr d98203b portable call to time. Add unpack/head/build/seq test 1db823f Fix bench. make runbench now works again, using the new dirty cache system 54d9dec fromIntegral missing in test 012cbf6 missing import in test 427b4d3 some things done on the todo list 7529a84 doc 64a857e better dirtyCache, idea from roman 8a237c1 O(1) useAsCStringLen, idea from BulatZ ca4c7d4 Clarify comments regarding *AsCString functions 339db99 Handle TextMode properly on windows. Thanks to BulatZ de10f1d tighten import list ff644a2 openBinaryFile/openFile distinction 2e95933 And use openFile/openBinaryFile in .Lazy stuff too c4f452b -optc-O1 is no more required (because we don't use -optc-O2 by default) ae7c607 Simple implementation of getArgs for non-GHC platforms 98b6ffd hGetLines now use hIsEOF instead of catching all exceptions fe64085 ByteString.Char8 - removed now unnecessary #if_GHCs 526ee5b 'interact' for strict ByteString c117e86 mallocByteString = mallocForeignPtrBytes | mallocPlainForeignPtrBytes e558b8b Merge changes ff06dcd Add hugs versions of some IO functions, merged from BulatZ's patches 70c2c1e Simplified and unified lazy hGetContentsN/hGetN/hGetNonBlockingN 4da0635 wibble in Makefile for clean ec8cabd Faster record test 4e4e54b Merge-o 41b4849 hugs wibble 6cc3f27 missing import for hugs a4e4c54 todo, fix groupBy (in ghci only?) 4077a26 Add test for groupby issue 544d010 testify c9f5bb1 run unpackand groupby tests each 'make everything' run 21a8c13 Lazy.Char8 was exporting interact from Prelude rather than Lazy e5b5f00 notes a518bfe add some missing functions to Char8 5a8e0bc this is now the 0.8 branch ad407ca remember that we still have to fix groupBy fe12d1b Encourage users to use -funbox-strict-fields 5689d41 comment out some tests we don't use now d74369a Sync 0.8 and streams api 2e0cbb5 wibble e32c458 wibbles 849a213 Add lazy-as-available byte strings 7835ac8 comment out lengthU rules, now there's no lengthU 2a57542 Merge e1d282a lazy init isn't O(1), I think it should be O(n/c) 4c4e5ee Rewrite some lazy consumers so they don't cause space leaks e10b808 Merge from the unstable branch. API mostly, and hGetSome story. Add fast 'empty()' while I'm here 35277e7 no more findIndexOrEnd exported 4b49215 no more joinWithByte e720cfc remove some bogus things done better with rules a033c64 fix Properties.hs 58c9c5d hide hGet*N functions in .Lazy 3fddf55 no more tokens b9cbf4f inline words, don't export hGet*N from .Lazy.Char8 6ab9c0f no more tokens QC dc27311 No, I can't just merge createAndTrim straight from unstable 621678a good bye packWith/unpackWith fda06a7 rule for join -> joinByte 586a265 rules for break/breakByte and span/spanByte 4ca4656 propeties for the new rules cac7a61 add rules for break isSpace -> breakSpace b7a677e Add rule for specialise dropWhile isSpace -> dropSpace f897002 fix build for hugs 2903ab6 more hugs fixes 47836fb fusion wibbles 674392e update Bench.hs to new api 469ef32 hide internal module from haddock in Data.ByteString a965434 wibbe c72f9d3 hide LPS constructor. move lazy bytestring defn in to .Base 66404de Fix testsuite a425ed1 add fromChunks/toChunks 1e8f6c9 Fix type an implementation of toChunks. It should be returing a list of chunks! :-) Spotted by int-e. 82fa5da add readInteger for *.Char8, and add appropriate quickcheck properties f5846b7 remove leftover strictness annotations. they seemed to hurt more than help. 1d0da03 remove tokens and mapAccumR from .Lazy ef86c74 and another tokens occurence 078c1e1 fix hugs b51f119 fix hugs nice and good 4a4baee Fix lazyness of take, drop & splitAt. Spotted by Einar Karttunen. Thanks to him and to Bertram Felgenhauer for explaining the problem and the fix to me. f7bde9d make cons create 16 byte chunks instead of 17 byte chunks for lazy butestrings 2188ffa export the right 'cycle' 8fc2332 import portability fixes from Ross's base commits 095aad0 remove a slighly suspicious use of unsafeCoerce# 9a96c2b double check blank lines (since QC isn't generating them for us) 0779fbc portability: give alternate import modules for nhc98 85f4119 Workaround for import resolution bug in nhc98. Where there are multiple renamed imports: import X as P import Y as P import Z as P and they all export or re-export the same entity e, nhc98 does not seem to be able to recognise that P.e is a unique entity, despite X.e, Y.e, and Z.e all referring to the same thing. This patch just introduces an extra module name import X as S so that S.e is resolvable. 51c2929 workaround nhc98 import resolution bug for another module 5b16acf wibbles to fix ghc build b7e569a Setup.lhs ae0daf1 Fixups for building with nhc98 - inadvertently missed this file earlier. 1002e53 In teh testsuite, always pass the same GHC options, via ${GHCFLAGS} 02ed236 Test the library in-place rather than whatever is installed 2edc6c7 Add a unit tests file, a test that append is lazy in the tail, and make it so. Append was looking at the tails to see whether or not it was [], which forced evaluation of the tail in situations where that is undesirable. ebebe2a Add lazybuild test cfea341 Hide build noice when running tests 2511eda HEADS UP: Change CString api b4f5c5f add iavor's CString test ea619ea remove filterNotByte, and its rules. Its a rather pointless rule (filter -> filterNotByte -> filter) f9363cb Make fromForeignPtr take the start so it is truly the inverse of toForeignPtr 13e5395 transforming 00c715b adhering to agile principles, requiring a boot-in-place to run the tests on each commit is removed.. f7da7e0 no boot-in-place 3f3c27c comment only a58f789 Make the lazy cons lazy, and add a cons' for when you want it to be strict f82f917 Correct docs for Data.ByteString.Lazy.Char8.cons bdbf53c Add cons' to Lazy.Char8 too 2e228a1 Add complexity to Lazy.cons' docs b90d1cb Define headTail :: ByteString -> Maybe (Word8, ByteString) f9b78ce headTail -> uncons 771dc5b Makefile build system for nhc98 b11229e need things from cbits directory for nhc98 build 8423510 fps package needs extra stack to build (+ add D.BS.Char8) 56c0e47 Implement byteswapping, used for endian fiddling. If the ByteString is going to end up being interpreted as a binary representation of a sequence of 4-byte quantities (e.g. Float), then one might need to change the endianness (byte ordering) of the representation. This patch adds the API call byteswap :: ByteString -> ByteString for such applications. It assumes the bytestring will be a multiple of 4 in size. (If not, the last n<4 bytes will be untouched.) It also assumes (without checking) that the start of the bytestring has the correct alignment. d2ed184 nhc now has hGetBuf/hPutBuf f7f3985 append on lazy bytestrings is O(n/c) (just the inital spine is copied0 1ea65b1 Fix types of foreign imports a6b4957 Remove incorrectly typed commented out foreign imports bf0efcf old nhc98 Makefiles now obsolete 7b08784 nhc98 needs extra stack to build for profiling c0c31a0 Change package name to bytestring and bump version number, and add myself as another author and maintainer 6e5d6d4 Expect to use ghc-6.7 so no need for -DSLOW_FOREIGN_PTR and -funbox-strict-fields was never needed in the first place. d39e604 also rename fps.cabal -> bytestring.cabal b0b36ba Rename .Base module to .Internal 72266d9 Move definition of empty from Internal to main ByteString module I can't recall why we moved it there in the first place, but it's not necessary any more. 23b74c8 Split .Internal module into .Unsafe and .Lazy.Internal The Unsafe module exports parts o the public API but that do unchecked things like unsafe indexing, or things with CStrings that have side conditions. But it doesn't really expose the internal representation, for example it does not give away the fact that internally it uses ForeignPtrs. The Internal module now just exports really internal things including the representation, low level construction functions and utilities. The representation of lazy ByteStrings is moved into it's own Internal module which means we can call it ByteString without having to use a type alias. That should make hugs and/or nhc a bit happier. 7c75495 We no longer use instance of type synonym extension 8535e69 Change useAsCString so it does not use C malloc and free it was unnecessary e95ff44 Fix use of free finaliser in hGetContents The memory was allocated with mallocBytes so it must be freed with free or finalizerFree from the Foreign.Marshal.Alloc module. There is no guarantee that this is the same as the C free function. 148248e Eliminate newForeignFreePtr just inline its only use. 452cb77 No longer need to ffi-import C's malloc and free 488cd64 Use the (re|m)allocBytes rather than (re|m)allocArray functions It's simpler and more direct, we are working with bytes here, not arrays. And remove unused imports. 39a6287 Remove byteswap function It should not have been added in the first place. It's a fine function to have but not in the basic ByteString module which we should try and limit to the list api. 8df5fa4 Implement intersperse for lazy bytestring a6b8131 Remove unnecessary import 38ef212 update some todos 525fa2d Rename join to intercalate to match the standard Data.List And implement Lazy.Char8 version of intersperse 5c9dfd6 Don't include undocumented functions into haddoc docs Use the #prune haddock module annotation. Move 'join' in export list to a section with no header so we don't get an empty section where join used to be. b0eb4b7 Move some lazy ByteString internals into the .Lazy.Internal module This therefore exposes them in case people need them (eg binary, zlib). It now exports the chunk size constants and the LPS data type invariant and data abstraction functions. fcbaaf1 Add Data.ByteString.Fusion to the cabal file 8491513 Update copyright holders and add more metadata to .cabal file f247de8 Sort really does need allocaArray not allocaBytes Since it's an array of CSize not Word Since it's an array of CSize not Word8. Fixes segfault. 13fb652 Fix Lazy.lines "foo\n\nbar" e650399 Add a dep on array 2ebc807 Add a prologue.txt 5ff00c9 Fix inlining of intercalate join was just the deprecated alias for the new intercalate df60977 Add isInfixOf as an alias of isSubstringOf For api compatability with Data.List 16c1b07 Update the tests to work with module reorganisation 84a4642 Add Lazy.mapAccumR and reimplement mapAccumL including tests ec17c23 Implement Lazy.groupBy Seems to pass the QC test. 8dc8815 Rarange modules in .cabal file Hide the .Fusion module so we can change it later without changing the public api. Also, install the .h file. 813c510 Few updates to the README e92a7d4 Remove hacks that are no longer necessary The simplifier no longer discards these I think. a12fd51 Add commented out exports for functions we're missing And change the formatting of some exports and docs of exported bits. 2c2aba4 Add partition for strict and lazy Uses a simple implementation, we can optimise later. Getting the api addition in now is the priority. c8bf2c5 -Wall fix: don't import unsed thing bf60698 Export isInfixOf, alias for isSubstringOf e6fb272 Add Lazy.hPutStr as compatibility alias for hPut To match api of strict module. 7236250 Add naive implementations of Lazy.unzip and isSuffixOf 6efaafd Don't run the testsuite on commit, as it doesn't work 80e45a1 Move the fpstring.h to an include directory. a769b71 spell nhc98-options correctly 3c38c39 Remove reference in docs to non-existant function tokens 130906e Remove one indirection in the representation of lazy ByteString Instead of: newtype ByteString = LPS [S.ByteString] we have: data ByteString = Empty | Chunk {-# UNPACK #-} !S.ByteString ByteString That is, the strict ByteString element is unpacked into the Chunk constructor so it's now just one pointer to get to the data rather than having to look up the S.ByteString cons element and then follow the pointer to the data. Combined with SpecConstr we should be able to get some good speed improvements. 964d87d fix for Hugs: import internal newForeignPtr_ 7a0ab06 Export Fusion module, just for the sake of the testsuite 9484264 TAG ghc-6.8 branched 2007-09-03 e8e0d20 Add a boring file 1a2c3a8 Make it build with ghc-6.4.2 c128e41 Use new style syntax in .cabal file and use configurations for ghc-6.4.2 We previously had a comment saying what to change to get it to build with older ghc versions. Now we can do it automatically with configurations. ab51141 Haddock section header fixes, spelling, and trivial whitespace bits Section names and content should be more consistent between the modules now. dcadcc6 Export isInfixOf from Data.ByteString.Char8 It got added to Data.ByteString as an alias for isSubstringOf because isInfixOf got added to Data.List b8a9bbe Note that the ByteString searching api is about to be replaced So add a deprecated note to that effect to encourage people not to use them. Besides, the current implementation is slower than a naive search. 5acb5d8 extra , at end of line not accepted by the head 6158acb Comment out Cabal version check This was causing the build to fail as Cabal didn't know its own version number. d5e1bc6 bytestring head depends on array c08c2d5 Make it build with ghc-6.4 and 6.6 The patch cannot be pushed to ghc-6.8's bytestring branch until ghc bootstraps Cabal correctly, otherwise it trips up over the "cabal-version: >=1.2" field. 08a3d3b typo in doc fdb9234 Documentation only: haddock the arguments and return values of fromForeignPtr and toForeignPtr. e2e9881 bump version number. import flags from ndp project 5150cfc update QC properties for 6.8 5f1ecc0 fix building of testsuite 8ee6c71 move countOccurences out of .Internal 6623251 clean up some internals (docs, inlining) 2f9c786 don't test unpack stuff 843ca60 Disable old array fusion mechanisms, was messing with the simplifier. Big perf improvements to lazy map/filter/fold c1d0766 no api changes, just perf improvments 35ad399 keep haddock happy bc8c204 update small test programs decda6f add category 593dc8c add isSpaceChar8, a good bit faster in tight inner loops 5f59e92 For lazy IO operations, be sure to hClose the resource on EOF 2d2432c new email address be6a669 add test for lazy hclose working ce7ac3c Remember to always hClose when doing a strict hGetContents. Avoids resource leaks. fe0175e Don't hClose on getN functions -- they're not expected to read the whole file anyway 6af5098 complete test for resource leaks in getContents/readFile on both types 83a7917 bump version f8d1f9e note that Lazy.lines is too strict, and sketch lazy imlementation 62bfccd instance IsString for strict and lazy bytestrings. Use -XOverloadedStrings 0daf1ef fix laziness issue with Lazy.lines 7cfe53f bump version eaf7ba1 todo, find the memcmp length threshodl 26af6ea typo in doc. spotted by Johan Tibell 296754b Remove pessimistic INLINE on compareBytes. 5x speedup for some Ord-heavy tests d9f07e5 some tests on Ord speed 419ed24 bump version bde5b1b Documentations typos (filterByte instead of filterChar). e3c9505 Use unsafeDupablePerformIO as a cheaper unsafePerformIO, fixes stack overflow issues in stack squeezing cases 136021e clean up some things 4a5e842 respect warnings 2fe2097 portably use unsafeDupablePerformIO 075673a erroneos inline [1] on Char8.dropWhile 17a1e67 Add rewrite rule for Char8, matching the Word8 one, specialising break (==x) 5c1f5a3 more tests b1e981f remove deprecated 'join' -- people should have transitioned to intercalate in the past 12 months c00c83d Document IsString ByteString, and how to enable it 96dec13 dead code ed211e5 standardise rules firing with prefix "ByteString" bfef7b5 standardise rule names with "ByteString" prefix f266cc4 tweaks 7ae1eca normalise rewrite rule names 5f1827a document second argument of hGet 4a3478c note how to run testsuite with hugs fa42f18 bump version number 95dfe74 use appropriate -X flags e4ba7c1 ghc uses -XUnliftedFFITypes -XMagicHash -XUnboxedTuples -XDeriveDataTypeable 54ceef1 reuse internal invariant test 03b25ab coverage for Monoid instance a02a52d Use -fno-ignore-asserts when testing 07949b7 improve performance of findSubstrings on small strings 6410a7f more test coverage 40de93b actually fail if tests don't pass b7bc41b return failures c056923 use "ByteString" prefix for rules d4ab449 comments 530170a add cheaper hpc test target df0d550 require Instances 04e5992 no longer depend on array b385a04 tweaks 0f032f4 more tests fe9ca2c faster findSubstrings a65029c Add breakSubstring, split a bytestring on another bytestring. More idiomatic approach than findSubstring 4992455 properties for breakSubstring eedb41a tweak makefile 4a3a75c better clean target c7be0e8 More coverage 1ad58ab tweaks dc23b18 More testing. 80% of bytestring is now tested with QuickCheck 8084d08 normalise rule names 3484b9c more testing 7a64776 typos in comment 513458a add a cunning test for packMallocCString 38fb6ad Remove obscure filter (==) rewrite rule ef59f64 Use -fglasgow-exts to re-enable rewrite rules 1a2bf6d more QuickCheck properties, 88% covered now 319d9fd pointless filter rule c189ff3 some more tests 7700999 tune deprecation string eb346ed more tests 530b8dc Remove old fusion mechanism. Data.ByteString.Fusion is a place holder for streams now. 7c2790e fix warnings 97baa03 Add properties for rewrite rules, compiled sans -fhpc 345f3ef extra-source-files c84adbf Point to HPC coverage data d5548fe make hackage happy 9d2cccf more aggressive inlining on lazy bytestring readInt. Performance wins for sum-file 3ef2a98 clean up flags. building on 6.9 1048c66 notes, and undo -fcpr-off 46e21e3 typo in comment d16cdb7 clarify comments on hGet and EOF 09229fa Only a minor version bump cbc3a57 stupid ghc-prim 56e297e Drop unrecognised and unnecessary pragma fdcd243 Build with both base-3 and 4 640608a Drop -fglasgow-exts, use LANGUAGE pragmas fc9b7c6 Whitespace changes to the package description 631090a Bump version to 0.9.1.3 6fc64f5 fix import of Control.Exception for nhc98 a76f436 Drop dependency on syb with base 4 4b60cb1 Bump version to 0.9.1.4 f476915 Import fix for nhc98 f75b4c3 avoid import renaming errors in nhc98 c1e10f7 Make everything build with ghc-6.6 and 6.4 No code changes, just cpp for new LANGUAGE pragmas and not using a RULE with a funky LHS for ghc-6.4 which didn't allow it. d35456d Add TODO item to eliminate -fno-warn-orphans Orphan instances in libraries are not a good thing. b63d692 Fix strictness bugs in readInt and readInteger. 83b1d54 Add a test for the laziness of readInt and readInteger over lazy ByteStrings 265c4c6 bump versoin 434be9b Use comma separated lists in the LANGUAGE pragmas Haddock complains. 9ad8269 Improve the top-level documentation for the Unsafe and Internal modules Clarify the purpose and properties of the functions in the two modules. In particular try to disuade people from using the Internal functions unnecessarily. ac67540 Make docs for fromForeignPtr point to suitable public alternatives 4b1b473 Fix docs for unsafePackAddressLen, it doesn't need null-termination 28ecbeb Hide the .Internal modules in the haddock docs This should stop users accidentally using the semi-public modules while still leaving them available for extension packages. Also means that references to 'ByteString' go to a sensible place rather than the .Internal modules. 579e862 Fix some "warn-unused-do-bind" warnings where we want to ignore the value 8732db3 Remove INLINE pragmas on recursive functions Merge of patch from ghc's fork: Fri Dec 5 17:04:52 GMT 2008 simonpj at microsoft.com * Remove INLINE pragmas on recursive functions 4d97daa Fix "cabal check" warnings Merge of patch from ghc's fork: Tue Aug 11 22:58:58 BST 2009 Ian Lynagh * Fix "Cabal check" warnings 586ea72 Update for new IO library Merge of patch from ghc's fork: Thu Jun 11 15:09:37 BST 2009 Simon Marlow * Update for new IO library 719c21d Fix import warnings Patches merged from ghc's fork: Tue Jul 7 12:58:17 BST 2009 Ian Lynagh * Remove unused imports 40c5f36 Clean up the language extension pragmas We cannot actually specify them correctly, see ghc ticket #3457. We can at least simplify things and make it clear it does not work, rather than having misleading code that looks like it might work. e9fc821 Update "tested-with" list It builds with ghc-6.4 through to 6.11 (23/08/09) It builds with no warnings with ghc 6.8, 6.10 and 6.11. 8bd0a05 Fix elemIndices and split They were using inlinePerformIO to lazily delay IO actions within the scope of a withForeignPtr. Thus the ptr was still in use after the ForeignPtr went out of scope. This lead to dangling pointers, incorrect results and segfaults. Nasty. See ghc tickets #3486 and #3487. Audited the rest of the code base for the same anit-pattern. Thanks to nwn and people on the haskell-jp mailing list for reporting the bug with nice test cases and also to Ian, Bertram and Don for diagnosing the source of the problem. 1bcfb05 Check for negative lengths in hGet and hGetNonBlocking See ghc ticket #3514 8b49490 Check for negative lengths in packCStringLen 8de83ec Update copyright dates a97d5e6 Use Setup.hs like everyone else does baf0c73 Drop the stability field from the .cabal file It is pretty meaningless. It also said "provisional" which isn't true. 0d5abdf Fix warnings with ghc-6.12 And check and update tested-with list. It really does build with Cabal-1.2.3.0 and with ghc-6.4 through 6.12. 7526f75 Remove redundant specialise pragmas GHC HEAD will now warn about these. cbb71b4 Make it compile with non-ghc. 73b0bef hGetContents: use hGet instead of hGetNonBlocking + hWaitForInput + hIsEOF ae78a19 update docs for hGet, hGetNonBlocking 6e67a2b Fix up import warnings d12e43d Bump version to 0.9.1.6 31673d5 bump version to 0.9.1.7 72b654e ROLLBACK: hGetContents: use hGet instead of hGetNonBlocking + hWaitForInput + hIsEOF 74492ea ROLLBACK partly: update docs for hGet, hGetNonBlocking 05ebb50 Fix for SPJs new typechecking system A local value was being generalised to Ptr a, and used at type Ptr Word8 and also at type Ptr CChar. SPJs new type checker prefers not to generalise local bindings such as this. This instance is also a bit wierd from an engineering point of view. The code is now more explicit that we are using a pointer at two different types, by using a castPtr, which is the same as the way we handle other CString cases. 2b4485b Add a note to the docs for hGetContents(N) about using hSetBinaryMode See GHC bug #3808 d55dfd6 Bump version number to 0.9.1.8 e2e94a9 add Data.ByteString.hGetSome; use it in Data.ByteString.Lazy.hGetContents See GHC ticket #3808 e9bba92 Fix syntax errors in one branch of an #ifdef 1d0b973 Make it build again for nhc98. 469dd6d Add an explicit Data.String import list to fix build with GHC 7.2 38eca6f Fix imports for older GHC versions c65a5d7 Bump version number to 0.9.1.9 2f0e605 Make is build with nhc98. fb2a76e Bump version number to 0.9.1.10 15c5ae7 Use explicit import list for GHC.IO to avoid build failure 6cef919 Add hPutNonBlocking Based originally on a patch by David Fox Fixes ghc ticket #1070. Also update the documentation for hGetNonBlocking dff7b69 Export putStrLn and hPutStrLn from D.B.Lazy.Char8 and deprecate both functions in the non-Char8 modules. Functions that rely on ASCII encodings belong in the Char8 modules. 02aee0e Bump minor version due to API additions a95da63 Drop support for ghc-6.4 and 6.6 151c1af Update maintainers' email addresses efdca75 Update the test suite to QC2 and add a tests-suite stanza to the cabal file QC2 uses a rather different instance for Arbitrary Int which uses much bigger numbers than QC1 used. Some properties have had to be updated to use a smaller int range or they would take nearly forever to run. 9c7df37 Remove some old done TODO items d15a7ed Remove old GHC flag from Cabal file 4af4f62 Use Safe Haskell if GHC >= 7.2 385c93c Follow change to FFI decls: Import constructors of newtypes a73a711 Specify sensible fixities for cons and snoc As suggested by Yitzchak Gale. ff5b7ca Throw exception in IO for functions in IO Tracked down by Gershom Bazerman 96eda1d Add NFData instances for strict and lazy ByteStrings 7af3c56 Update cabal package metadata Remove old homepage, add source repo and bug report addresses. 59648db Fix test-suite and get rid of some warnings Based on a patch by Bas van Dijk 88f65a7 Remove unused fusion module a625b69 Add new internal list pack and unpack functions Use them for the Show and Read instances. They should also be a tad better in terms of speed and memory use. 8ea65cb Add a proper Show and Read instance for lazy bytestrings Previous one was derived which was silly. 18cec43 Add proper Data class instances that actually contain the data. Same style as instances for Data.Text. 01374ce Move the IsString instance so it is not an orphan c914a5f Drop unnecessary -funbox-strict-fields and set -fspec-constr-count We use the UNPACK pragma explicitly in the couple places where we use strict fields. c25779d Use the new {un,}pack{Bytes,Chars} functions and simplify We had a whole variety of odd pack/unpack functions. The nice thing is that with modern ghc we can use simpler implementations and get as good or better code than the old ones. d8b0a5d Move Eq, Ord, Monoid instances to eliminate orphans ae5086b Add BangPatterns extension 3c74db3 Add tests for groupBy Note that it fails for Lazy.groupBy due to a chunk boundary bug. 8ae0cea Include non-0 offset in instance Arbitrary Strict.ByteString And fix a test that breaks. bdfe39c Add more extensive tests for the various new pack and unpack functions 02aecf0 Clean up a few minor things in the test properties f51cb87 Fix implementation of Lazy.groupBy 442fe00 CPP-conditional LANGUAGE pragmas now work since ghc-7.0.x 6d6e732 Fix warning about C FFI types 35db5c4 Fix for ghc-6.8 / base-3 77af820 Update package description and tested-with list Liberally borrowed the style of description from the text package. 464cdfa A few minor doc improvements 5b17318 Update module metadata and copyright info 52ae9e1 Bump version to 0.10.0.0 Some minor API changes and a number of extensions 7c20c22 Fix documentation of complexity of toChunks 77e1df6 Add conversion functions between lazy and (single) strict ByteStrings API proposal and initial patch by Herbert Valerio Riedel http://article.gmane.org/gmane.comp.lang.haskell.libraries/16444 More or less unanimous support. 2accd98 Also export foldrChunks and foldlChunks Along with fromStrict and toStrict we now match the Text API in this area. e0f62b4 Added tests for toStrict and fromStrict 6e52436 Add new Builder monoid by Simon Meier The design of strict and lazy ByteStrings makes concatenation expensive. A builder monoid lets us efficiently build bytestrings by sticking bits together in an ad-hoc way. For example by pretty-printing or serialising. This is as opposed to a uniform approach using unfoldr. b33c352 Update docs for chunk size constants 8112f6c Add the test suite for the builder monoid Again, this is Simon Meier's code 3185c3b Make the builder test suite into a cabal test-suite The advantage is it makes it easier to run automatically. The disadvantage is we cannot use the nice test-framework package since cabal then thinks we've got a circular dependency since test-framework indirectly depends on bytestring. This will be solvable in future with encapsulated package dependencies, but util then we use a minimal implementation of the bit of the test-framework that we're using. c8e7960 Convert existing main test suite over to the minimal TestFramework code This will make it easier to switch to the test-framework package later. e9cb88f Add missing extension fe87271 Add Simon's builder benchmark suite and add to .cabal file Makes use of cabal's new support for benchmarks 159ae22 Fix a few test failures due to incorrect Int64 -> Int conversion Switch it around so we only promote Int -> Int64. 7efb416 port additional work on bytestring builder c59520d Do not expose the BasicEncoding and other internals for this release We are being conservative here. There is useful functionality that we will want to expose somehow eventually, including the fixed and bounded size encodings for maximum speed of short encodings, plus the ability to do things like size-prefixed runs of data. However we will give ourselves some time to let this stuff settle down and a bit longer to think about the best way to support the more advanced & low-level bits. 0847231 Fix building with ghc-7.3 and hopefully 7.4.x also Based on a patch contributed by Herbert Valerio Riedel. Also fixes warnings for ghc-7.2. 523c926 Add implementation of builder internal hPut for old or non-ghc Handle The current hPut is specific to newer GHC with the new Unicode Handle stuff. Provide an implementation for older ghc and non-ghc compilers. 933e86f Make the testHandlePutBuilder conditional and add char8 version The testHandlePutBuilder does not apply to older ghc with the pre-Unicode Handles. Extra char8 test covers old ghc and should work with new too. febf5d2 Fixes for ghc-6.10 b30ac17 Fix an issue with char/binary Handle write ordering with ghc-6.12 For 6.12 it needs an extra flushWriteBuffer. e0cfcd6 Fix some more import warnings 6eb0d62 Allow using older versions of the random package f54a935 Move __hscore_memcpy_src_off from base into include/fpstring.h 1b7baf1 Add .gitignore file for GHC build. aa31ed1 Add unsafePackMallocCStringLen f13d7b2 Add a NOINLINE [1] for zipWith as it is matched in a RULE GHC correctly warns that RULES cannot reliably match on functions that get inlined too early. Spotted by Paolo Capriotti. 5d6b262 Implemented unsnoc, unsafeInit and unsafeLast 89d58ea Fix property in the documentation for unfoldrN Spotted by Dan Burton 97c2717 Fix implementation of hPutNonBlocking for non-GHC Spotted by Dan Burton 0a324d0 Remove the old memcpy_ptr_baoff / memcpy alias 0480fa9 Export hGetSome from Data.ByteString.Char8 6ceb567 Use binary mode for Char8 file functions It doesn't actually make any difference these days, but it's better to be explicit and consistent about it here. 515cc0d Add internal functions createUptoN and createUptoN' Just tidies things up, not exported for now. b0ac129 Rename Builder modules Just Data.ByteString.Builder rather than Data.ByteString.Lazy.Builder And instead of BasicEncoding, just Prim, so Data.ByteString.Builder.Prim And use Extra instead of Extras f185f61 Simplify the implementation of unsnoc We have to do two traversals either way, no saving. 149e84a Rename Encoding types to Prim BoundedEncoding -> BoundedPrim FixedEncoding -> FixedPrim Also rename various operations to match 6a23bf6 Re-export all of the D.B.Builder.ASCII via top level D.B.Builder Decided it's better to have a few biger builder modules than to confuse users with loads of Builder.* modules. 5afd623 Expose the Data.ByteString.Builder.Prim module 9bb2713 Don't export builder prim testing support functions Now that it's an exposed API a76a0d7 Document for the Char8 I/O that it does not respect the newline mode though that this is considered a flaw and may be changed in future. 715a007 Go back to using short names for eitherB, condB combinators 6e45e78 Rename byteStringHexFixed to just byteStringHex The Fixed added nothing in this case, as the alternative would be silly. ff2fc80 Adjust documentation to talk about builder primitives rather than encodings 85ffe22 Minor doc addition, spelling fixes 7a8cf9c Add and export a lower level runBuilder function ad3436d Mention the Builder in the package description 9a9c417 Reluctantly expose the builder internal modules with a stiff warning 40bf048 Fix up the builder testsuite following recent renamings 5341838 Add a test for the new runBuilder stuff 07c8bfc Fix the Prim.Extra module for the sake of the tests It's not currentl built as part of the lib. 01d63d7 Export createUptoN and unsafeCreateUptoN afterall 7c4ee8f Fixes for ghc-7.6+ b4907e9 Drop support for ghc-6.10 and older in the .cabal file be3a97e Add all other-modules for the testsuites ac7cd50 Fix up the builder benchmarks for the recent builder renamings 070f840 Bump the version to 0.10.1.0 We've added some builder stuff. While 0.10.0.0 was never properly released, it could be a little confusing. So might as well bump. 3b87534 TAG 0.10.0.0 2409162 Retrospective 0.10.0.1 release ebb5579 TAG 0.10.0.1 c8a9cd6 Fix docs that use old showF/showB testing functions 2b24d79 Add a show instance for Builder just for convenience d243ad5 Add compat modules for builder under previous names We were not able to get our name changes included in time, so we have to be compatible with the 0.10.0.0 release. b3426cc Fix module names of builder test 49866c2 Bump version to 0.10.2.0 We're skipping the 0.10.1.0, that one can't be released as it is not compatible with what got released as 0.10.0.0 86df1f1 Fix a few incorrect uses of inlinePerformIO The incorrect use of inlinePerformIO resulted in multiple calls to mallocByteString being shared, and hence two different strings sharing the same memory. See http://hackage.haskell.org/trac/ghc/ticket/7270 d4d1983 Import unsafeDupablePerformIO 42b2de6 Re-implement the foldr and foldl functions and fix unpack fusion They were just wrong. The old foldr and foldl were doing strict accumulation when they should be lazy. 4a46cd1 Remove references to array fusion from the haddock docs We are not doing fusion and have not done so for ages and ages. 90ba5e2 Retrospective 0.10.0.2 release 8f35e60 Bump to current 0.10.3.x version 8d80968 Relax directory version constraint for builder testsuite 5adc3b9 TAG 0.10.0.2 859729a Fix a couple warnings 9c593a5 Ignore some more bits b20547a Point various URLs at github 89bda08 Add an IsString instance for Builder 4d24356 Add some ignore files for hg and git bf3ab9e Make tests build standalone 794c345 Fix the rewrite rule that optimizes packing of string literals 3a42bb1 Move D.B.Unsafe.unsafePackAddr to D.B.Internal efe48cd conditionally export D.B.Internal.unsafePackAddress 176a2e6 Fix build on GHC 7.0 bca8a9f Fix typos in docs of 'unsafePackAddress' 36e7e21 Fix typos in docs of 'unsafePackAddressLen' 8dd2efa Merge pull request #3 from meiersi/fix-typos-in-bytestring-internals 6cdd5dd Declare "digits" static b53e34a Fix export of module Data.ByteString.Builder.ASCII 2cafebf Implement (lazy) byteStringHexFixed c521a78 Add trustworthy pragmas to various safe builder modules and also make internal modules that expose ByteString constructors unsafe. b3bd784 Merge pull request #4 from scslab/trust 9e2814f Add a new ShortByteString type 3bb3b57 Add a builder primitive for ShortByteString 341a4c1 Unbreak the testsuite 5a86aa7 Add tests for the ShortByteString 25708d3 Port performance patches from private bytestring branch 4ac4be0 Use 'unsafeDupablePerformIO' instead of 'unsafePerformIO'. 49ffb60 Remove unnecessary code for chunked and variable-length encoding. 1a0ede3 Remove unneeded and/or commented-out code. 0a4b8dd Update builder tests and setup 'hpc'. a8b7b02 Finish renaming 'Bounded/FixedEncoding ~> Bounded/FixedPrim'. 53f91ca Make benchmarks compile and install again. 5890510 Compare integer encoding and bytestring insertion performance to blaze-builder. 92f19a5 Implement fast decimal integer encoding. 4720784 Use 'integer-simple' flag analogous to the 'text' library. eaa31e0 Make Data.ByteString.Short work on several ghc versions bf73032 Fix warnings for different GHC versions, including 7.8 4cc37e8 Remove dubious and unnecessary use of unsafeCoerce 2fdf6fc A few minor documentation tweaks and improvements 388303c Fix formatting typo in package description 8279aca Fix documentation of memory overheads 9c3ee74 Mention ShortByteString in the package description 0e147dd Move the other benchmarks into the separate cabal file f2b3258 Declare all extensions in .hs files 930a45b Bump version to 0.10.4.0 16772aa Tidy up a few more uses of extensions 033a686 Update tested-with list 6ad8c0d Don't declare the Trustworthy & Unsafe extensions in the .cabal file f0bac1d Apparently the Unsafe extension is only in ghc 7.4+ 9ea13b7 Add Travis-CI script a14c7ce Merge pull request #7 from hvr/master 80ff4a3 Rename and document inlinePerformIO to better reflect its behaviour 35b38d1 Fixed logic on CONLIKE hack. 8312989 Added Data.ByteString.Lazy.elemIndexEnd implementation 6093aef QuickCheck update from yesterday breaks the build e2d2352 Make travis builds work again 86ab496 Updated README 737332b Whoops, the .cabal file referred to the README 4c5855c Delete prologue.txt e97df17 Use S.foldl' on each chunk when strictly folding a lazy bytestring. 38540d3 Update .travis.yml description 6cf683d Add `FlexibleContexts` to fix compilation with GHC HEAD b916e3b Add GHC 7.8.3 to the Travis build-matrix f04e6f5 Constrain version of QuickCheck for compatibility 37b3017 Allow tests to use multiple cores ca80162 Ignore cabal sandbox fun 7f9acc4 Ignore Emacs files 1d3b3fd Protect against Int overflow in concat f097086 Drop trailing whitespace 2530b1c Rename sumP to checkedSum, and export it fbcc0af Fix Int overflow in Lazy.toStrict d61dffb Add regressions to test suite 09edcd8 Remove trailing comma from build-depends a832f99 Add new test-framework deps to TravisCI job ec1d7c7 Enable ScopedTypeVariables for tests/Regressions 3115296 Enable --show-details=always 1cc7cfb Disable regression test and turn on test-framework a562ab2 Use --show-details=streaming when available da4c7e9 Don't mention ISO-8859-1 in doc string for hGetContents d4798e9 Fix typos: rename funtion to function f37493f Merge pull request #31 from spl/patch-1 39de720 Merge pull request #21 from Lemmih/master 8faa3ab Merge pull request #25 from thomie/T5861 b060048 Fix haddock references to the ASCII module 9f0ee6b Fix documented complexity of unsafePackMallocCStringLen 5475757 Add a changelog 87aa6ee Improve the author credits 27d597b Bump to development version 0.10.5.0 30e135c Add support for `deepseq-1.4.0.0` 7a7602a Merge pull request #34 from hvr/pr-deepseq-14 a399cdd Update Safe Haskell tags on some modules cf3af8f Merge pull request #36 from dterei/more-safe-haskell eb4514e Merge pull request #12 from DaveCTurner/master cf29654 Replace explicit uses of seq with bang patterns ee2b178 We should not have exported breakByte, add a deprecation message 0bfef87 Add required CPP language pragmas c3457d7 Re-export isSuffixOf from D.B.L.Char8 fd022fe Replace STRICT macros with bang patterns 7670357 Add -fwarn-tabs 1a8ed9f Remove various old commented-out implementations ba75c25 Remove old fusion related stuff 8c3c7f3 Fix unfoldrN to call the predicate at most n times. 77cf05c Fix readFile for files with incorrectly reported file sizes cb85a53 Update changelog fa7e1cc Bump version to 0.10.6.0 8d512e1 hGet returns 'empty' not 'null' at EOF 9b63d5f Eta expand continuation of empty c1960a9 Merge pull request #40 from bgamari/builder-opt 08d5c3a Merge pull request #38 from DaveCTurner/patch-1 From git at git.haskell.org Fri Jan 23 22:44:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:07 +0000 (UTC) Subject: [commit: packages/containers] master: Remove unnecessary (Sized *) constraints. (5f519e6) Message-ID: <20150123224407.1228B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/5f519e641aa7099c0dc6b12d3df08920e8496d04 >--------------------------------------------------------------- commit 5f519e641aa7099c0dc6b12d3df08920e8496d04 Author: Milan Straka Date: Sat Jan 10 14:29:34 2015 +0100 Remove unnecessary (Sized *) constraints. >--------------------------------------------------------------- 5f519e641aa7099c0dc6b12d3df08920e8496d04 Data/Sequence.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/Data/Sequence.hs b/Data/Sequence.hs index b62b16a..491dd6d 100644 --- a/Data/Sequence.hs +++ b/Data/Sequence.hs @@ -640,13 +640,13 @@ deep :: Sized a => Digit a -> FingerTree (Node a) -> Digit a -> Finge deep pr m sf = Deep (size pr + size m + size sf) pr m sf {-# INLINE pullL #-} -pullL :: Sized a => Int -> FingerTree (Node a) -> Digit a -> FingerTree a +pullL :: Int -> FingerTree (Node a) -> Digit a -> FingerTree a pullL s m sf = case viewLTree m of Nothing2 -> digitToTree' s sf Just2 pr m' -> Deep s (nodeToDigit pr) m' sf {-# INLINE pullR #-} -pullR :: Sized a => Int -> Digit a -> FingerTree (Node a) -> FingerTree a +pullR :: Int -> Digit a -> FingerTree (Node a) -> FingerTree a pullR s pr m = case viewRTree m of Nothing2 -> digitToTree' s pr Just2 m' sf -> Deep s pr m' (nodeToDigit sf) @@ -1840,7 +1840,7 @@ initsNode (Node3 s a b c) = Node3 s (One a) (Two a b) (Three a b c) {-# SPECIALIZE tailsTree :: (FingerTree (Node a) -> Node b) -> FingerTree (Node a) -> FingerTree (Node b) #-} -- | Given a function to apply to tails of a tree, applies that function -- to every tail of the specified tree. -tailsTree :: (Sized a, Sized b) => (FingerTree a -> b) -> FingerTree a -> FingerTree b +tailsTree :: Sized a => (FingerTree a -> b) -> FingerTree a -> FingerTree b tailsTree _ Empty = Empty tailsTree f (Single x) = Single (f (Single x)) tailsTree f (Deep n pr m sf) = @@ -1855,7 +1855,7 @@ tailsTree f (Deep n pr m sf) = {-# SPECIALIZE initsTree :: (FingerTree (Node a) -> Node b) -> FingerTree (Node a) -> FingerTree (Node b) #-} -- | Given a function to apply to inits of a tree, applies that function -- to every init of the specified tree. -initsTree :: (Sized a, Sized b) => (FingerTree a -> b) -> FingerTree a -> FingerTree b +initsTree :: Sized a => (FingerTree a -> b) -> FingerTree a -> FingerTree b initsTree _ Empty = Empty initsTree f (Single x) = Single (f (Single x)) initsTree f (Deep n pr m sf) = From git at git.haskell.org Fri Jan 23 22:44:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:09 +0000 (UTC) Subject: [commit: packages/containers] master: Update .travis.yml per hvr's advice (d1c257a) Message-ID: <20150123224409.1A7193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/d1c257aa1385ebe6801a296e5b5decfb3b6e84f3 >--------------------------------------------------------------- commit d1c257aa1385ebe6801a296e5b5decfb3b6e84f3 Author: David Feuer Date: Wed Jan 14 22:47:19 2015 -0500 Update .travis.yml per hvr's advice We want it to be able to build with 7.10 and head. >--------------------------------------------------------------- d1c257aa1385ebe6801a296e5b5decfb3b6e84f3 .travis.yml | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index 8af3116..9505f69 100644 --- a/.travis.yml +++ b/.travis.yml @@ -7,12 +7,13 @@ env: # no package for earlier cabal versions in the PPA - GHCVER=7.4.2 CABALVER=1.16 - GHCVER=7.6.3 CABALVER=1.16 - - GHCVER=7.8.2 CABALVER=1.18 - - GHCVER=head CABALVER=1.20 + - GHCVER=7.8.4 CABALVER=1.18 + - GHCVER=7.10.1 CABALVER=1.22 + - GHCVER=head CABALVER=head matrix: allow_failures: - - env: GHCVER=head CABALVER=1.20 + - env: GHCVER=head CABALVER=head # Note: the distinction between `before_install` and `install` is not # important. From git at git.haskell.org Fri Jan 23 22:44:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:11 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #132 from treeowl/travis-update (25c3fee) Message-ID: <20150123224411.228A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/25c3fee44aa39b17ac3e74382591260c5edce1fa >--------------------------------------------------------------- commit 25c3fee44aa39b17ac3e74382591260c5edce1fa Merge: 5f519e6 d1c257a Author: Milan Straka Date: Thu Jan 15 12:26:15 2015 +0100 Merge pull request #132 from treeowl/travis-update Update .travis.yml per hvr's advice >--------------------------------------------------------------- 25c3fee44aa39b17ac3e74382591260c5edce1fa .travis.yml | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Jan 23 22:44:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:13 +0000 (UTC) Subject: [commit: packages/containers] master: Bump version number to 0.5.6.3 (fabde6b) Message-ID: <20150123224413.29D2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/fabde6b6381e459a49dee4ba1ac8b96848348542 >--------------------------------------------------------------- commit fabde6b6381e459a49dee4ba1ac8b96848348542 Author: Milan Straka Date: Thu Jan 15 12:41:01 2015 +0100 Bump version number to 0.5.6.3 >--------------------------------------------------------------- fabde6b6381e459a49dee4ba1ac8b96848348542 containers.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/containers.cabal b/containers.cabal index c5d7523..d7db653 100644 --- a/containers.cabal +++ b/containers.cabal @@ -1,5 +1,5 @@ name: containers -version: 0.5.6.2 +version: 0.5.6.3 license: BSD3 license-file: LICENSE maintainer: fox at ucw.cz From git at git.haskell.org Fri Jan 23 22:44:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:15 +0000 (UTC) Subject: [commit: packages/containers] master: Improve MIN_VERSION_base fall-back (3dddb04) Message-ID: <20150123224415.309683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/3dddb04bf514e37a87d7f8c5fd7ac58cda89d94f >--------------------------------------------------------------- commit 3dddb04bf514e37a87d7f8c5fd7ac58cda89d94f Author: David Feuer Date: Fri Jan 16 13:51:06 2015 -0500 Improve MIN_VERSION_base fall-back Guess the base library version based on `__GLASGOW_HASKELL__` when compiling without Cabal. >--------------------------------------------------------------- 3dddb04bf514e37a87d7f8c5fd7ac58cda89d94f include/containers.h | 27 +++++++++++++++++++++++---- 1 file changed, 23 insertions(+), 4 deletions(-) diff --git a/include/containers.h b/include/containers.h index ea895d1..b075799 100644 --- a/include/containers.h +++ b/include/containers.h @@ -51,11 +51,30 @@ /* * We use cabal-generated MIN_VERSION_base to adapt to changes of base. * Nevertheless, as a convenience, we also allow compiling without cabal by - * defining trivial MIN_VERSION_base if needed. + * defining an approximate MIN_VERSION_base if needed. The alternative version + * guesses the version of base using the version of GHC. This is usually + * sufficiently accurate. However, it completely ignores minor version numbers, + * and it makes the assumption that a pre-release version of GHC will ship with + * base libraries with the same version numbers as the final release. This + * assumption is violated in certain stages of GHC development, but in practice + * this should very rarely matter, and will not affect any released version. */ #ifndef MIN_VERSION_base -#define MIN_VERSION_base(major1,major2,minor) 0 +#if __GLASGOW_HASKELL__ >= 709 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=8))) +#elif __GLASGOW_HASKELL__ >= 707 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=7))) +#elif __GLASGOW_HASKELL__ >= 705 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=6))) +#elif __GLASGOW_HASKELL__ >= 703 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=5))) +#elif __GLASGOW_HASKELL__ >= 701 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=4))) +#elif __GLASGOW_HASKELL__ >= 700 +#define MIN_VERSION_base(major1,major2,minor) (((major1)<4)||(((major1) == 4)&&((major2)<=3))) +#else +#define MIN_VERSION_base(major1,major2,minor) (0) #endif +#endif // MIN_VERSION_base was not defined - -#endif +#endif // This file was already included From git at git.haskell.org Fri Jan 23 22:44:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:44:17 +0000 (UTC) Subject: [commit: packages/containers] master: Merge pull request #133 from treeowl/minversionbase (414bd0e) Message-ID: <20150123224417.380FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : master Link : http://git.haskell.org/packages/containers.git/commitdiff/414bd0e566a7025d24678bee556f610b1f5637f5 >--------------------------------------------------------------- commit 414bd0e566a7025d24678bee556f610b1f5637f5 Merge: fabde6b 3dddb04 Author: Milan Straka Date: Mon Jan 19 09:49:31 2015 +0100 Merge pull request #133 from treeowl/minversionbase Improve MIN_VERSION_base fall-back >--------------------------------------------------------------- 414bd0e566a7025d24678bee556f610b1f5637f5 include/containers.h | 27 +++++++++++++++++++++++---- 1 file changed, 23 insertions(+), 4 deletions(-) From git at git.haskell.org Fri Jan 23 22:48:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:11 +0000 (UTC) Subject: [commit: packages/pretty] branch 'typeclass-pretty' created Message-ID: <20150123224811.263633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty New branch : typeclass-pretty Referencing: b524d4c54213093270780388ea3bb50943a72f12 From git at git.haskell.org Fri Jan 23 22:48:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:13 +0000 (UTC) Subject: [commit: packages/pretty] branch 'moretests' created Message-ID: <20150123224813.2696A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty New branch : moretests Referencing: d45b1be45b3e6ec982f1e8b0fe556d3650ee2e60 From git at git.haskell.org Fri Jan 23 22:48:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:15 +0000 (UTC) Subject: [commit: packages/pretty] branch 'large_docs' created Message-ID: <20150123224815.270F23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty New branch : large_docs Referencing: b0364100bf58126dfe34715843102b27850d8f36 From git at git.haskell.org Fri Jan 23 22:48:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:17 +0000 (UTC) Subject: [commit: packages/pretty] branch 'next' created Message-ID: <20150123224817.282D93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty New branch : next Referencing: 1e3c792a54777c95be6d243570cf3ae248d16d68 From git at git.haskell.org Fri Jan 23 22:48:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:19 +0000 (UTC) Subject: [commit: packages/pretty] branch 'next2' created Message-ID: <20150123224819.292BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty New branch : next2 Referencing: 4d280b754435471eab4eac7ef6154f6fcadaf0c5 From git at git.haskell.org Fri Jan 23 22:48:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:21 +0000 (UTC) Subject: [commit: packages/pretty] branch 'new-pretty' created Message-ID: <20150123224821.2AC233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty New branch : new-pretty Referencing: b524d4c54213093270780388ea3bb50943a72f12 From git at git.haskell.org Fri Jan 23 22:48:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:23 +0000 (UTC) Subject: [commit: packages/pretty] branch 'ghc-head' deleted Message-ID: <20150123224823.2AE5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty Deleted branch: ghc-head From git at git.haskell.org Fri Jan 23 22:48:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:25 +0000 (UTC) Subject: [commit: packages/pretty] tag 'pretty-1.1.2.0-release' created Message-ID: <20150123224825.2C67D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty New tag : pretty-1.1.2.0-release Referencing: ce110db5639ed534341600f5ff48b42a36cfeb0c From git at git.haskell.org Fri Jan 23 22:48:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:27 +0000 (UTC) Subject: [commit: packages/pretty] new-pretty, typeclass-pretty: Update to pretty (9fc5ae3) Message-ID: <20150123224827.39ADE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: new-pretty,typeclass-pretty Link : http://git.haskell.org/packages/pretty.git/commitdiff/9fc5ae3cb9624bf32909870aa97a375fe9d22d1a >--------------------------------------------------------------- commit 9fc5ae3cb9624bf32909870aa97a375fe9d22d1a Author: David Terei Date: Tue Aug 23 18:38:35 2011 -0700 Update to pretty >--------------------------------------------------------------- 9fc5ae3cb9624bf32909870aa97a375fe9d22d1a Bench1.hs | 54 ++ CHANGELOG | 157 +++++ README | 4 + Text/PrettyPrint/Core.hs | 865 ++++++++++++++++++++++++++ Text/PrettyPrint/{HughesPJ.hs => Internal.hs} | 678 ++++++++------------ Text/PrettyPrint2.hs | 129 ++++ pretty.cabal | 4 + 7 files changed, 1473 insertions(+), 418 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9fc5ae3cb9624bf32909870aa97a375fe9d22d1a From git at git.haskell.org Fri Jan 23 22:48:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:29 +0000 (UTC) Subject: [commit: packages/pretty] new-pretty, typeclass-pretty: Some changes to Bench1 (0e91ce8) Message-ID: <20150123224829.42C483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: new-pretty,typeclass-pretty Link : http://git.haskell.org/packages/pretty.git/commitdiff/0e91ce85dae1724d8a6179d355e5dfd25cabb7e4 >--------------------------------------------------------------- commit 0e91ce85dae1724d8a6179d355e5dfd25cabb7e4 Author: David Terei Date: Wed Aug 24 15:10:21 2011 -0700 Some changes to Bench1 >--------------------------------------------------------------- 0e91ce85dae1724d8a6179d355e5dfd25cabb7e4 Bench1.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/Bench1.hs b/Bench1.hs index 09a1d14..c3a0661 100644 --- a/Bench1.hs +++ b/Bench1.hs @@ -1,8 +1,7 @@ module Main where --- import Text.PrettyPrint.HughesPJ -import Text.PrettyPrint2 -import Text.PrettyPrint.Internal +import Text.PrettyPrint.HughesPJ +-- import Pretty stuff :: String -> String -> Double -> Rational -> Int -> Int -> Int -> Doc stuff s1 s2 d1 r1 i1 i2 i3 = @@ -29,15 +28,17 @@ doc2 = stuff "aDSAS ADS asdasdsa sdsda xx" "SDAB WEEAA" 1333.212 ((-4)/5) 31 301 doc3 :: Doc doc3 = stuff "ADsAs --____ aDS" "DasSdAB weEAA" 2533.21299 ((-4)/999) 39 399 60 +{- txt :: TextDetails -> String -> String txt (Chr c) s = c:s txt (Str s1) s2 = s1 ++ s2 -txt (PStr s1) s2 = s1 ++ s2 +-} main :: IO () main = do putStrLn "===================================================" putStrLn $ render doc1 +{- putStrLn "===================================================" putStrLn $ fullRender PageMode 1000 4 txt "" doc2 putStrLn "===================================================" @@ -49,6 +50,7 @@ main = do putStrLn "===================================================" putStrLn $ fullRender OneLineMode 1000 4 txt "" doc3 putStrLn "===================================================" +-} putStrLn $ render doc3 From git at git.haskell.org Fri Jan 23 22:48:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:31 +0000 (UTC) Subject: [commit: packages/pretty] new-pretty, typeclass-pretty: Big update to pretty to merge in the GHC pretty module. (fdb90b4) Message-ID: <20150123224831.4B5E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: new-pretty,typeclass-pretty Link : http://git.haskell.org/packages/pretty.git/commitdiff/fdb90b408a59f3c665a870d85b6ce76ada395d2a >--------------------------------------------------------------- commit fdb90b408a59f3c665a870d85b6ce76ada395d2a Author: David Terei Date: Wed Aug 24 16:41:21 2011 -0700 Big update to pretty to merge in the GHC pretty module. We now have a core library that uses a type class instead of a concrete data type to store the underlying strings, making pretty abstract on the string data type. >--------------------------------------------------------------- fdb90b408a59f3c665a870d85b6ce76ada395d2a Text/PrettyPrint.hs | 74 +++- Text/PrettyPrint/Core.hs | 11 +- Text/PrettyPrint/HughesPJ.hs | 12 +- Text/PrettyPrint/Internal.hs | 958 ------------------------------------------- Text/PrettyPrint2.hs | 129 ------ pretty.cabal | 11 +- 6 files changed, 91 insertions(+), 1104 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fdb90b408a59f3c665a870d85b6ce76ada395d2a From git at git.haskell.org Fri Jan 23 22:48:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:33 +0000 (UTC) Subject: [commit: packages/pretty] new-pretty, typeclass-pretty: Update changelog (b9eadc2) Message-ID: <20150123224833.508A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: new-pretty,typeclass-pretty Link : http://git.haskell.org/packages/pretty.git/commitdiff/b9eadc25156334b5bf254b8e7dc2fe1cb9e3894e >--------------------------------------------------------------- commit b9eadc25156334b5bf254b8e7dc2fe1cb9e3894e Author: David Terei Date: Wed Aug 24 19:00:59 2011 -0700 Update changelog >--------------------------------------------------------------- b9eadc25156334b5bf254b8e7dc2fe1cb9e3894e CHANGELOG | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/CHANGELOG b/CHANGELOG index df924fd..71dbc98 100644 --- a/CHANGELOG +++ b/CHANGELOG @@ -2,6 +2,18 @@ Pretty library change log. +========= Version 4.0, 24 August 2011 ========== + +* Big change to the structure of the library. Now we don't have a fixed + TextDetails data type for storing the various String types that we + support. Instead we have changed that to be a type class that just + provides a way to convert String and Chars to an arbitary type. This + arbitary type is now provided by the user of the library so that they + can implement support very easily for any String type they want. + + This new code lives in Text.PrettyPrint.Core and the Text.PrettyPrint + module uses it to implement the old API. The Text.PrettyPrint.HughesPJ + module has been left unchanged for a compatability module but deprecated. ========= Version 3.0, 28 May 1987 ========== From git at git.haskell.org Fri Jan 23 22:48:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:35 +0000 (UTC) Subject: [commit: packages/pretty] new-pretty, typeclass-pretty: Update DocBase name to DocText and use GADT syntax (8aced36) Message-ID: <20150123224835.5BA463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: new-pretty,typeclass-pretty Link : http://git.haskell.org/packages/pretty.git/commitdiff/8aced36d05e917b916de1f25018ca8ebd67bfadf >--------------------------------------------------------------- commit 8aced36d05e917b916de1f25018ca8ebd67bfadf Author: David Terei Date: Thu Aug 25 15:18:54 2011 -0700 Update DocBase name to DocText and use GADT syntax >--------------------------------------------------------------- 8aced36d05e917b916de1f25018ca8ebd67bfadf Text/PrettyPrint.hs | 2 +- Text/PrettyPrint/Core.hs | 193 ++++++++++++++++++++++++----------------------- 2 files changed, 101 insertions(+), 94 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8aced36d05e917b916de1f25018ca8ebd67bfadf From git at git.haskell.org Fri Jan 23 22:48:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:37 +0000 (UTC) Subject: [commit: packages/pretty] new-pretty, typeclass-pretty: Add in quickcheck test (b524d4c) Message-ID: <20150123224837.651DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: new-pretty,typeclass-pretty Link : http://git.haskell.org/packages/pretty.git/commitdiff/b524d4c54213093270780388ea3bb50943a72f12 >--------------------------------------------------------------- commit b524d4c54213093270780388ea3bb50943a72f12 Author: David Terei Date: Sat Sep 10 12:56:00 2011 -0700 Add in quickcheck test >--------------------------------------------------------------- b524d4c54213093270780388ea3bb50943a72f12 pretty.cabal | 11 + {Text => src/Text}/PrettyPrint.hs | 0 {Text => src/Text}/PrettyPrint/Core.hs | 0 {Text => src/Text}/PrettyPrint/HughesPJ.hs | 3 +- Bench1.hs => test/Bench1.hs | 0 test/BugSep.hs | 30 + test/PrettyTestVersion.hs | 10 + test/Test.hs | 1066 ++++++++++++++++++++++++++++ 8 files changed, 1119 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b524d4c54213093270780388ea3bb50943a72f12 From git at git.haskell.org Fri Jan 23 22:48:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:39 +0000 (UTC) Subject: [commit: packages/pretty] next: Tweak tests definition; no functional change (1e3c792) Message-ID: <20150123224839.6AEA93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : next Link : http://git.haskell.org/packages/pretty.git/commitdiff/1e3c792a54777c95be6d243570cf3ae248d16d68 >--------------------------------------------------------------- commit 1e3c792a54777c95be6d243570cf3ae248d16d68 Author: Ian Lynagh Date: Thu Feb 14 16:32:43 2013 +0000 Tweak tests definition; no functional change Signed-off-by: David Terei >--------------------------------------------------------------- 1e3c792a54777c95be6d243570cf3ae248d16d68 tests/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/all.T b/tests/all.T index 5189843..81e2c73 100644 --- a/tests/all.T +++ b/tests/all.T @@ -1,2 +1,2 @@ -test('pp1', compose(expect_broken(1062), only_ways(['normal'])), compile_and_run, ['']) +test('pp1', [expect_broken(1062), only_ways(['normal'])], compile_and_run, ['']) test('T3911', normal, compile_and_run, ['']) From git at git.haskell.org Fri Jan 23 22:48:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:41 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: Fix paper link. (2c41eb0) Message-ID: <20150123224841.6FB8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/2c41eb0e5eb9d883e0acee84c899477596500d6c >--------------------------------------------------------------- commit 2c41eb0e5eb9d883e0acee84c899477596500d6c Author: David Terei Date: Tue Nov 12 20:47:45 2013 -0800 Fix paper link. >--------------------------------------------------------------- 2c41eb0e5eb9d883e0acee84c899477596500d6c README.md | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/README.md b/README.md index b50a9d6..d7cbe49 100644 --- a/README.md +++ b/README.md @@ -5,9 +5,10 @@ way to easily print out text in a consistent format of your choosing. This is useful for compilers and related tools. It is based on the pretty-printer outlined in the paper 'The Design -of a Pretty-printing Library' in Advanced Functional Programming, -Johan Jeuring and Erik Meijer (eds), LNCS 925 - +of a Pretty-printing Library' by John Hughes in Advanced Functional +Programming, 1995. It can be found +[here](http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.38.8777). + ## Licensing From git at git.haskell.org Fri Jan 23 22:48:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:43 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: Add NFData and Eq instances (3e9c0ea) Message-ID: <20150123224843.759963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/3e9c0eab6adf4859fd62396111fd2676c95a4997 >--------------------------------------------------------------- commit 3e9c0eab6adf4859fd62396111fd2676c95a4997 Author: Ivan Lazar Miljenovic Date: Tue Jun 24 19:55:22 2014 +1000 Add NFData and Eq instances Eq instance is based via the default rendering in case of differences in how they were created. >--------------------------------------------------------------- 3e9c0eab6adf4859fd62396111fd2676c95a4997 pretty.cabal | 3 ++- src/Text/PrettyPrint/HughesPJ.hs | 24 ++++++++++++++++++++++-- 2 files changed, 24 insertions(+), 3 deletions(-) diff --git a/pretty.cabal b/pretty.cabal index 7714b73..7d71469 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -30,7 +30,8 @@ Library exposed-modules: Text.PrettyPrint Text.PrettyPrint.HughesPJ - build-depends: base >= 3 && < 5 + build-depends: base >= 3 && < 5, + deepseq >= 1.1 && < 1.4 extensions: CPP, BangPatterns ghc-options: -Wall -fwarn-tabs diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index 10de760..2a36f07 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -75,8 +75,10 @@ module Text.PrettyPrint.HughesPJ ( ) where #endif -import Data.Monoid ( Monoid(mempty, mappend) ) -import Data.String ( IsString(fromString) ) +import Control.DeepSeq ( NFData(rnf) ) +import Data.Function ( on ) +import Data.Monoid ( Monoid(mempty, mappend) ) +import Data.String ( IsString(fromString) ) -- --------------------------------------------------------------------------- -- The Doc calculus @@ -236,6 +238,24 @@ instance Show Doc where (ribbonsPerLine style) txtPrinter cont doc +instance Eq Doc where + (==) = (==) `on` render + +instance NFData Doc where + rnf Empty = () + rnf (NilAbove d) = rnf d + rnf (TextBeside td i d) = rnf td `seq` rnf i `seq` rnf d + rnf (Nest k d) = rnf k `seq` rnf d + rnf (Union ur ul) = rnf ur `seq` rnf ul + rnf NoDoc = () + rnf (Beside ld s rd) = rnf ld `seq` rnf s `seq` rnf rd + rnf (Above ud s ld) = rnf ud `seq` rnf s `seq` rnf ld + +instance NFData TextDetails where + rnf (Chr c) = rnf c + rnf (Str str) = rnf str + rnf (PStr str) = rnf str + -- --------------------------------------------------------------------------- -- Values and Predicates on GDocs and TextDetails From git at git.haskell.org Fri Jan 23 22:48:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:45 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: Merge pull request #13 from ivan-m/add_instances (3ca7e48) Message-ID: <20150123224845.7BA393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/3ca7e487dca7e23abff0641bca2e46d59a6ddca9 >--------------------------------------------------------------- commit 3ca7e487dca7e23abff0641bca2e46d59a6ddca9 Merge: 2c41eb0 3e9c0ea Author: David Terei Date: Sun Jun 29 19:09:09 2014 -0700 Merge pull request #13 from ivan-m/add_instances Add NFData and Eq instances >--------------------------------------------------------------- 3ca7e487dca7e23abff0641bca2e46d59a6ddca9 pretty.cabal | 3 ++- src/Text/PrettyPrint/HughesPJ.hs | 24 ++++++++++++++++++++++-- 2 files changed, 24 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Jan 23 22:48:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:47 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: add travis support (84edff6) Message-ID: <20150123224847.818AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/84edff6bc69b398bedab65701418e7cdd2a061e8 >--------------------------------------------------------------- commit 84edff6bc69b398bedab65701418e7cdd2a061e8 Author: David Terei Date: Tue Sep 16 23:47:03 2014 -0700 add travis support >--------------------------------------------------------------- 84edff6bc69b398bedab65701418e7cdd2a061e8 .travis.yml | 39 +++++++++++++++++++++++++++++++++++++++ 1 file changed, 39 insertions(+) diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..c4cdfd4 --- /dev/null +++ b/.travis.yml @@ -0,0 +1,39 @@ +env: + - GHCVER=7.4.1 + - GHCVER=7.4.2 + - GHCVER=7.6.1 + - GHCVER=7.6.2 + - GHCVER=7.6.3 + - GHCVER=7.8.1 + - GHCVER=7.8.2 + - GHCVER=7.8.3 + - GHCVER=head + +matrix: + allow_failures: + - env: GHCVER=head + +before_install: + - sudo add-apt-repository -y ppa:hvr/ghc + - sudo apt-get update + - sudo apt-get install cabal-install-1.18 ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:$PATH + +install: + - cabal-1.18 update + - ghc --version + +script: + - cabal-1.18 configure -v2 + - cabal-1.18 build + - cabal-1.18 check + - cabal-1.18 sdist + - export SRC_TGZ=$(cabal-1.18 info . | awk '{print $2 ".tar.gz";exit}') ; + cd dist/; + if [ -f "$SRC_TGZ" ]; then + cabal-1.18 install "$SRC_TGZ"; + else + echo "expected '$SRC_TGZ' not found"; + exit 1; + fi + From git at git.haskell.org Fri Jan 23 22:48:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:49 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: update travis config (59a1c1d) Message-ID: <20150123224849.8835B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/59a1c1dd38468235cf070057fc65d49092836467 >--------------------------------------------------------------- commit 59a1c1dd38468235cf070057fc65d49092836467 Author: David Terei Date: Mon Dec 8 23:04:55 2014 -0800 update travis config >--------------------------------------------------------------- 59a1c1dd38468235cf070057fc65d49092836467 .travis.yml | 43 ++++++++++++++++++++++--------------------- 1 file changed, 22 insertions(+), 21 deletions(-) diff --git a/.travis.yml b/.travis.yml index c4cdfd4..ff8b00f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,37 +1,38 @@ env: - - GHCVER=7.4.1 - - GHCVER=7.4.2 - - GHCVER=7.6.1 - - GHCVER=7.6.2 - - GHCVER=7.6.3 - - GHCVER=7.8.1 - - GHCVER=7.8.2 - - GHCVER=7.8.3 - - GHCVER=head + - CABALVER=1.16 GHCVER=7.4.1 + - CABALVER=1.16 GHCVER=7.4.2 + - CABALVER=1.16 GHCVER=7.6.1 + - CABALVER=1.16 GHCVER=7.6.2 + - CABALVER=1.16 GHCVER=7.6.3 + - CABALVER=1.18 GHCVER=7.8.1 + - CABALVER=1.18 GHCVER=7.8.2 + - CABALVER=1.18 GHCVER=7.8.3 + - CABALVER=head GHCVER=head matrix: allow_failures: - - env: GHCVER=head + - env: CABALVER=head GHCVER=head before_install: - - sudo add-apt-repository -y ppa:hvr/ghc - - sudo apt-get update - - sudo apt-get install cabal-install-1.18 ghc-$GHCVER - - export PATH=/opt/ghc/$GHCVER/bin:$PATH + - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH install: - - cabal-1.18 update + - cabal --version - ghc --version + - travis_retry cabal update script: - - cabal-1.18 configure -v2 - - cabal-1.18 build - - cabal-1.18 check - - cabal-1.18 sdist - - export SRC_TGZ=$(cabal-1.18 info . | awk '{print $2 ".tar.gz";exit}') ; + - cabal configure -v2 + - cabal build + - cabal check || [ "$CABALVER" == "1.16" ] + - cabal sdist + - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; if [ -f "$SRC_TGZ" ]; then - cabal-1.18 install "$SRC_TGZ"; + cabal install --force-reinstalls "$SRC_TGZ"; else echo "expected '$SRC_TGZ' not found"; exit 1; From git at git.haskell.org Fri Jan 23 22:48:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:51 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: update readme to include badges (2832850) Message-ID: <20150123224851.8DACE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/28328504503743331ae3dc3662f16fd34198144c >--------------------------------------------------------------- commit 28328504503743331ae3dc3662f16fd34198144c Author: David Terei Date: Mon Dec 8 23:05:05 2014 -0800 update readme to include badges >--------------------------------------------------------------- 28328504503743331ae3dc3662f16fd34198144c README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index d7cbe49..c66f266 100644 --- a/README.md +++ b/README.md @@ -1,5 +1,7 @@ # Pretty : A Haskell Pretty-printer library +[![Hackage version](https://img.shields.io/hackage/v/hlint.svg?style=flat)](https://hackage.haskell.org/package/pretty) [![Build Status](https://img.shields.io/travis/haskell/pretty.svg?style=flat)](https://travis-ci.org/haskell/pretty) + Pretty is a pretty-printing library, a set of API's that provides a way to easily print out text in a consistent format of your choosing. This is useful for compilers and related tools. From git at git.haskell.org Fri Jan 23 22:48:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:53 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: fixes to hackage badge in readme (334adf8) Message-ID: <20150123224853.93B993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/334adf809f40857897c40f9ab920cf065548c2d3 >--------------------------------------------------------------- commit 334adf809f40857897c40f9ab920cf065548c2d3 Author: David Terei Date: Thu Dec 11 19:49:40 2014 -0800 fixes to hackage badge in readme >--------------------------------------------------------------- 334adf809f40857897c40f9ab920cf065548c2d3 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index c66f266..2a4cb50 100644 --- a/README.md +++ b/README.md @@ -1,6 +1,6 @@ # Pretty : A Haskell Pretty-printer library -[![Hackage version](https://img.shields.io/hackage/v/hlint.svg?style=flat)](https://hackage.haskell.org/package/pretty) [![Build Status](https://img.shields.io/travis/haskell/pretty.svg?style=flat)](https://travis-ci.org/haskell/pretty) +[![Hackage version](https://img.shields.io/hackage/v/pretty.svg?style=flat)](https://hackage.haskell.org/package/pretty) [![Build Status](https://img.shields.io/travis/haskell/pretty.svg?style=flat)](https://travis-ci.org/haskell/pretty) Pretty is a pretty-printing library, a set of API's that provides a way to easily print out text in a consistent format of your choosing. From git at git.haskell.org Fri Jan 23 22:48:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:55 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: tweaks to travis ci (9799d77) Message-ID: <20150123224855.9A6C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/9799d771a4d3457955811cdaebe7b501f2c287b7 >--------------------------------------------------------------- commit 9799d771a4d3457955811cdaebe7b501f2c287b7 Author: David Terei Date: Wed Dec 17 02:06:29 2014 -0800 tweaks to travis ci >--------------------------------------------------------------- 9799d771a4d3457955811cdaebe7b501f2c287b7 .travis.yml | 19 +++++++++++-------- 1 file changed, 11 insertions(+), 8 deletions(-) diff --git a/.travis.yml b/.travis.yml index ff8b00f..8cb857c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,12 +1,14 @@ +language: haskell env: - - CABALVER=1.16 GHCVER=7.4.1 - - CABALVER=1.16 GHCVER=7.4.2 - - CABALVER=1.16 GHCVER=7.6.1 - - CABALVER=1.16 GHCVER=7.6.2 - - CABALVER=1.16 GHCVER=7.6.3 - - CABALVER=1.18 GHCVER=7.8.1 - - CABALVER=1.18 GHCVER=7.8.2 - - CABALVER=1.18 GHCVER=7.8.3 + - CABALVER=1.18 GHCVER=7.4.1 + - CABALVER=1.18 GHCVER=7.4.2 + - CABALVER=1.18 GHCVER=7.6.1 + - CABALVER=1.18 GHCVER=7.6.2 + - CABALVER=1.18 GHCVER=7.6.3 + - CABALVER=1.20 GHCVER=7.8.1 + - CABALVER=1.20 GHCVER=7.8.2 + - CABALVER=1.20 GHCVER=7.8.3 + - CABALVER=1.20 GHCVER=7.8.3 - CABALVER=head GHCVER=head matrix: @@ -25,6 +27,7 @@ install: - travis_retry cabal update script: + - cabal install --only-dependencies --enable-tests - cabal configure -v2 - cabal build - cabal check || [ "$CABALVER" == "1.16" ] From git at git.haskell.org Fri Jan 23 22:48:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:57 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: change doc wording for `ribbonsPerLine` (#14) (5c0f0fa) Message-ID: <20150123224857.A02853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/5c0f0fa4e59cc695541c90c5afff5c26272f9876 >--------------------------------------------------------------- commit 5c0f0fa4e59cc695541c90c5afff5c26272f9876 Author: David Terei Date: Wed Dec 17 02:06:52 2014 -0800 change doc wording for `ribbonsPerLine` (#14) >--------------------------------------------------------------- 5c0f0fa4e59cc695541c90c5afff5c26272f9876 src/Text/PrettyPrint/HughesPJ.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index 2a36f07..b13d665 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -806,7 +806,7 @@ oneLiner (Beside {}) = error "oneLiner Beside" data Style = Style { mode :: Mode -- ^ The rendering mode , lineLength :: Int -- ^ Length of line, in chars - , ribbonsPerLine :: Float -- ^ Ratio of ribbon length to line length + , ribbonsPerLine :: Float -- ^ Ratio of line length to ribbon length } -- | The default style (@mode=PageMode, lineLength=100, ribbonsPerLine=1.5@). From git at git.haskell.org Fri Jan 23 22:48:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:48:59 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: remove bounds on deepseq (fixes #15) (5e45854) Message-ID: <20150123224859.A5C343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/5e45854b4e34763463cbf13dd4aee7b69824a6da >--------------------------------------------------------------- commit 5e45854b4e34763463cbf13dd4aee7b69824a6da Author: David Terei Date: Sun Dec 21 23:03:26 2014 -0800 remove bounds on deepseq (fixes #15) >--------------------------------------------------------------- 5e45854b4e34763463cbf13dd4aee7b69824a6da pretty.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pretty.cabal b/pretty.cabal index 7d71469..64f1b83 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -31,7 +31,7 @@ Library Text.PrettyPrint Text.PrettyPrint.HughesPJ build-depends: base >= 3 && < 5, - deepseq >= 1.1 && < 1.4 + deepseq >= 1.1 extensions: CPP, BangPatterns ghc-options: -Wall -fwarn-tabs From git at git.haskell.org Fri Jan 23 22:49:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:01 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: Fix cabal build issue with test-suite (6190328) Message-ID: <20150123224901.AC2473A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/61903283f09598477b166194acf24c3afacd2f35 >--------------------------------------------------------------- commit 61903283f09598477b166194acf24c3afacd2f35 Author: David Terei Date: Sun Dec 21 23:16:50 2014 -0800 Fix cabal build issue with test-suite >--------------------------------------------------------------- 61903283f09598477b166194acf24c3afacd2f35 pretty.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/pretty.cabal b/pretty.cabal index 64f1b83..27e45db 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -40,6 +40,7 @@ Test-Suite test-pretty hs-source-dirs: tests src build-depends: base >= 3 && < 5, + deepseq >= 1.1, QuickCheck >= 2.5 && <3 main-is: Test.hs other-modules: From git at git.haskell.org Fri Jan 23 22:49:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:03 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: add cabal sandbox to gitignore (ab82211) Message-ID: <20150123224903.B1E1E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/ab822112ce06a2b0aef7088cd5c0c3b34e075869 >--------------------------------------------------------------- commit ab822112ce06a2b0aef7088cd5c0c3b34e075869 Author: David Terei Date: Sun Dec 21 23:17:22 2014 -0800 add cabal sandbox to gitignore >--------------------------------------------------------------- ab822112ce06a2b0aef7088cd5c0c3b34e075869 .gitignore | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.gitignore b/.gitignore index 1234c1a..0477e90 100644 --- a/.gitignore +++ b/.gitignore @@ -2,3 +2,5 @@ dist/ GNUmakefile dist-install ghc.mk +cabal.sandbox.config +.cabal-sandbox From git at git.haskell.org Fri Jan 23 22:49:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:05 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: Fixes to travis and have travis run test-suite (cbbd53a) Message-ID: <20150123224905.B806E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/cbbd53aaee7970ce5b866b668a3387cf1dec6ba3 >--------------------------------------------------------------- commit cbbd53aaee7970ce5b866b668a3387cf1dec6ba3 Author: David Terei Date: Sun Dec 21 23:17:24 2014 -0800 Fixes to travis and have travis run test-suite >--------------------------------------------------------------- cbbd53aaee7970ce5b866b668a3387cf1dec6ba3 .travis.yml | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 8cb857c..99aeeed 100644 --- a/.travis.yml +++ b/.travis.yml @@ -27,10 +27,12 @@ install: - travis_retry cabal update script: - - cabal install --only-dependencies --enable-tests - - cabal configure -v2 + - cabal install --only-dependencies + - cabal install QuickCheck >= 2.5 && <= 3 + - cabal configure -v2 --enable-tests - cabal build - cabal check || [ "$CABALVER" == "1.16" ] + - cabal test - cabal sdist - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; From git at git.haskell.org Fri Jan 23 22:49:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:07 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: add back in lost 1.1.1.2 release notes (cd1c995) Message-ID: <20150123224907.BD3503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/cd1c99535b5c56f9d3d7ecc8e9bfc952421dbee8 >--------------------------------------------------------------- commit cd1c99535b5c56f9d3d7ecc8e9bfc952421dbee8 Author: David Terei Date: Sun Dec 21 23:24:59 2014 -0800 add back in lost 1.1.1.2 release notes >--------------------------------------------------------------- cd1c99535b5c56f9d3d7ecc8e9bfc952421dbee8 CHANGELOG.md | 6 +++++- pretty.cabal | 2 +- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index e3cf06f..e496ccd 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,6 +1,10 @@ # Pretty library change log -## 1.1.1.1 +## 1.1.1.2 -- 18th August, 2014 + +* Add NFData and Eq instances (by Ivan Lazar Miljenovic). + +## 1.1.1.1 -- 27th October, 2013 * Update pretty cabal file and readme. * Fix tests to work with latest quickcheck. diff --git a/pretty.cabal b/pretty.cabal index 27e45db..22a99b8 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -1,5 +1,5 @@ name: pretty -version: 1.1.1.1 +version: 1.1.1.2 synopsis: Pretty-printing library description: This package contains a pretty-printing library, a set of API's From git at git.haskell.org Fri Jan 23 22:49:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:09 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: make 1.1.1.3 release (c59e1df) Message-ID: <20150123224909.C37F13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/c59e1df384b2bc7710c5efcb80a9341d172a7ff1 >--------------------------------------------------------------- commit c59e1df384b2bc7710c5efcb80a9341d172a7ff1 Author: David Terei Date: Sun Dec 21 23:25:29 2014 -0800 make 1.1.1.3 release >--------------------------------------------------------------- c59e1df384b2bc7710c5efcb80a9341d172a7ff1 CHANGELOG.md | 5 +++++ pretty.cabal | 2 +- 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index e496ccd..c41c2e1 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,5 +1,10 @@ # Pretty library change log +## 1.1.1.3 -- 21st December, 2014 + +* Remove upper bound on `deepseq` package to fix build issues with + latest GHC. + ## 1.1.1.2 -- 18th August, 2014 * Add NFData and Eq instances (by Ivan Lazar Miljenovic). diff --git a/pretty.cabal b/pretty.cabal index 22a99b8..7a7b2a5 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -1,5 +1,5 @@ name: pretty -version: 1.1.1.2 +version: 1.1.1.3 synopsis: Pretty-printing library description: This package contains a pretty-printing library, a set of API's From git at git.haskell.org Fri Jan 23 22:49:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:11 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: More fixes to travis ci (29792d6) Message-ID: <20150123224911.C8B573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/29792d65f1b95c35e1d012f6994193e93294f11f >--------------------------------------------------------------- commit 29792d65f1b95c35e1d012f6994193e93294f11f Author: David Terei Date: Sun Dec 21 23:30:56 2014 -0800 More fixes to travis ci >--------------------------------------------------------------- 29792d65f1b95c35e1d012f6994193e93294f11f .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 99aeeed..9179847 100644 --- a/.travis.yml +++ b/.travis.yml @@ -28,7 +28,7 @@ install: script: - cabal install --only-dependencies - - cabal install QuickCheck >= 2.5 && <= 3 + - cabal install "QuickCheck >= 2.5 && < 3" - cabal configure -v2 --enable-tests - cabal build - cabal check || [ "$CABALVER" == "1.16" ] From git at git.haskell.org Fri Jan 23 22:49:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:13 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: update readme to reflect use of branches in git (0e24600) Message-ID: <20150123224913.CE5753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/0e246004229f20e57661b3580471907dcdea14ad >--------------------------------------------------------------- commit 0e246004229f20e57661b3580471907dcdea14ad Author: David Terei Date: Mon Dec 22 00:05:40 2014 -0800 update readme to reflect use of branches in git >--------------------------------------------------------------- 0e246004229f20e57661b3580471907dcdea14ad README.md | 20 ++++++++------------ 1 file changed, 8 insertions(+), 12 deletions(-) diff --git a/README.md b/README.md index 2a4cb50..ae5c7b8 100644 --- a/README.md +++ b/README.md @@ -11,7 +11,6 @@ of a Pretty-printing Library' by John Hughes in Advanced Functional Programming, 1995. It can be found [here](http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.38.8777). - ## Licensing This library is BSD-licensed. @@ -19,23 +18,20 @@ This library is BSD-licensed. ## Building The library uses the Cabal build system, so building is simply a -matter of running +matter of running: ``` +cabal sandbox init +cabal install "QuickCheck >= 2.5 && < 3" +cabal install --only-dependencies cabal configure --enable-tests cabal build +cabal test ``` -## Branches - -Usually two branches are maintained for Pretty development: - - * master: This branch is generally kept in a stable state and is - where release are pulled and made from. The reason for this is GHC - includes the pretty library and tracks the master branch by default - so we don't want experimental code being pulled into GHC at times. - - * next: This branch is the general development branch. +We have to install `QuickCheck` manually as otherwise Cabal currently +throws an error due to the cyclic dependency between `pretty` and +`QuickCheck`. ## Get involved! From git at git.haskell.org Fri Jan 23 22:49:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:15 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: Remove incorrect 'version 4' entry from changelog (95bbc32) Message-ID: <20150123224915.D41FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/95bbc328d2ad46cf36260d97121288100c1b9798 >--------------------------------------------------------------- commit 95bbc328d2ad46cf36260d97121288100c1b9798 Author: David Terei Date: Mon Dec 22 00:11:09 2014 -0800 Remove incorrect 'version 4' entry from changelog Version 4 was an experiment that isn't present in pretty at this time. >--------------------------------------------------------------- 95bbc328d2ad46cf36260d97121288100c1b9798 CHANGELOG.md | 13 ------------- 1 file changed, 13 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index c41c2e1..2195744 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -14,19 +14,6 @@ * Update pretty cabal file and readme. * Fix tests to work with latest quickcheck. -## Version 4.0, 24 August 2011 - -* Big change to the structure of the library. Now we don't have a fixed - TextDetails data type for storing the various String types that we - support. Instead we have changed that to be a type class that just - provides a way to convert String and Chars to an arbitary type. This - arbitary type is now provided by the user of the library so that they - can implement support very easily for any String type they want. - - This new code lives in Text.PrettyPrint.Core and the Text.PrettyPrint - module uses it to implement the old API. The Text.PrettyPrint.HughesPJ - module has been left unchanged for a compatability module but deprecated. - ## Version 3.0, 28 May 1987 * Cured massive performance bug. If you write: From git at git.haskell.org Fri Jan 23 22:49:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:17 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: Update maintainer email in source code (14a0117) Message-ID: <20150123224917.DCB073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/14a01176769e055616bfb02ba83f264c1603fe60 >--------------------------------------------------------------- commit 14a01176769e055616bfb02ba83f264c1603fe60 Author: David Terei Date: Mon Dec 22 00:11:54 2014 -0800 Update maintainer email in source code >--------------------------------------------------------------- 14a01176769e055616bfb02ba83f264c1603fe60 src/Text/PrettyPrint.hs | 7 ++++--- src/Text/PrettyPrint/HughesPJ.hs | 2 +- 2 files changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Text/PrettyPrint.hs b/src/Text/PrettyPrint.hs index 15b3f93..0d6b6d4 100644 --- a/src/Text/PrettyPrint.hs +++ b/src/Text/PrettyPrint.hs @@ -7,12 +7,13 @@ -- Copyright : (c) The University of Glasgow 2001 -- License : BSD-style (see the file LICENSE) -- --- Maintainer : David Terei +-- Maintainer : David Terei -- Stability : stable -- Portability : portable -- --- The default interface to the pretty-printing library. Provides a collection --- of pretty printer combinators. +-- Provides a collection of pretty printer combinators, a set of API's +-- that provides a way to easily print out text in a consistent format +-- of your choosing. -- -- This module should be used as opposed to the "Text.PrettyPrint.HughesPJ" -- module. Both are equivalent though as this module simply re-exports the diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index b13d665..509720b 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -10,7 +10,7 @@ -- Copyright : (c) The University of Glasgow 2001 -- License : BSD-style (see the file LICENSE) -- --- Maintainer : David Terei +-- Maintainer : David Terei -- Stability : stable -- Portability : portable -- From git at git.haskell.org Fri Jan 23 22:49:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:19 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: Merge in prettyclass package as useful to have in core (a964141) Message-ID: <20150123224919.E36A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/a964141bc0b305e14131cb6c0b2db73cb056c1cb >--------------------------------------------------------------- commit a964141bc0b305e14131cb6c0b2db73cb056c1cb Author: David Terei Date: Wed Dec 24 15:30:33 2014 -0800 Merge in prettyclass package as useful to have in core >--------------------------------------------------------------- a964141bc0b305e14131cb6c0b2db73cb056c1cb pretty.cabal | 1 + src/Text/PrettyPrint/HughesPJClass.hs | 142 ++++++++++++++++++++++++++++++++++ 2 files changed, 143 insertions(+) diff --git a/pretty.cabal b/pretty.cabal index 7a7b2a5..47c1a8f 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -30,6 +30,7 @@ Library exposed-modules: Text.PrettyPrint Text.PrettyPrint.HughesPJ + Text.PrettyPrint.HughesPJClass build-depends: base >= 3 && < 5, deepseq >= 1.1 extensions: CPP, BangPatterns diff --git a/src/Text/PrettyPrint/HughesPJClass.hs b/src/Text/PrettyPrint/HughesPJClass.hs new file mode 100644 index 0000000..da1b474 --- /dev/null +++ b/src/Text/PrettyPrint/HughesPJClass.hs @@ -0,0 +1,142 @@ +#if __GLASGOW_HASKELL__ >= 701 +{-# LANGUAGE Safe #-} +#endif + +----------------------------------------------------------------------------- +-- | +-- Module : Text.PrettyPrint.HughesPJClass +-- Copyright : (c) Lennart Augustsson 2014 +-- License : BSD-style (see the file LICENSE) +-- +-- Maintainer : David Terei +-- Stability : stable +-- Portability : portable +-- +-- Pretty printing class, simlar to 'Show' but nicer looking. +-- +-- Note that the precedence level is a 'Rational' so there is an unlimited +-- number of levels. This module re-exports 'Text.PrettyPrint.HughesPJ'. +-- +----------------------------------------------------------------------------- + +module Text.PrettyPrint.HughesPJClass ( + -- * Pretty typeclass + Pretty(..), + + PrettyLevel(..), prettyNormal, + prettyShow, prettyParen, + + -- re-export HughesPJ + module Text.PrettyPrint.HughesPJ + ) where + +import Text.PrettyPrint.HughesPJ + +-- | Level of detail in the pretty printed output. +-- Level 0 is the least detail. +newtype PrettyLevel = PrettyLevel Int + deriving (Eq, Ord, Show) + +-- | The "normal" (Level 0) of detail. +prettyNormal :: PrettyLevel +prettyNormal = PrettyLevel 0 + +-- | Pretty printing class. The precedence level is used in a similar way as in +-- the 'Show' class. Minimal complete definition is either 'pPrintPrec' or +-- 'pPrint'. +class Pretty a where + pPrintPrec :: PrettyLevel -> Rational -> a -> Doc + pPrintPrec _ _ = pPrint + + pPrint :: a -> Doc + pPrint = pPrintPrec prettyNormal 0 + + pPrintList :: PrettyLevel -> [a] -> Doc + pPrintList l = brackets . fsep . punctuate comma . map (pPrintPrec l 0) + +-- | Pretty print a value with the 'prettyNormal' level. +prettyShow :: (Pretty a) => a -> String +prettyShow = render . pPrint + +pPrint0 :: (Pretty a) => PrettyLevel -> a -> Doc +pPrint0 l = pPrintPrec l 0 + +appPrec :: Rational +appPrec = 10 + +-- | Parenthesize an value if the boolean is true. +prettyParen :: Bool -> Doc -> Doc +maybeParens False = id +maybeParens True = parens + +-- Various Pretty instances +instance Pretty Int where pPrint = int + +instance Pretty Integer where pPrint = integer + +instance Pretty Float where pPrint = float + +instance Pretty Double where pPrint = double + +instance Pretty () where pPrint _ = text "()" + +instance Pretty Bool where pPrint = text . show + +instance Pretty Ordering where pPrint = text . show + +instance Pretty Char where + pPrint = char + pPrintList _ = text . show + +instance (Pretty a) => Pretty (Maybe a) where + pPrintPrec _ _ Nothing = text "Nothing" + pPrintPrec l p (Just x) = + prettyParen (p > appPrec) $ text "Just" <+> pPrintPrec l (appPrec+1) x + +instance (Pretty a, Pretty b) => Pretty (Either a b) where + pPrintPrec l p (Left x) = + prettyParen (p > appPrec) $ text "Left" <+> pPrintPrec l (appPrec+1) x + pPrintPrec l p (Right x) = + prettyParen (p > appPrec) $ text "Right" <+> pPrintPrec l (appPrec+1) x + +instance (Pretty a) => Pretty [a] where + pPrintPrec l _ = pPrintList l + +instance (Pretty a, Pretty b) => Pretty (a, b) where + pPrintPrec l _ (a, b) = + parens $ fsep $ punctuate comma [pPrint0 l a, pPrint0 l b] + +instance (Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) where + pPrintPrec l _ (a, b, c) = + parens $ fsep $ punctuate comma [pPrint0 l a, pPrint0 l b, pPrint0 l c] + +instance (Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) where + pPrintPrec l _ (a, b, c, d) = + parens $ fsep $ punctuate comma + [pPrint0 l a, pPrint0 l b, pPrint0 l c, pPrint0 l d] + +instance (Pretty a, Pretty b, Pretty c, Pretty d, Pretty e) => Pretty (a, b, c, d, e) where + pPrintPrec l _ (a, b, c, d, e) = + parens $ fsep $ punctuate comma + [pPrint0 l a, pPrint0 l b, pPrint0 l c, pPrint0 l d, pPrint0 l e] + +instance (Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f) => Pretty (a, b, c, d, e, f) where + pPrintPrec l _ (a, b, c, d, e, f) = + parens $ fsep $ punctuate comma + [pPrint0 l a, pPrint0 l b, pPrint0 l c, + pPrint0 l d, pPrint0 l e, pPrint0 l f] + +instance (Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g) => + Pretty (a, b, c, d, e, f, g) where + pPrintPrec l _ (a, b, c, d, e, f, g) = + parens $ fsep $ punctuate comma + [pPrint0 l a, pPrint0 l b, pPrint0 l c, + pPrint0 l d, pPrint0 l e, pPrint0 l f, pPrint0 l g] + +instance (Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h) => + Pretty (a, b, c, d, e, f, g, h) where + pPrintPrec l _ (a, b, c, d, e, f, g, h) = + parens $ fsep $ punctuate comma + [pPrint0 l a, pPrint0 l b, pPrint0 l c, + pPrint0 l d, pPrint0 l e, pPrint0 l f, pPrint0 l g, pPrint0 l h] + From git at git.haskell.org Fri Jan 23 22:49:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:21 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, master, moretests: Add 'maybe*' variants to all bracketing functions (4badfbd) Message-ID: <20150123224921.E9D283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,master,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/4badfbd6bfbc31098df2c6f19fe5b11f39c70174 >--------------------------------------------------------------- commit 4badfbd6bfbc31098df2c6f19fe5b11f39c70174 Author: David Terei Date: Wed Dec 24 15:30:58 2014 -0800 Add 'maybe*' variants to all bracketing functions >--------------------------------------------------------------- 4badfbd6bfbc31098df2c6f19fe5b11f39c70174 src/Text/PrettyPrint/HughesPJ.hs | 25 +++++++++++++++++++++++++ src/Text/PrettyPrint/HughesPJClass.hs | 4 ++-- 2 files changed, 27 insertions(+), 2 deletions(-) diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index 509720b..9ed67b2 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -41,6 +41,7 @@ module Text.PrettyPrint.HughesPJ ( -- ** Wrapping documents in delimiters parens, brackets, braces, quotes, doubleQuotes, + maybeParens, maybeBrackets, maybeBraces, maybeQuotes, maybeDoubleQuotes, -- ** Combining documents empty, @@ -385,6 +386,30 @@ parens p = char '(' <> p <> char ')' brackets p = char '[' <> p <> char ']' braces p = char '{' <> p <> char '}' +-- | Apply 'parens' to 'Doc' if boolean is true. +maybeParens :: Bool -> Doc -> Doc +maybeParens False = id +maybeParens True = parens + +-- | Apply 'brackets' to 'Doc' if boolean is true. +maybeBrackets :: Bool -> Doc -> Doc +maybeBrackets False = id +maybeBrackets True = brackets + +-- | Apply 'braces' to 'Doc' if boolean is true. +maybeBraces :: Bool -> Doc -> Doc +maybeBraces False = id +maybeBraces True = braces + +-- | Apply 'quotes' to 'Doc' if boolean is true. +maybeQuotes :: Bool -> Doc -> Doc +maybeQuotes False = id +maybeQuotes True = quotes + +-- | Apply 'doubleQuotes' to 'Doc' if boolean is true. +maybeDoubleQuotes :: Bool -> Doc -> Doc +maybeDoubleQuotes False = id +maybeDoubleQuotes True = doubleQuotes -- --------------------------------------------------------------------------- -- Structural operations on GDocs diff --git a/src/Text/PrettyPrint/HughesPJClass.hs b/src/Text/PrettyPrint/HughesPJClass.hs index da1b474..ebf6ea2 100644 --- a/src/Text/PrettyPrint/HughesPJClass.hs +++ b/src/Text/PrettyPrint/HughesPJClass.hs @@ -65,9 +65,9 @@ appPrec :: Rational appPrec = 10 -- | Parenthesize an value if the boolean is true. +{-# DEPRECATED prettyParen "Please use 'maybeParens' instead" #-} prettyParen :: Bool -> Doc -> Doc -maybeParens False = id -maybeParens True = parens +prettyParen = maybeParens -- Various Pretty instances instance Pretty Int where pPrint = int From git at git.haskell.org Fri Jan 23 22:49:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:23 +0000 (UTC) Subject: [commit: packages/pretty] master: Bump to version 1.1.2.0 (314b743) Message-ID: <20150123224923.F0B5A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/314b74353534e0fadd4ccb1720cdf3206d5f9a98 >--------------------------------------------------------------- commit 314b74353534e0fadd4ccb1720cdf3206d5f9a98 Author: David Terei Date: Wed Dec 24 15:31:31 2014 -0800 Bump to version 1.1.2.0 >--------------------------------------------------------------- 314b74353534e0fadd4ccb1720cdf3206d5f9a98 pretty.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pretty.cabal b/pretty.cabal index 47c1a8f..91e80fb 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -1,5 +1,5 @@ name: pretty -version: 1.1.1.3 +version: 1.1.2.0 synopsis: Pretty-printing library description: This package contains a pretty-printing library, a set of API's From git at git.haskell.org Fri Jan 23 22:49:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:26 +0000 (UTC) Subject: [commit: packages/pretty] master: add minimal pragma to pretty class (6883fda) Message-ID: <20150123224926.02DE13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/6883fdac42eefc0b93db1938449eed8fd057e6a4 >--------------------------------------------------------------- commit 6883fdac42eefc0b93db1938449eed8fd057e6a4 Author: David Terei Date: Wed Dec 24 15:49:00 2014 -0800 add minimal pragma to pretty class >--------------------------------------------------------------- 6883fdac42eefc0b93db1938449eed8fd057e6a4 src/Text/PrettyPrint/HughesPJClass.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Text/PrettyPrint/HughesPJClass.hs b/src/Text/PrettyPrint/HughesPJClass.hs index ebf6ea2..298f447 100644 --- a/src/Text/PrettyPrint/HughesPJClass.hs +++ b/src/Text/PrettyPrint/HughesPJClass.hs @@ -54,6 +54,10 @@ class Pretty a where pPrintList :: PrettyLevel -> [a] -> Doc pPrintList l = brackets . fsep . punctuate comma . map (pPrintPrec l 0) +#if __GLASGOW_HASKELL__ >= 708 + {-# MINIMAL pPrintPrec | pPrint #-} +#endif + -- | Pretty print a value with the 'prettyNormal' level. prettyShow :: (Pretty a) => a -> String prettyShow = render . pPrint From git at git.haskell.org Fri Jan 23 22:49:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:28 +0000 (UTC) Subject: [commit: packages/pretty] master: fix hslint warnings (ac1b41a) Message-ID: <20150123224928.082E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/ac1b41a6a613376f0e864707a5117a77d82a2785 >--------------------------------------------------------------- commit ac1b41a6a613376f0e864707a5117a77d82a2785 Author: David Terei Date: Thu Dec 25 01:43:15 2014 -0800 fix hslint warnings >--------------------------------------------------------------- ac1b41a6a613376f0e864707a5117a77d82a2785 src/Text/PrettyPrint/HughesPJ.hs | 63 ++++++++++++++++++++-------------------- 1 file changed, 31 insertions(+), 32 deletions(-) diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index 4111202..86c4b71 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -366,9 +366,9 @@ rbrack = char ']' lbrace = char '{' rbrace = char '}' -space_text, nl_text :: TextDetails -space_text = Chr ' ' -nl_text = Chr '\n' +spaceText, nlText :: TextDetails +spaceText = Chr ' ' +nlText = Chr '\n' int :: Int -> Doc -- ^ @int n = text (show n)@ integer :: Integer -> Doc -- ^ @integer n = text (show n)@ @@ -497,17 +497,17 @@ reduceAB (Beside Empty _ q) = q reduceAB doc = doc nilAbove_ :: RDoc -> RDoc -nilAbove_ p = NilAbove p +nilAbove_ = NilAbove -- Arg of a TextBeside is always an RDoc textBeside_ :: TextDetails -> Int -> RDoc -> RDoc -textBeside_ s sl p = TextBeside s sl p +textBeside_ = TextBeside nest_ :: Int -> RDoc -> RDoc -nest_ k p = Nest k p +nest_ = Nest union_ :: RDoc -> RDoc -> RDoc -union_ p q = Union p q +union_ = Union -- --------------------------------------------------------------------------- @@ -547,7 +547,7 @@ above_ p g q = Above p g q above :: Doc -> Bool -> RDoc -> RDoc above (Above p g1 q1) g2 q2 = above p g1 (above q1 g2 q2) -above p@(Beside _ _ _) g q = aboveNest (reduceDoc p) g 0 (reduceDoc q) +above p@(Beside{}) g q = aboveNest (reduceDoc p) g 0 (reduceDoc q) above p g q = aboveNest p g 0 (reduceDoc q) -- Specfication: aboveNest p g k q = p $g$ (nest k q) @@ -615,7 +615,7 @@ beside (Nest k p) g q = nest_ k $! beside p g q beside p@(Beside p1 g1 q1) g2 q2 | g1 == g2 = beside p1 g1 $! beside q1 g2 q2 | otherwise = beside (reduceDoc p) g2 q2 -beside p@(Above _ _ _) g q = let !d = reduceDoc p in beside d g q +beside p@(Above{}) g q = let !d = reduceDoc p in beside d g q beside (NilAbove p) g q = nilAbove_ $! beside p g q beside (TextBeside s sl p) g q = textBeside_ s sl $! rest where @@ -628,7 +628,7 @@ beside (TextBeside s sl p) g q = textBeside_ s sl $! rest nilBeside :: Bool -> RDoc -> RDoc nilBeside _ Empty = Empty -- Hence the text "" in the spec nilBeside g (Nest _ p) = nilBeside g p -nilBeside g p | g = textBeside_ space_text 1 p +nilBeside g p | g = textBeside_ spaceText 1 p | otherwise = p @@ -759,8 +759,7 @@ best :: Int -- Line length -> Int -- Ribbon length -> RDoc -> RDoc -- No unions in here! -best w0 r p0 - = get w0 p0 +best w0 r = get w0 where get w _ | w == 0 && False = undefined get _ Empty = Empty @@ -784,7 +783,7 @@ best w0 r p0 get1 _ _ (Beside {}) = error "best get1 Beside" nicest :: Int -> Int -> Doc -> Doc -> Doc -nicest !w !r p q = nicest1 w r 0 p q +nicest !w !r = nicest1 w r 0 nicest1 :: Int -> Int -> Int -> Doc -> Doc -> Doc nicest1 !w !r !sl p q | fits ((w `min` r) - sl) p = p @@ -852,13 +851,13 @@ data Mode = PageMode -- ^ Normal -- | Render the @Doc@ to a String using the default @Style at . render :: Doc -> String -render doc = fullRender (mode style) (lineLength style) (ribbonsPerLine style) - txtPrinter "" doc +render = fullRender (mode style) (lineLength style) (ribbonsPerLine style) + txtPrinter "" -- | Render the @Doc@ to a String using the given @Style at . renderStyle :: Style -> Doc -> String -renderStyle s doc = fullRender (mode s) (lineLength s) (ribbonsPerLine s) - txtPrinter "" doc +renderStyle s = fullRender (mode s) (lineLength s) (ribbonsPerLine s) + txtPrinter "" -- | Default TextDetails printer txtPrinter :: TextDetails -> String -> String @@ -875,9 +874,9 @@ fullRender :: Mode -- ^ Rendering mode -> Doc -- ^ The document -> a -- ^ Result fullRender OneLineMode _ _ txt end doc - = easy_display space_text (\_ y -> y) txt end (reduceDoc doc) + = easyDisplay spaceText (\_ y -> y) txt end (reduceDoc doc) fullRender LeftMode _ _ txt end doc - = easy_display nl_text first txt end (reduceDoc doc) + = easyDisplay nlText first txt end (reduceDoc doc) fullRender m lineLen ribbons txt rest doc = display m lineLen ribbonLen txt rest doc' @@ -890,23 +889,23 @@ fullRender m lineLen ribbons txt rest doc ZigZagMode -> maxBound _ -> lineLen -easy_display :: TextDetails +easyDisplay :: TextDetails -> (Doc -> Doc -> Doc) -> (TextDetails -> a -> a) -> a -> Doc -> a -easy_display nl_space_text choose txt end doc - = lay doc +easyDisplay nlSpaceText choose txt end + = lay where - lay NoDoc = error "easy_display: NoDoc" + lay NoDoc = error "easyDisplay: NoDoc" lay (Union p q) = lay (choose p q) lay (Nest _ p) = lay p lay Empty = end - lay (NilAbove p) = nl_space_text `txt` lay p + lay (NilAbove p) = nlSpaceText `txt` lay p lay (TextBeside s _ p) = s `txt` lay p - lay (Above {}) = error "easy_display Above" - lay (Beside {}) = error "easy_display Beside" + lay (Above {}) = error "easyDisplay Above" + lay (Beside {}) = error "easyDisplay Beside" display :: Mode -> Int -> Int -> (TextDetails -> a -> a) -> a -> Doc -> a display m !page_width !ribbon_width txt end doc @@ -916,19 +915,19 @@ display m !page_width !ribbon_width txt end doc lay k _ | k `seq` False = undefined lay k (Nest k1 p) = lay (k + k1) p lay _ Empty = end - lay k (NilAbove p) = nl_text `txt` lay k p + lay k (NilAbove p) = nlText `txt` lay k p lay k (TextBeside s sl p) = case m of ZigZagMode | k >= gap_width - -> nl_text `txt` ( + -> nlText `txt` ( Str (replicate shift '/') `txt` ( - nl_text `txt` + nlText `txt` lay1 (k - shift) s sl p )) | k < 0 - -> nl_text `txt` ( + -> nlText `txt` ( Str (replicate shift '\\') `txt` ( - nl_text `txt` + nlText `txt` lay1 (k + shift) s sl p )) _ -> lay1 k s sl p @@ -941,7 +940,7 @@ display m !page_width !ribbon_width txt end doc in Str (indent k) `txt` (s `txt` lay2 r p) lay2 k _ | k `seq` False = undefined - lay2 k (NilAbove p) = nl_text `txt` lay k p + lay2 k (NilAbove p) = nlText `txt` lay k p lay2 k (TextBeside s sl p) = s `txt` lay2 (k + sl) p lay2 k (Nest _ p) = lay2 k p lay2 _ Empty = end From git at git.haskell.org Fri Jan 23 22:49:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:30 +0000 (UTC) Subject: [commit: packages/pretty] master: add Generic instance to Doc (428e3f7) Message-ID: <20150123224930.0EE3F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/428e3f74ad2b4b76a6166f58994b3f7ea0fd83e3 >--------------------------------------------------------------- commit 428e3f74ad2b4b76a6166f58994b3f7ea0fd83e3 Author: David Terei Date: Thu Dec 25 01:35:46 2014 -0800 add Generic instance to Doc >--------------------------------------------------------------- 428e3f74ad2b4b76a6166f58994b3f7ea0fd83e3 src/Text/PrettyPrint/HughesPJ.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index 9ed67b2..4111202 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -2,6 +2,7 @@ {-# LANGUAGE BangPatterns #-} #if __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Safe #-} +{-# LANGUAGE DeriveGeneric #-} #endif ----------------------------------------------------------------------------- @@ -81,6 +82,8 @@ import Data.Function ( on ) import Data.Monoid ( Monoid(mempty, mappend) ) import Data.String ( IsString(fromString) ) +import GHC.Generics + -- --------------------------------------------------------------------------- -- The Doc calculus @@ -178,6 +181,9 @@ data Doc | NoDoc -- The empty set of documents | Beside Doc Bool Doc -- True <=> space between | Above Doc Bool Doc -- True <=> never overlap +#if __GLASGOW_HASKELL__ >= 701 + deriving (Generic) +#endif {- Here are the invariants: From git at git.haskell.org Fri Jan 23 22:49:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:32 +0000 (UTC) Subject: [commit: packages/pretty] master: Add appropriate Show, Eq and Generic instances (a7db5b5) Message-ID: <20150123224932.169F33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/a7db5b5897be64d94d9a13e9f9df120e05ff8afa >--------------------------------------------------------------- commit a7db5b5897be64d94d9a13e9f9df120e05ff8afa Author: David Terei Date: Thu Dec 25 01:54:14 2014 -0800 Add appropriate Show, Eq and Generic instances >--------------------------------------------------------------- a7db5b5897be64d94d9a13e9f9df120e05ff8afa src/Text/PrettyPrint/HughesPJ.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index 86c4b71..6f11a8d 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -231,6 +231,7 @@ data TextDetails = Chr {-# UNPACK #-} !Char -- ^ A single Char fragment | PStr String -- ^ Used to represent a Fast String fragment -- but now deprecated and identical to the -- Str constructor. + deriving (Show, Eq, Generic) -- Combining @Doc@ values instance Monoid Doc where @@ -838,6 +839,7 @@ data Style , lineLength :: Int -- ^ Length of line, in chars , ribbonsPerLine :: Float -- ^ Ratio of line length to ribbon length } + deriving (Show, Eq, Generic) -- | The default style (@mode=PageMode, lineLength=100, ribbonsPerLine=1.5@). style :: Style @@ -848,6 +850,7 @@ data Mode = PageMode -- ^ Normal | ZigZagMode -- ^ With zig-zag cuts | LeftMode -- ^ No indentation, infinitely long lines | OneLineMode -- ^ All on one line + deriving (Show, Eq, Generic) -- | Render the @Doc@ to a String using the default @Style at . render :: Doc -> String From git at git.haskell.org Fri Jan 23 22:49:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:34 +0000 (UTC) Subject: [commit: packages/pretty] master: fix missing ghc-prim package (a2e79da) Message-ID: <20150123224934.1B91D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/a2e79daa67b831a2b61233ca908fa14da5f5f7ad >--------------------------------------------------------------- commit a2e79daa67b831a2b61233ca908fa14da5f5f7ad Author: David Terei Date: Thu Dec 25 02:08:59 2014 -0800 fix missing ghc-prim package >--------------------------------------------------------------- a2e79daa67b831a2b61233ca908fa14da5f5f7ad pretty.cabal | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/pretty.cabal b/pretty.cabal index 91e80fb..db04752 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -32,7 +32,8 @@ Library Text.PrettyPrint.HughesPJ Text.PrettyPrint.HughesPJClass build-depends: base >= 3 && < 5, - deepseq >= 1.1 + deepseq >= 1.1, + ghc-prim extensions: CPP, BangPatterns ghc-options: -Wall -fwarn-tabs @@ -42,6 +43,7 @@ Test-Suite test-pretty src build-depends: base >= 3 && < 5, deepseq >= 1.1, + ghc-prim, QuickCheck >= 2.5 && <3 main-is: Test.hs other-modules: From git at git.haskell.org Fri Jan 23 22:49:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:36 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, moretests: add minimal pragma to pretty class (4ce5928) Message-ID: <20150123224936.22C1F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/4ce5928d2f201932439562430b8d7b88f5050f7c >--------------------------------------------------------------- commit 4ce5928d2f201932439562430b8d7b88f5050f7c Author: David Terei Date: Wed Dec 24 15:49:00 2014 -0800 add minimal pragma to pretty class >--------------------------------------------------------------- 4ce5928d2f201932439562430b8d7b88f5050f7c src/Text/PrettyPrint/HughesPJClass.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Text/PrettyPrint/HughesPJClass.hs b/src/Text/PrettyPrint/HughesPJClass.hs index ebf6ea2..298f447 100644 --- a/src/Text/PrettyPrint/HughesPJClass.hs +++ b/src/Text/PrettyPrint/HughesPJClass.hs @@ -54,6 +54,10 @@ class Pretty a where pPrintList :: PrettyLevel -> [a] -> Doc pPrintList l = brackets . fsep . punctuate comma . map (pPrintPrec l 0) +#if __GLASGOW_HASKELL__ >= 708 + {-# MINIMAL pPrintPrec | pPrint #-} +#endif + -- | Pretty print a value with the 'prettyNormal' level. prettyShow :: (Pretty a) => a -> String prettyShow = render . pPrint From git at git.haskell.org Fri Jan 23 22:49:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:38 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, moretests: Add appropriate Show, Eq and Generic instances (912f63c) Message-ID: <20150123224938.298883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/912f63cf490064d0f071c60fb71d6ce7e6205897 >--------------------------------------------------------------- commit 912f63cf490064d0f071c60fb71d6ce7e6205897 Author: David Terei Date: Thu Dec 25 01:35:46 2014 -0800 Add appropriate Show, Eq and Generic instances >--------------------------------------------------------------- 912f63cf490064d0f071c60fb71d6ce7e6205897 pretty.cabal | 8 +++++--- src/Text/PrettyPrint/HughesPJ.hs | 15 +++++++++++++++ tests/PrettyTestVersion.hs | 4 ++++ 3 files changed, 24 insertions(+), 3 deletions(-) diff --git a/pretty.cabal b/pretty.cabal index 47c1a8f..e97ac11 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -32,8 +32,9 @@ Library Text.PrettyPrint.HughesPJ Text.PrettyPrint.HughesPJClass build-depends: base >= 3 && < 5, - deepseq >= 1.1 - extensions: CPP, BangPatterns + deepseq >= 1.1, + ghc-prim + extensions: CPP, BangPatterns, DeriveGeneric ghc-options: -Wall -fwarn-tabs Test-Suite test-pretty @@ -42,12 +43,13 @@ Test-Suite test-pretty src build-depends: base >= 3 && < 5, deepseq >= 1.1, + ghc-prim, QuickCheck >= 2.5 && <3 main-is: Test.hs other-modules: TestGenerators TestStructures - extensions: CPP, BangPatterns + extensions: CPP, BangPatterns, DeriveGeneric include-dirs: src/Text/PrettyPrint -- Executable Bench1 diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index 9ed67b2..f0efbd1 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -2,6 +2,7 @@ {-# LANGUAGE BangPatterns #-} #if __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Safe #-} +{-# LANGUAGE DeriveGeneric #-} #endif ----------------------------------------------------------------------------- @@ -81,6 +82,8 @@ import Data.Function ( on ) import Data.Monoid ( Monoid(mempty, mappend) ) import Data.String ( IsString(fromString) ) +import GHC.Generics + -- --------------------------------------------------------------------------- -- The Doc calculus @@ -178,6 +181,9 @@ data Doc | NoDoc -- The empty set of documents | Beside Doc Bool Doc -- True <=> space between | Above Doc Bool Doc -- True <=> never overlap +#if __GLASGOW_HASKELL__ >= 701 + deriving (Generic) +#endif {- Here are the invariants: @@ -225,6 +231,9 @@ data TextDetails = Chr {-# UNPACK #-} !Char -- ^ A single Char fragment | PStr String -- ^ Used to represent a Fast String fragment -- but now deprecated and identical to the -- Str constructor. +#if __GLASGOW_HASKELL__ >= 701 + deriving (Show, Eq, Generic) +#endif -- Combining @Doc@ values instance Monoid Doc where @@ -833,6 +842,9 @@ data Style , lineLength :: Int -- ^ Length of line, in chars , ribbonsPerLine :: Float -- ^ Ratio of line length to ribbon length } +#if __GLASGOW_HASKELL__ >= 701 + deriving (Show, Eq, Generic) +#endif -- | The default style (@mode=PageMode, lineLength=100, ribbonsPerLine=1.5@). style :: Style @@ -843,6 +855,9 @@ data Mode = PageMode -- ^ Normal | ZigZagMode -- ^ With zig-zag cuts | LeftMode -- ^ No indentation, infinitely long lines | OneLineMode -- ^ All on one line +#if __GLASGOW_HASKELL__ >= 701 + deriving (Show, Eq, Generic) +#endif -- | Render the @Doc@ to a String using the default @Style at . render :: Doc -> String diff --git a/tests/PrettyTestVersion.hs b/tests/PrettyTestVersion.hs index 4a7cf6b..557504e 100644 --- a/tests/PrettyTestVersion.hs +++ b/tests/PrettyTestVersion.hs @@ -1,4 +1,8 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE BangPatterns #-} +#if __GLASGOW_HASKELL__ >= 701 +{-# LANGUAGE DeriveGeneric #-} +#endif #define TESTING From git at git.haskell.org Fri Jan 23 22:49:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:40 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, moretests: fix hslint warnings (ac4c532) Message-ID: <20150123224940.2FAAB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/ac4c532fc964007ce9a2267b9ec13a35feb627ad >--------------------------------------------------------------- commit ac4c532fc964007ce9a2267b9ec13a35feb627ad Author: David Terei Date: Thu Dec 25 01:43:15 2014 -0800 fix hslint warnings >--------------------------------------------------------------- ac4c532fc964007ce9a2267b9ec13a35feb627ad src/Text/PrettyPrint/HughesPJ.hs | 63 ++++++++++++++++++++-------------------- 1 file changed, 31 insertions(+), 32 deletions(-) diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index f0efbd1..aac7de0 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -369,9 +369,9 @@ rbrack = char ']' lbrace = char '{' rbrace = char '}' -space_text, nl_text :: TextDetails -space_text = Chr ' ' -nl_text = Chr '\n' +spaceText, nlText :: TextDetails +spaceText = Chr ' ' +nlText = Chr '\n' int :: Int -> Doc -- ^ @int n = text (show n)@ integer :: Integer -> Doc -- ^ @integer n = text (show n)@ @@ -500,17 +500,17 @@ reduceAB (Beside Empty _ q) = q reduceAB doc = doc nilAbove_ :: RDoc -> RDoc -nilAbove_ p = NilAbove p +nilAbove_ = NilAbove -- Arg of a TextBeside is always an RDoc textBeside_ :: TextDetails -> Int -> RDoc -> RDoc -textBeside_ s sl p = TextBeside s sl p +textBeside_ = TextBeside nest_ :: Int -> RDoc -> RDoc -nest_ k p = Nest k p +nest_ = Nest union_ :: RDoc -> RDoc -> RDoc -union_ p q = Union p q +union_ = Union -- --------------------------------------------------------------------------- @@ -550,7 +550,7 @@ above_ p g q = Above p g q above :: Doc -> Bool -> RDoc -> RDoc above (Above p g1 q1) g2 q2 = above p g1 (above q1 g2 q2) -above p@(Beside _ _ _) g q = aboveNest (reduceDoc p) g 0 (reduceDoc q) +above p@(Beside{}) g q = aboveNest (reduceDoc p) g 0 (reduceDoc q) above p g q = aboveNest p g 0 (reduceDoc q) -- Specfication: aboveNest p g k q = p $g$ (nest k q) @@ -618,7 +618,7 @@ beside (Nest k p) g q = nest_ k $! beside p g q beside p@(Beside p1 g1 q1) g2 q2 | g1 == g2 = beside p1 g1 $! beside q1 g2 q2 | otherwise = beside (reduceDoc p) g2 q2 -beside p@(Above _ _ _) g q = let !d = reduceDoc p in beside d g q +beside p@(Above{}) g q = let !d = reduceDoc p in beside d g q beside (NilAbove p) g q = nilAbove_ $! beside p g q beside (TextBeside s sl p) g q = textBeside_ s sl $! rest where @@ -631,7 +631,7 @@ beside (TextBeside s sl p) g q = textBeside_ s sl $! rest nilBeside :: Bool -> RDoc -> RDoc nilBeside _ Empty = Empty -- Hence the text "" in the spec nilBeside g (Nest _ p) = nilBeside g p -nilBeside g p | g = textBeside_ space_text 1 p +nilBeside g p | g = textBeside_ spaceText 1 p | otherwise = p @@ -762,8 +762,7 @@ best :: Int -- Line length -> Int -- Ribbon length -> RDoc -> RDoc -- No unions in here! -best w0 r p0 - = get w0 p0 +best w0 r = get w0 where get w _ | w == 0 && False = undefined get _ Empty = Empty @@ -787,7 +786,7 @@ best w0 r p0 get1 _ _ (Beside {}) = error "best get1 Beside" nicest :: Int -> Int -> Doc -> Doc -> Doc -nicest !w !r p q = nicest1 w r 0 p q +nicest !w !r = nicest1 w r 0 nicest1 :: Int -> Int -> Int -> Doc -> Doc -> Doc nicest1 !w !r !sl p q | fits ((w `min` r) - sl) p = p @@ -861,13 +860,13 @@ data Mode = PageMode -- ^ Normal -- | Render the @Doc@ to a String using the default @Style at . render :: Doc -> String -render doc = fullRender (mode style) (lineLength style) (ribbonsPerLine style) - txtPrinter "" doc +render = fullRender (mode style) (lineLength style) (ribbonsPerLine style) + txtPrinter "" -- | Render the @Doc@ to a String using the given @Style at . renderStyle :: Style -> Doc -> String -renderStyle s doc = fullRender (mode s) (lineLength s) (ribbonsPerLine s) - txtPrinter "" doc +renderStyle s = fullRender (mode s) (lineLength s) (ribbonsPerLine s) + txtPrinter "" -- | Default TextDetails printer txtPrinter :: TextDetails -> String -> String @@ -884,9 +883,9 @@ fullRender :: Mode -- ^ Rendering mode -> Doc -- ^ The document -> a -- ^ Result fullRender OneLineMode _ _ txt end doc - = easy_display space_text (\_ y -> y) txt end (reduceDoc doc) + = easyDisplay spaceText (\_ y -> y) txt end (reduceDoc doc) fullRender LeftMode _ _ txt end doc - = easy_display nl_text first txt end (reduceDoc doc) + = easyDisplay nlText first txt end (reduceDoc doc) fullRender m lineLen ribbons txt rest doc = display m lineLen ribbonLen txt rest doc' @@ -899,23 +898,23 @@ fullRender m lineLen ribbons txt rest doc ZigZagMode -> maxBound _ -> lineLen -easy_display :: TextDetails +easyDisplay :: TextDetails -> (Doc -> Doc -> Doc) -> (TextDetails -> a -> a) -> a -> Doc -> a -easy_display nl_space_text choose txt end doc - = lay doc +easyDisplay nlSpaceText choose txt end + = lay where - lay NoDoc = error "easy_display: NoDoc" + lay NoDoc = error "easyDisplay: NoDoc" lay (Union p q) = lay (choose p q) lay (Nest _ p) = lay p lay Empty = end - lay (NilAbove p) = nl_space_text `txt` lay p + lay (NilAbove p) = nlSpaceText `txt` lay p lay (TextBeside s _ p) = s `txt` lay p - lay (Above {}) = error "easy_display Above" - lay (Beside {}) = error "easy_display Beside" + lay (Above {}) = error "easyDisplay Above" + lay (Beside {}) = error "easyDisplay Beside" display :: Mode -> Int -> Int -> (TextDetails -> a -> a) -> a -> Doc -> a display m !page_width !ribbon_width txt end doc @@ -925,19 +924,19 @@ display m !page_width !ribbon_width txt end doc lay k _ | k `seq` False = undefined lay k (Nest k1 p) = lay (k + k1) p lay _ Empty = end - lay k (NilAbove p) = nl_text `txt` lay k p + lay k (NilAbove p) = nlText `txt` lay k p lay k (TextBeside s sl p) = case m of ZigZagMode | k >= gap_width - -> nl_text `txt` ( + -> nlText `txt` ( Str (replicate shift '/') `txt` ( - nl_text `txt` + nlText `txt` lay1 (k - shift) s sl p )) | k < 0 - -> nl_text `txt` ( + -> nlText `txt` ( Str (replicate shift '\\') `txt` ( - nl_text `txt` + nlText `txt` lay1 (k + shift) s sl p )) _ -> lay1 k s sl p @@ -950,7 +949,7 @@ display m !page_width !ribbon_width txt end doc in Str (indent k) `txt` (s `txt` lay2 r p) lay2 k _ | k `seq` False = undefined - lay2 k (NilAbove p) = nl_text `txt` lay k p + lay2 k (NilAbove p) = nlText `txt` lay k p lay2 k (TextBeside s sl p) = s `txt` lay2 (k + sl) p lay2 k (Nest _ p) = lay2 k p lay2 _ Empty = end From git at git.haskell.org Fri Jan 23 22:49:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:42 +0000 (UTC) Subject: [commit: packages/pretty] moretests: Bump to version 1.1.2.0 (a158ec3) Message-ID: <20150123224942.361953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/a158ec3a57544e8f77939ff3931d9308fbff02ba >--------------------------------------------------------------- commit a158ec3a57544e8f77939ff3931d9308fbff02ba Author: David Terei Date: Wed Dec 24 15:31:31 2014 -0800 Bump to version 1.1.2.0 >--------------------------------------------------------------- a158ec3a57544e8f77939ff3931d9308fbff02ba pretty.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pretty.cabal b/pretty.cabal index e97ac11..dc65a46 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -1,5 +1,5 @@ name: pretty -version: 1.1.1.3 +version: 1.1.2.0 synopsis: Pretty-printing library description: This package contains a pretty-printing library, a set of API's From git at git.haskell.org Fri Jan 23 22:49:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:44 +0000 (UTC) Subject: [commit: packages/pretty] moretests: update changelong (33840d4) Message-ID: <20150123224944.3C3413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/33840d44e50e673a25043dc0aa6533353738da0e >--------------------------------------------------------------- commit 33840d44e50e673a25043dc0aa6533353738da0e Author: David Terei Date: Thu Dec 25 02:18:43 2014 -0800 update changelong >--------------------------------------------------------------- 33840d44e50e673a25043dc0aa6533353738da0e CHANGELOG.md | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 2195744..8d3b974 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,5 +1,11 @@ # Pretty library change log +## 1.1.2.0 -- 25th December, 2014 + +* Merge in prettyclass package -- new Text.PrettyPrint.HughesPHClass. +* Add in 'maybe\*' variants of various bracket functins. +* Add Generic instances for appropriate data types. + ## 1.1.1.3 -- 21st December, 2014 * Remove upper bound on `deepseq` package to fix build issues with From git at git.haskell.org Fri Jan 23 22:49:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:46 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, moretests: work around bug with `cabal test` (f6b2e75) Message-ID: <20150123224946.4217F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/f6b2e752ed0b2b093e8354040eee45125b882706 >--------------------------------------------------------------- commit f6b2e752ed0b2b093e8354040eee45125b882706 Author: David Terei Date: Thu Dec 25 22:43:16 2014 -0800 work around bug with `cabal test` >--------------------------------------------------------------- f6b2e752ed0b2b093e8354040eee45125b882706 .travis.yml | 2 +- README.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 9179847..2db9d94 100644 --- a/.travis.yml +++ b/.travis.yml @@ -32,7 +32,7 @@ script: - cabal configure -v2 --enable-tests - cabal build - cabal check || [ "$CABALVER" == "1.16" ] - - cabal test + - cabal test --show-details=streaming - cabal sdist - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; diff --git a/README.md b/README.md index ae5c7b8..6b24d8c 100644 --- a/README.md +++ b/README.md @@ -33,6 +33,11 @@ We have to install `QuickCheck` manually as otherwise Cabal currently throws an error due to the cyclic dependency between `pretty` and `QuickCheck`. +*If `cabal test` freezes*, then run +`cabal test --show-details=streaming` instead. This is due to a +[bug](https://github.com/haskell/cabal/issues/1810) in certain +versions of Cabal. + ## Get involved! We are happy to receive bug reports, fixes, documentation enhancements, From git at git.haskell.org Fri Jan 23 22:49:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:48 +0000 (UTC) Subject: [commit: packages/pretty] large_docs, moretests: remove some unused helper functions from test-suite (ead25e7) Message-ID: <20150123224948.497CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branches: large_docs,moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/ead25e7d14af5e207a602822ecabd92c31e571e6 >--------------------------------------------------------------- commit ead25e7d14af5e207a602822ecabd92c31e571e6 Author: David Terei Date: Thu Dec 25 22:44:32 2014 -0800 remove some unused helper functions from test-suite >--------------------------------------------------------------- ead25e7d14af5e207a602822ecabd92c31e571e6 tests/Test.hs | 5 ----- 1 file changed, 5 deletions(-) diff --git a/tests/Test.hs b/tests/Test.hs index bcda271..51f659d 100644 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -134,11 +134,6 @@ visibleSpace ' ' = '.' visibleSpace '.' = error "dot in visibleSpace (avoid confusion, please)" visibleSpace c = c --- shorthands debug functions -pd = (print.prettyDoc) -pds = mapM_ pd -rds = (map mergeTexts.flattenDoc) - -- (1) QuickCheck Properties: Laws -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Fri Jan 23 22:49:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:50 +0000 (UTC) Subject: [commit: packages/pretty] moretests: fix travis for bug in cabal 1.20 (0e993b2) Message-ID: <20150123224950.4EA3C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/0e993b2479f05c451c034b586fd001dd69b82194 >--------------------------------------------------------------- commit 0e993b2479f05c451c034b586fd001dd69b82194 Author: David Terei Date: Thu Dec 25 22:55:01 2014 -0800 fix travis for bug in cabal 1.20 >--------------------------------------------------------------- 0e993b2479f05c451c034b586fd001dd69b82194 .travis.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 2db9d94..de5fe5b 100644 --- a/.travis.yml +++ b/.travis.yml @@ -31,8 +31,8 @@ script: - cabal install "QuickCheck >= 2.5 && < 3" - cabal configure -v2 --enable-tests - cabal build - - cabal check || [ "$CABALVER" == "1.16" ] - - cabal test --show-details=streaming + - cabal check + - ([ "$CABALVER" == "1.20" ] && cabal test --show-details=streaming) || ([ "$CABALVER" != "1.20" ] && cabal test) - cabal sdist - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; From git at git.haskell.org Fri Jan 23 22:49:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:52 +0000 (UTC) Subject: [commit: packages/pretty] moretests: Improve test-suite, merging in GHC tests (d45b1be) Message-ID: <20150123224952.56E963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : moretests Link : http://git.haskell.org/packages/pretty.git/commitdiff/d45b1be45b3e6ec982f1e8b0fe556d3650ee2e60 >--------------------------------------------------------------- commit d45b1be45b3e6ec982f1e8b0fe556d3650ee2e60 Author: David Terei Date: Thu Dec 25 23:58:45 2014 -0800 Improve test-suite, merging in GHC tests >--------------------------------------------------------------- d45b1be45b3e6ec982f1e8b0fe556d3650ee2e60 pretty.cabal | 2 ++ tests/BugSep.hs | 3 +++ tests/T3911.hs | 23 ----------------- tests/T3911.stdout | 4 --- tests/Test.hs | 6 ++++- tests/TestUtils.hs | 19 ++++++++++++++ tests/UnitPP1.hs | 76 ++++++++++++++++++++++++++++++++++++++++++++++++++++++ tests/UnitT3911.hs | 25 ++++++++++++++++++ tests/all.T | 2 -- tests/pp1.hs | 18 ------------- tests/pp1.stdout | 4 --- 11 files changed, 130 insertions(+), 52 deletions(-) diff --git a/pretty.cabal b/pretty.cabal index dc65a46..c763e25 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -49,6 +49,8 @@ Test-Suite test-pretty other-modules: TestGenerators TestStructures + UnitPP1 + UnitT3911 extensions: CPP, BangPatterns, DeriveGeneric include-dirs: src/Text/PrettyPrint diff --git a/tests/BugSep.hs b/tests/BugSep.hs index 2047480..fe16b80 100644 --- a/tests/BugSep.hs +++ b/tests/BugSep.hs @@ -1,3 +1,6 @@ +-- | Demonstration of ambiguity in HughesPJ library at this time. GHC's +-- internal copy has a different answer than we currently do, preventing them +-- using our library. module Main (main) where import Text.PrettyPrint.HughesPJ diff --git a/tests/T3911.hs b/tests/T3911.hs deleted file mode 100644 index 01ccb22..0000000 --- a/tests/T3911.hs +++ /dev/null @@ -1,23 +0,0 @@ - -module Main where - -import Text.PrettyPrint.HughesPJ - -xs :: [Doc] -xs = [text "hello", - nest 10 (text "world")] - -d1 :: Doc -d1 = vcat xs - -d2 :: Doc -d2 = foldr ($$) empty xs - -d3 :: Doc -d3 = foldr ($+$) empty xs - -main :: IO () -main = do print d1 - print d2 - print d3 - diff --git a/tests/T3911.stdout b/tests/T3911.stdout deleted file mode 100644 index 7677e8d..0000000 --- a/tests/T3911.stdout +++ /dev/null @@ -1,4 +0,0 @@ -hello world -hello world -hello - world diff --git a/tests/Test.hs b/tests/Test.hs index 51f659d..107e32a 100644 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -1,4 +1,3 @@ -{-# OPTIONS -XStandaloneDeriving -XDeriveDataTypeable -XPackageImports #-} ----------------------------------------------------------------------------- -- Module : HughesPJQuickCheck -- Copyright : (c) 2008 Benedikt Huber @@ -16,6 +15,9 @@ import PrettyTestVersion import TestGenerators import TestStructures +import UnitPP1 +import UnitT3911 + import Control.Monad import Data.Char (isSpace) import Data.List (intersperse) @@ -31,6 +33,8 @@ main = do check_non_prims -- hpc full coverage check_rendering check_list_def + testPP1 + testT3911 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- Utility functions diff --git a/tests/TestUtils.hs b/tests/TestUtils.hs new file mode 100644 index 0000000..24ef7c7 --- /dev/null +++ b/tests/TestUtils.hs @@ -0,0 +1,19 @@ +-- | Test-suite framework and utility functions. +module TestUtils ( + simpleMatch + ) where + +import Control.Monad +import System.Exit + +simpleMatch :: String -> String -> String -> IO () +simpleMatch test expected actual = + when (actual /= expected) $ do + putStrLn $ "Test `" ++ test ++ "' failed!" + putStrLn "-----------------------------" + putStrLn $ "Expected: " ++ expected + putStrLn "-----------------------------" + putStrLn $ "Actual: " ++ actual + putStrLn "-----------------------------" + exitFailure + diff --git a/tests/UnitPP1.hs b/tests/UnitPP1.hs new file mode 100644 index 0000000..31217c4 --- /dev/null +++ b/tests/UnitPP1.hs @@ -0,0 +1,76 @@ +-- This code used to print an infinite string, by calling 'spaces' +-- with a negative argument. There's a patch in the library now, +-- which makes 'spaces' do something sensible when called with a negative +-- argument, but it really should not happen at all. + +module UnitPP1 where + +import TestUtils + +import Text.PrettyPrint.HughesPJ + +ncat :: Doc -> Doc -> Doc +ncat x y = nest 4 $ cat [ x, y ] + +d1, d2 :: Doc +d1 = foldl1 ncat $ take 50 $ repeat $ char 'a' +d2 = parens $ sep [ d1, text "+" , d1 ] + +testPP1 :: IO () +testPP1 = simpleMatch "PP1" expected out + where out = show d2 + +expected :: String +expected = + "(aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa\n\ ++ a\n\ + a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a)" + diff --git a/tests/UnitT3911.hs b/tests/UnitT3911.hs new file mode 100644 index 0000000..39aa1e2 --- /dev/null +++ b/tests/UnitT3911.hs @@ -0,0 +1,25 @@ +module UnitT3911 where + +import Text.PrettyPrint.HughesPJ + +import TestUtils + +xs :: [Doc] +xs = [text "hello", + nest 10 (text "world")] + +d1, d2, d3 :: Doc +d1 = vcat xs +d2 = foldr ($$) empty xs +d3 = foldr ($+$) empty xs + +testT3911 :: IO () +testT3911 = simpleMatch "T3911" expected out + where out = show d1 ++ "\n" ++ show d2 ++ "\n" ++ show d3 + +expected :: String +expected = + "hello world\n\ +hello world\n\ +hello\n\ + world" diff --git a/tests/all.T b/tests/all.T deleted file mode 100644 index 81e2c73..0000000 --- a/tests/all.T +++ /dev/null @@ -1,2 +0,0 @@ -test('pp1', [expect_broken(1062), only_ways(['normal'])], compile_and_run, ['']) -test('T3911', normal, compile_and_run, ['']) diff --git a/tests/pp1.hs b/tests/pp1.hs deleted file mode 100644 index 384d565..0000000 --- a/tests/pp1.hs +++ /dev/null @@ -1,18 +0,0 @@ --- This code used to print an infinite string, by calling 'spaces' --- with a negative argument. There's a patch in the library now, --- which makes 'spaces' do something sensible when called with a negative --- argument, but it really should not happen at all. - - -module Main where - -import Text.PrettyPrint.HughesPJ - - -ncat x y = nest 4 $ cat [ x, y ] - -d1 = foldl1 ncat $ take 50 $ repeat $ char 'a' -d2 = parens $ sep [ d1, text "+" , d1 ] - -main = print d2 - diff --git a/tests/pp1.stdout b/tests/pp1.stdout deleted file mode 100644 index 6915311..0000000 --- a/tests/pp1.stdout +++ /dev/null @@ -1,4 +0,0 @@ -This output is not what is expected, becuase the -test "works" now, by virtue of a hack in HughesPJ.spaces. -I'm leaving this strange output here to remind us to look -at the root cause of the problem. Sometime. \ No newline at end of file From git at git.haskell.org Fri Jan 23 22:49:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:54 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: fix travis for bug in cabal 1.20 (459bca1) Message-ID: <20150123224954.5C12E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/459bca1c840ed90734aaf3a45c221c9d87f36b38 >--------------------------------------------------------------- commit 459bca1c840ed90734aaf3a45c221c9d87f36b38 Author: David Terei Date: Thu Dec 25 22:55:01 2014 -0800 fix travis for bug in cabal 1.20 >--------------------------------------------------------------- 459bca1c840ed90734aaf3a45c221c9d87f36b38 .travis.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 2db9d94..de5fe5b 100644 --- a/.travis.yml +++ b/.travis.yml @@ -31,8 +31,8 @@ script: - cabal install "QuickCheck >= 2.5 && < 3" - cabal configure -v2 --enable-tests - cabal build - - cabal check || [ "$CABALVER" == "1.16" ] - - cabal test --show-details=streaming + - cabal check + - ([ "$CABALVER" == "1.20" ] && cabal test --show-details=streaming) || ([ "$CABALVER" != "1.20" ] && cabal test) - cabal sdist - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; From git at git.haskell.org Fri Jan 23 22:49:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:56 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: Improve test-suite, merging in GHC tests (02503a3) Message-ID: <20150123224956.64DEE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/02503a367d000f6b6d76db4ab238af134fdc92b8 >--------------------------------------------------------------- commit 02503a367d000f6b6d76db4ab238af134fdc92b8 Author: David Terei Date: Thu Dec 25 23:58:45 2014 -0800 Improve test-suite, merging in GHC tests >--------------------------------------------------------------- 02503a367d000f6b6d76db4ab238af134fdc92b8 pretty.cabal | 2 ++ tests/BugSep.hs | 3 +++ tests/T3911.hs | 23 ----------------- tests/T3911.stdout | 4 --- tests/Test.hs | 6 ++++- tests/TestUtils.hs | 19 ++++++++++++++ tests/UnitPP1.hs | 76 ++++++++++++++++++++++++++++++++++++++++++++++++++++++ tests/UnitT3911.hs | 25 ++++++++++++++++++ tests/all.T | 2 -- tests/pp1.hs | 18 ------------- tests/pp1.stdout | 4 --- 11 files changed, 130 insertions(+), 52 deletions(-) diff --git a/pretty.cabal b/pretty.cabal index e97ac11..104803e 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -49,6 +49,8 @@ Test-Suite test-pretty other-modules: TestGenerators TestStructures + UnitPP1 + UnitT3911 extensions: CPP, BangPatterns, DeriveGeneric include-dirs: src/Text/PrettyPrint diff --git a/tests/BugSep.hs b/tests/BugSep.hs index 2047480..fe16b80 100644 --- a/tests/BugSep.hs +++ b/tests/BugSep.hs @@ -1,3 +1,6 @@ +-- | Demonstration of ambiguity in HughesPJ library at this time. GHC's +-- internal copy has a different answer than we currently do, preventing them +-- using our library. module Main (main) where import Text.PrettyPrint.HughesPJ diff --git a/tests/T3911.hs b/tests/T3911.hs deleted file mode 100644 index 01ccb22..0000000 --- a/tests/T3911.hs +++ /dev/null @@ -1,23 +0,0 @@ - -module Main where - -import Text.PrettyPrint.HughesPJ - -xs :: [Doc] -xs = [text "hello", - nest 10 (text "world")] - -d1 :: Doc -d1 = vcat xs - -d2 :: Doc -d2 = foldr ($$) empty xs - -d3 :: Doc -d3 = foldr ($+$) empty xs - -main :: IO () -main = do print d1 - print d2 - print d3 - diff --git a/tests/T3911.stdout b/tests/T3911.stdout deleted file mode 100644 index 7677e8d..0000000 --- a/tests/T3911.stdout +++ /dev/null @@ -1,4 +0,0 @@ -hello world -hello world -hello - world diff --git a/tests/Test.hs b/tests/Test.hs index 51f659d..107e32a 100644 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -1,4 +1,3 @@ -{-# OPTIONS -XStandaloneDeriving -XDeriveDataTypeable -XPackageImports #-} ----------------------------------------------------------------------------- -- Module : HughesPJQuickCheck -- Copyright : (c) 2008 Benedikt Huber @@ -16,6 +15,9 @@ import PrettyTestVersion import TestGenerators import TestStructures +import UnitPP1 +import UnitT3911 + import Control.Monad import Data.Char (isSpace) import Data.List (intersperse) @@ -31,6 +33,8 @@ main = do check_non_prims -- hpc full coverage check_rendering check_list_def + testPP1 + testT3911 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- Utility functions diff --git a/tests/TestUtils.hs b/tests/TestUtils.hs new file mode 100644 index 0000000..24ef7c7 --- /dev/null +++ b/tests/TestUtils.hs @@ -0,0 +1,19 @@ +-- | Test-suite framework and utility functions. +module TestUtils ( + simpleMatch + ) where + +import Control.Monad +import System.Exit + +simpleMatch :: String -> String -> String -> IO () +simpleMatch test expected actual = + when (actual /= expected) $ do + putStrLn $ "Test `" ++ test ++ "' failed!" + putStrLn "-----------------------------" + putStrLn $ "Expected: " ++ expected + putStrLn "-----------------------------" + putStrLn $ "Actual: " ++ actual + putStrLn "-----------------------------" + exitFailure + diff --git a/tests/UnitPP1.hs b/tests/UnitPP1.hs new file mode 100644 index 0000000..31217c4 --- /dev/null +++ b/tests/UnitPP1.hs @@ -0,0 +1,76 @@ +-- This code used to print an infinite string, by calling 'spaces' +-- with a negative argument. There's a patch in the library now, +-- which makes 'spaces' do something sensible when called with a negative +-- argument, but it really should not happen at all. + +module UnitPP1 where + +import TestUtils + +import Text.PrettyPrint.HughesPJ + +ncat :: Doc -> Doc -> Doc +ncat x y = nest 4 $ cat [ x, y ] + +d1, d2 :: Doc +d1 = foldl1 ncat $ take 50 $ repeat $ char 'a' +d2 = parens $ sep [ d1, text "+" , d1 ] + +testPP1 :: IO () +testPP1 = simpleMatch "PP1" expected out + where out = show d2 + +expected :: String +expected = + "(aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa\n\ ++ a\n\ + a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a\n\ +a)" + diff --git a/tests/UnitT3911.hs b/tests/UnitT3911.hs new file mode 100644 index 0000000..39aa1e2 --- /dev/null +++ b/tests/UnitT3911.hs @@ -0,0 +1,25 @@ +module UnitT3911 where + +import Text.PrettyPrint.HughesPJ + +import TestUtils + +xs :: [Doc] +xs = [text "hello", + nest 10 (text "world")] + +d1, d2, d3 :: Doc +d1 = vcat xs +d2 = foldr ($$) empty xs +d3 = foldr ($+$) empty xs + +testT3911 :: IO () +testT3911 = simpleMatch "T3911" expected out + where out = show d1 ++ "\n" ++ show d2 ++ "\n" ++ show d3 + +expected :: String +expected = + "hello world\n\ +hello world\n\ +hello\n\ + world" diff --git a/tests/all.T b/tests/all.T deleted file mode 100644 index 81e2c73..0000000 --- a/tests/all.T +++ /dev/null @@ -1,2 +0,0 @@ -test('pp1', [expect_broken(1062), only_ways(['normal'])], compile_and_run, ['']) -test('T3911', normal, compile_and_run, ['']) diff --git a/tests/pp1.hs b/tests/pp1.hs deleted file mode 100644 index 384d565..0000000 --- a/tests/pp1.hs +++ /dev/null @@ -1,18 +0,0 @@ --- This code used to print an infinite string, by calling 'spaces' --- with a negative argument. There's a patch in the library now, --- which makes 'spaces' do something sensible when called with a negative --- argument, but it really should not happen at all. - - -module Main where - -import Text.PrettyPrint.HughesPJ - - -ncat x y = nest 4 $ cat [ x, y ] - -d1 = foldl1 ncat $ take 50 $ repeat $ char 'a' -d2 = parens $ sep [ d1, text "+" , d1 ] - -main = print d2 - diff --git a/tests/pp1.stdout b/tests/pp1.stdout deleted file mode 100644 index 6915311..0000000 --- a/tests/pp1.stdout +++ /dev/null @@ -1,4 +0,0 @@ -This output is not what is expected, becuase the -test "works" now, by virtue of a hack in HughesPJ.spaces. -I'm leaving this strange output here to remind us to look -at the root cause of the problem. Sometime. \ No newline at end of file From git at git.haskell.org Fri Jan 23 22:49:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:49:58 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: Fix compilation under GHC 7.10 (04ca57e) Message-ID: <20150123224958.6A0A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/04ca57e32ac6474fbbdcf7f0a8dcd4ba8396fa89 >--------------------------------------------------------------- commit 04ca57e32ac6474fbbdcf7f0a8dcd4ba8396fa89 Author: David Terei Date: Fri Dec 26 00:01:42 2014 -0800 Fix compilation under GHC 7.10 >--------------------------------------------------------------- 04ca57e32ac6474fbbdcf7f0a8dcd4ba8396fa89 src/Text/PrettyPrint/HughesPJ.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index aac7de0..6646b38 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -79,7 +79,9 @@ module Text.PrettyPrint.HughesPJ ( import Control.DeepSeq ( NFData(rnf) ) import Data.Function ( on ) -import Data.Monoid ( Monoid(mempty, mappend) ) +#if __GLASGOW_HASKELL__ < 709 +import Data.Monoid ( Monoid(mempty, mappend) ) +#endif import Data.String ( IsString(fromString) ) import GHC.Generics From git at git.haskell.org Fri Jan 23 22:50:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:50:00 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: Update changelog (8be7d73) Message-ID: <20150123225000.6F7213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/8be7d73450deb55056719e35185063244a35ec57 >--------------------------------------------------------------- commit 8be7d73450deb55056719e35185063244a35ec57 Author: David Terei Date: Thu Dec 25 02:18:43 2014 -0800 Update changelog >--------------------------------------------------------------- 8be7d73450deb55056719e35185063244a35ec57 CHANGELOG.md | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 2195744..5cb8069 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,5 +1,12 @@ # Pretty library change log +## 1.1.2.0 -- 25th December, 2014 + +* Merge in prettyclass package -- new Text.PrettyPrint.HughesPHClass. +* Add in 'maybe\*' variants of various bracket functins. +* Add Generic instances for appropriate data types. +* Fix compilation under GHC 7.10 + ## 1.1.1.3 -- 21st December, 2014 * Remove upper bound on `deepseq` package to fix build issues with From git at git.haskell.org Fri Jan 23 22:50:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:50:02 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: Bump to version 1.1.2.0 (7eb7c6c) Message-ID: <20150123225002.7586E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/7eb7c6c01be4596da3dae9ca57d8adac37cc33fc >--------------------------------------------------------------- commit 7eb7c6c01be4596da3dae9ca57d8adac37cc33fc Author: David Terei Date: Wed Dec 24 15:31:31 2014 -0800 Bump to version 1.1.2.0 >--------------------------------------------------------------- 7eb7c6c01be4596da3dae9ca57d8adac37cc33fc pretty.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pretty.cabal b/pretty.cabal index 104803e..c763e25 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -1,5 +1,5 @@ name: pretty -version: 1.1.1.3 +version: 1.1.2.0 synopsis: Pretty-printing library description: This package contains a pretty-printing library, a set of API's From git at git.haskell.org Fri Jan 23 22:50:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:50:04 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: Add failing test for large vcat (dfc5ff9) Message-ID: <20150123225004.7D0A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/dfc5ff937a8cf27a55d0dfe236ff0cea61b22d00 >--------------------------------------------------------------- commit dfc5ff937a8cf27a55d0dfe236ff0cea61b22d00 Author: Eyal Lotem Date: Fri Jun 28 18:13:45 2013 +0300 Add failing test for large vcat >--------------------------------------------------------------- dfc5ff937a8cf27a55d0dfe236ff0cea61b22d00 pretty.cabal | 1 + tests/Test.hs | 13 +++++++++++++ tests/TestLargePretty.hs | 7 +++++++ 3 files changed, 21 insertions(+) diff --git a/pretty.cabal b/pretty.cabal index c763e25..5bb9b70 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -51,6 +51,7 @@ Test-Suite test-pretty TestStructures UnitPP1 UnitT3911 + TestLargePretty extensions: CPP, BangPatterns, DeriveGeneric include-dirs: src/Text/PrettyPrint diff --git a/tests/Test.hs b/tests/Test.hs index 107e32a..dda582a 100644 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -14,10 +14,12 @@ import PrettyTestVersion import TestGenerators import TestStructures +import TestLargePretty import UnitPP1 import UnitT3911 +import Control.Exception import Control.Monad import Data.Char (isSpace) import Data.List (intersperse) @@ -27,6 +29,7 @@ import Test.QuickCheck main :: IO () main = do + large_doc check_laws check_invariants check_improvements @@ -62,6 +65,16 @@ myAssert :: String -> Bool -> IO () myAssert msg b = putStrLn $ (if b then "Ok, passed " else "Failed test:\n ") ++ msg -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- Ordinary tests +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +large_doc :: IO () +large_doc = do + putStrLn "Testing large doc..." + evaluate largeDocRender + return () + +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- Quickcheck tests -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/tests/TestLargePretty.hs b/tests/TestLargePretty.hs new file mode 100644 index 0000000..6d181c4 --- /dev/null +++ b/tests/TestLargePretty.hs @@ -0,0 +1,7 @@ +module TestLargePretty where + +import Text.PrettyPrint +import Control.DeepSeq + +largeDocRender :: String +largeDocRender = force $ render $ vcat $ replicate 10000000 $ text "Hello" From git at git.haskell.org Fri Jan 23 22:50:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:50:06 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: Resolve foldr-strictness stack overflow bug (307b817) Message-ID: <20150123225006.842B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/307b8173f41cd776eae8f547267df6d72bff2d68 >--------------------------------------------------------------- commit 307b8173f41cd776eae8f547267df6d72bff2d68 Author: Eyal Lotem Date: Fri Jun 28 23:03:21 2013 +0300 Resolve foldr-strictness stack overflow bug >--------------------------------------------------------------- 307b8173f41cd776eae8f547267df6d72bff2d68 src/Text/PrettyPrint/HughesPJ.hs | 43 +++++++++++++++++++++++++++------------- 1 file changed, 29 insertions(+), 14 deletions(-) diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index 6646b38..f3f3bc2 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -433,15 +433,15 @@ reduceDoc p = p -- | List version of '<>'. hcat :: [Doc] -> Doc -hcat = reduceAB . foldr (beside_' False) empty +hcat = reduceAB . foldr (\p q -> Beside p False q) empty -- | List version of '<+>'. hsep :: [Doc] -> Doc -hsep = reduceAB . foldr (beside_' True) empty +hsep = reduceAB . foldr (\p q -> Beside p True q) empty -- | List version of '$$'. vcat :: [Doc] -> Doc -vcat = reduceAB . foldr (above_' False) empty +vcat = reduceAB . foldr (\p q -> Above p False q) empty -- | Nest (or indent) a document by a given number of positions -- (which may also be negative). 'nest' satisfies the laws: @@ -488,18 +488,33 @@ mkUnion :: Doc -> Doc -> Doc mkUnion Empty _ = Empty mkUnion p q = p `union_` q -beside_' :: Bool -> Doc -> Doc -> Doc -beside_' _ p Empty = p -beside_' g p q = Beside p g q - -above_' :: Bool -> Doc -> Doc -> Doc -above_' _ p Empty = p -above_' g p q = Above p g q - reduceAB :: Doc -> Doc -reduceAB (Above Empty _ q) = q -reduceAB (Beside Empty _ q) = q -reduceAB doc = doc +reduceAB = snd . reduceAB' + +data IsEmpty = IsEmpty | NotEmpty + +reduceAB' :: Doc -> (IsEmpty, Doc) +reduceAB' (Above p g q) = eliminateEmpty Above (reduceAB p) g (reduceAB' q) +reduceAB' (Beside p g q) = eliminateEmpty Beside (reduceAB p) g (reduceAB' q) +reduceAB' doc = (NotEmpty, doc) + +-- Left-arg-strict +eliminateEmpty :: + (Doc -> Bool -> Doc -> Doc) -> + Doc -> Bool -> (IsEmpty, Doc) -> (IsEmpty, Doc) +eliminateEmpty _ Empty _ q = q +eliminateEmpty cons p g q = + (NotEmpty, + -- We're not empty whether or not q is empty, so for laziness-sake, + -- after checking that p isn't empty, we put the NotEmpty result + -- outside independent of q. This allows reduceAB to immediately + -- return the appropriate constructor (Above or Beside) without + -- forcing the entire nested Doc. This allows the foldr in vcat, + -- hsep, and hcat to be lazy on its second argument, avoiding a + -- stack overflow. + case q of + (NotEmpty, q') -> cons p g q' + (IsEmpty, _) -> p) nilAbove_ :: RDoc -> RDoc nilAbove_ = NilAbove From git at git.haskell.org Fri Jan 23 22:50:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:50:08 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: Put large_doc test (slowest) last (9ebd518) Message-ID: <20150123225008.89B263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/9ebd5188f88000f37beeca4e668fa42ba798d6d0 >--------------------------------------------------------------- commit 9ebd5188f88000f37beeca4e668fa42ba798d6d0 Author: Eyal Lotem Date: Tue Jul 2 02:37:45 2013 +0300 Put large_doc test (slowest) last >--------------------------------------------------------------- 9ebd5188f88000f37beeca4e668fa42ba798d6d0 tests/Test.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/Test.hs b/tests/Test.hs index dda582a..f9cb025 100644 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -29,7 +29,6 @@ import Test.QuickCheck main :: IO () main = do - large_doc check_laws check_invariants check_improvements @@ -38,6 +37,7 @@ main = do check_list_def testPP1 testT3911 + large_doc -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- Utility functions From git at git.haskell.org Fri Jan 23 22:50:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:50:10 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: Special-case reduce for horiz/vert (c57c7a9) Message-ID: <20150123225010.901653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/c57c7a9dfc49617ba8d6e4fcdb019a3f29f1044c >--------------------------------------------------------------- commit c57c7a9dfc49617ba8d6e4fcdb019a3f29f1044c Author: Eyal Lotem Date: Tue Jul 2 02:36:31 2013 +0300 Special-case reduce for horiz/vert >--------------------------------------------------------------- c57c7a9dfc49617ba8d6e4fcdb019a3f29f1044c src/Text/PrettyPrint/HughesPJ.hs | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index f3f3bc2..c45f691 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -433,15 +433,15 @@ reduceDoc p = p -- | List version of '<>'. hcat :: [Doc] -> Doc -hcat = reduceAB . foldr (\p q -> Beside p False q) empty +hcat = snd . reduceHoriz . foldr (\p q -> Beside p False q) empty -- | List version of '<+>'. hsep :: [Doc] -> Doc -hsep = reduceAB . foldr (\p q -> Beside p True q) empty +hsep = snd . reduceHoriz . foldr (\p q -> Beside p True q) empty -- | List version of '$$'. vcat :: [Doc] -> Doc -vcat = reduceAB . foldr (\p q -> Above p False q) empty +vcat = snd . reduceVert . foldr (\p q -> Above p False q) empty -- | Nest (or indent) a document by a given number of positions -- (which may also be negative). 'nest' satisfies the laws: @@ -488,17 +488,17 @@ mkUnion :: Doc -> Doc -> Doc mkUnion Empty _ = Empty mkUnion p q = p `union_` q -reduceAB :: Doc -> Doc -reduceAB = snd . reduceAB' - data IsEmpty = IsEmpty | NotEmpty -reduceAB' :: Doc -> (IsEmpty, Doc) -reduceAB' (Above p g q) = eliminateEmpty Above (reduceAB p) g (reduceAB' q) -reduceAB' (Beside p g q) = eliminateEmpty Beside (reduceAB p) g (reduceAB' q) -reduceAB' doc = (NotEmpty, doc) +reduceHoriz :: Doc -> (IsEmpty, Doc) +reduceHoriz (Beside p g q) = eliminateEmpty Beside (snd (reduceHoriz p)) g (reduceHoriz q) +reduceHoriz doc = (NotEmpty, doc) + +reduceVert :: Doc -> (IsEmpty, Doc) +reduceVert (Above p g q) = eliminateEmpty Above (snd (reduceVert p)) g (reduceVert q) +reduceVert doc = (NotEmpty, doc) --- Left-arg-strict +{-# INLINE eliminateEmpty #-} eliminateEmpty :: (Doc -> Bool -> Doc -> Doc) -> Doc -> Bool -> (IsEmpty, Doc) -> (IsEmpty, Doc) From git at git.haskell.org Fri Jan 23 22:50:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:50:12 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: Improve bench1 cabal support (0a0b534) Message-ID: <20150123225012.96FCB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/0a0b534375372cac74265a0939c32a1e297a28af >--------------------------------------------------------------- commit 0a0b534375372cac74265a0939c32a1e297a28af Author: David Terei Date: Fri Dec 26 00:21:41 2014 -0800 Improve bench1 cabal support >--------------------------------------------------------------- 0a0b534375372cac74265a0939c32a1e297a28af pretty.cabal | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/pretty.cabal b/pretty.cabal index 5bb9b70..1109617 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -57,11 +57,8 @@ Test-Suite test-pretty -- Executable Bench1 -- main-is: Bench1.hs --- hs-source-dirs: test --- src --- other-modules: --- Text.PrettyPrint --- Text.PrettyPrint.HughesPJ --- extensions: CPP, BangPatterns +-- build-depends: base >= 3 && < 5, +-- pretty +-- hs-source-dirs: tests -- ghc-options: -O -fwarn-tabs From git at git.haskell.org Fri Jan 23 22:50:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:50:14 +0000 (UTC) Subject: [commit: packages/pretty] large_docs: Clean up UnitLargeDoc style to be like rest of test-suite (b036410) Message-ID: <20150123225014.9D0883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : large_docs Link : http://git.haskell.org/packages/pretty.git/commitdiff/b0364100bf58126dfe34715843102b27850d8f36 >--------------------------------------------------------------- commit b0364100bf58126dfe34715843102b27850d8f36 Author: David Terei Date: Fri Dec 26 00:26:42 2014 -0800 Clean up UnitLargeDoc style to be like rest of test-suite >--------------------------------------------------------------- b0364100bf58126dfe34715843102b27850d8f36 pretty.cabal | 2 +- tests/Test.hs | 18 +++++------------- tests/TestLargePretty.hs | 7 ------- tests/UnitLargeDoc.hs | 16 ++++++++++++++++ 4 files changed, 22 insertions(+), 21 deletions(-) diff --git a/pretty.cabal b/pretty.cabal index 1109617..8b81005 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -51,7 +51,7 @@ Test-Suite test-pretty TestStructures UnitPP1 UnitT3911 - TestLargePretty + UnitLargeDoc extensions: CPP, BangPatterns, DeriveGeneric include-dirs: src/Text/PrettyPrint diff --git a/tests/Test.hs b/tests/Test.hs index f9cb025..79e5a49 100644 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -14,12 +14,11 @@ import PrettyTestVersion import TestGenerators import TestStructures -import TestLargePretty +import UnitLargeDoc import UnitPP1 import UnitT3911 -import Control.Exception import Control.Monad import Data.Char (isSpace) import Data.List (intersperse) @@ -29,15 +28,18 @@ import Test.QuickCheck main :: IO () main = do + -- quickcheck tests check_laws check_invariants check_improvements check_non_prims -- hpc full coverage check_rendering check_list_def + + -- unit tests testPP1 testT3911 - large_doc + testLargeDoc -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- Utility functions @@ -65,16 +67,6 @@ myAssert :: String -> Bool -> IO () myAssert msg b = putStrLn $ (if b then "Ok, passed " else "Failed test:\n ") ++ msg -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --- Ordinary tests --- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - -large_doc :: IO () -large_doc = do - putStrLn "Testing large doc..." - evaluate largeDocRender - return () - --- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- Quickcheck tests -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/tests/TestLargePretty.hs b/tests/TestLargePretty.hs deleted file mode 100644 index 6d181c4..0000000 --- a/tests/TestLargePretty.hs +++ /dev/null @@ -1,7 +0,0 @@ -module TestLargePretty where - -import Text.PrettyPrint -import Control.DeepSeq - -largeDocRender :: String -largeDocRender = force $ render $ vcat $ replicate 10000000 $ text "Hello" diff --git a/tests/UnitLargeDoc.hs b/tests/UnitLargeDoc.hs new file mode 100644 index 0000000..5a44f34 --- /dev/null +++ b/tests/UnitLargeDoc.hs @@ -0,0 +1,16 @@ +module UnitLargeDoc where + +import Text.PrettyPrint.HughesPJ + +import Control.DeepSeq +import Control.Exception + +testLargeDoc :: IO () +testLargeDoc = do + putStrLn "Testing large doc..." + evaluate largeDocRender + return () + +largeDocRender :: String +largeDocRender = force $ render $ vcat $ replicate 10000000 $ text "Hello" + From git at git.haskell.org Fri Jan 23 22:50:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:50:16 +0000 (UTC) Subject: [commit: packages/pretty] master's head updated: fix missing ghc-prim package (a2e79da) Message-ID: <20150123225016.C07FA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty Branch 'master' now includes: 2b7db89 add tood note 0b8eada Remove use of compose from the testsuite driver b419701 Tweak tests definition; no functional change c5c8fd3 Merge branch 'master' of git://github.com/haskell/pretty into ghc-head 01c724b Bump version to 1.1.1.1 and update bug-reports URL bf3cbed Fix tests for latest quickcheck. 110b105 Update pretty cabal file, readme and changelog for 1.1.1.1. 2c41eb0 Fix paper link. 3e9c0ea Add NFData and Eq instances 3ca7e48 Merge pull request #13 from ivan-m/add_instances 84edff6 add travis support 59a1c1d update travis config 2832850 update readme to include badges 334adf8 fixes to hackage badge in readme 9799d77 tweaks to travis ci 5c0f0fa change doc wording for `ribbonsPerLine` (#14) 5e45854 remove bounds on deepseq (fixes #15) 6190328 Fix cabal build issue with test-suite ab82211 add cabal sandbox to gitignore cbbd53a Fixes to travis and have travis run test-suite cd1c995 add back in lost 1.1.1.2 release notes c59e1df make 1.1.1.3 release 29792d6 More fixes to travis ci 0e24600 update readme to reflect use of branches in git 95bbc32 Remove incorrect 'version 4' entry from changelog 14a0117 Update maintainer email in source code a964141 Merge in prettyclass package as useful to have in core 4badfbd Add 'maybe*' variants to all bracketing functions 314b743 Bump to version 1.1.2.0 6883fda add minimal pragma to pretty class 428e3f7 add Generic instance to Doc ac1b41a fix hslint warnings a7db5b5 Add appropriate Show, Eq and Generic instances a2e79da fix missing ghc-prim package From git at git.haskell.org Fri Jan 23 22:52:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:23 +0000 (UTC) Subject: [commit: packages/time] branch 'ghc-7.8' created Message-ID: <20150123225223.28B963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time New branch : ghc-7.8 Referencing: adafac26307cffab0be20c126385ab161c259237 From git at git.haskell.org Fri Jan 23 22:52:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:25 +0000 (UTC) Subject: [commit: packages/time] branch 'ghc-head' deleted Message-ID: <20150123225225.28C2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time Deleted branch: ghc-head From git at git.haskell.org Fri Jan 23 22:52:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:27 +0000 (UTC) Subject: [commit: packages/time] branch 'ezyang-scrap' deleted Message-ID: <20150123225227.299653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time Deleted branch: ezyang-scrap From git at git.haskell.org Fri Jan 23 22:52:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:29 +0000 (UTC) Subject: [commit: packages/time] tag 'time-1.5.0.1-release' created Message-ID: <20150123225229.2ACB93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time New tag : time-1.5.0.1-release Referencing: 02aa59816ac87af9623752937ce2cb6ddbd7eb98 From git at git.haskell.org Fri Jan 23 22:52:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:31 +0000 (UTC) Subject: [commit: packages/time] master: initial revision, including draft of Clock and outlines of TAI and Calendar (239f07b) Message-ID: <20150123225231.35DAF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/239f07b42ef31a05b9b3894dc656620c8699cc9b >--------------------------------------------------------------- commit 239f07b42ef31a05b9b3894dc656620c8699cc9b Author: Ashley Yakeley Date: Tue Feb 22 21:19:59 2005 -0800 initial revision, including draft of Clock and outlines of TAI and Calendar darcs-hash:20050223051959-ac6dd-ea6ff7c56b81deaffc2584a3a196a8e6262805d9 >--------------------------------------------------------------- 239f07b42ef31a05b9b3894dc656620c8699cc9b Makefile | 30 +++++++++++++ System/Time/Calendar.hs | 61 +++++++++++++++++++++++++ System/Time/Clock.hs | 116 ++++++++++++++++++++++++++++++++++++++++++++++++ System/Time/TAI.hs | 33 ++++++++++++++ TestTime.hs | 11 +++++ 5 files changed, 251 insertions(+) diff --git a/Makefile b/Makefile new file mode 100644 index 0000000..4a6709f --- /dev/null +++ b/Makefile @@ -0,0 +1,30 @@ +default: TestTime.run + +#TestTime: TestTime.o System/Time/Clock.o System/Time/TAI.o System/Time/Calendar.o +TestTime: TestTime.o System/Time/Clock.o + ghc $^ -o $@ + + +clean: + rm -f TestTime *.o *.hi System/Time/*.o System/Time/*.hi Makefile.bak + + +%.run: % + ./$< + +%.hi: %.o + @: + +%.o: %.hs + ghc -c $< -o $@ + +depend: TestTime.hs System/Time/Clock.hs System/Time/TAI.hs System/Time/Calendar.hs + ghc -M $^ +# DO NOT DELETE: Beginning of Haskell dependencies +TestTime.o : TestTime.hs +TestTime.o : ./System/Time/Clock.hi +System/Time/Clock.o : System/Time/Clock.hs +System/Time/TAI.o : System/Time/TAI.hs +System/Time/TAI.o : System/Time/Clock.hi +System/Time/Calendar.o : System/Time/Calendar.hs +# DO NOT DELETE: End of Haskell dependencies diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs new file mode 100644 index 0000000..944f4fb --- /dev/null +++ b/System/Time/Calendar.hs @@ -0,0 +1,61 @@ +module System.Time.Calendar +( + -- time zones + TimeZone, + + -- getting the locale time zone + + -- converting times to Gregorian "calendrical" format + TimeOfDay,CalendarDay,CalendarTime + + -- calendrical arithmetic + -- e.g. "one month after March 31st" + + -- parsing and showing dates and times +) where + +-- | count of minutes +newtype TimeZone = MkTimeZone Int deriving (Eq,Ord,Num) + + +data TimeOfDay = TimeOfDay +{ + todHour :: Int, + todMin :: Int, + todSec :: Int, + todPicosec :: Integer +} deriving (Eq,Ord) + +instance Show TimeOfDay where + show (TimeOfDay h m s ps) = + +data CalendarDay = CalendarDay +{ + cdYear :: Integer, + cdMonth :: Int, + cdDay :: Int +} deriving (Eq,Ord) + +data CalendarTime = CalendarTime +{ + ctDay :: CalendarDay, + ctTime :: TimeOfDay +} deriving (Eq,Ord) + + + +-- ((365 * 3 + 366) * 24 + 365 * 4) * 3 + (365 * 3 + 366) * 25 +dayToCalendar :: ModJulianDay -> CalendarDay +dayToCalendar mjd = let + a = mjd + 2000 -- ? + quadcent = a / 146097 + b = a % 146097 + cent = min (b / 36524) 3 + ...to be continued + + +utcToCalendar :: TimeZone -> UTCTime -> CalendarTime + +calendarToUTC :: TimeZone -> CalendarTime -> UTCTime + + diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs new file mode 100644 index 0000000..386c920 --- /dev/null +++ b/System/Time/Clock.hs @@ -0,0 +1,116 @@ +{-# OPTIONS -ffi #-} + +module System.Time.Clock +( + -- Modified Julian days and dates (for UT1) + ModJulianDay,ModJulianDate, + + -- absolute time intervals + DiffTime,timeToSISeconds,siSecondsToTime, + + -- UTC arithmetic + UTCTime(..),UTCDiffTime,utcTimeToUTCSeconds,utcSecondsToUTCTime, + + -- getting the current UTC time + getCurrentTime +) where + +import Foreign +import Foreign.C + +-- | standard Julian count of Earth days +type ModJulianDay = Integer + +-- | standard Julian dates for UT1, 1 = 1 day +type ModJulianDate = Rational + +secondPicoseconds :: (Num a) => a +secondPicoseconds = 1000000000000 + +newtype DiffTime = MkDiffTime Integer deriving (Eq,Ord,Show) + +timeToSIPicoseconds :: DiffTime -> Integer +timeToSIPicoseconds (MkDiffTime ps) = ps + +siPicosecondsToTime :: Integer -> DiffTime +siPicosecondsToTime = MkDiffTime + +timeToSISeconds :: (Fractional a) => DiffTime -> a +timeToSISeconds t = fromRational ((toRational (timeToSIPicoseconds t)) / (toRational secondPicoseconds)); + +siSecondsToTime :: (Real a) => a -> DiffTime +siSecondsToTime t = siPicosecondsToTime (round ((toRational t) * secondPicoseconds)) + +data UTCTime = UTCTime { + utctDay :: ModJulianDay, + utctDayTime :: DiffTime +} + +newtype UTCDiffTime = MkUTCDiffTime Integer + +utcTimeToUTCPicoseconds :: UTCDiffTime -> Integer +utcTimeToUTCPicoseconds (MkUTCDiffTime ps) = ps + +utcPicosecondsToUTCTime :: Integer -> UTCDiffTime +utcPicosecondsToUTCTime = MkUTCDiffTime + +utcTimeToUTCSeconds :: (Fractional a) => UTCDiffTime -> a +utcTimeToUTCSeconds t = fromRational ((toRational (utcTimeToUTCPicoseconds t)) / (toRational secondPicoseconds)) + +utcSecondsToUTCTime :: (Real a) => a -> UTCDiffTime +utcSecondsToUTCTime t = utcPicosecondsToUTCTime (round ((toRational t) * secondPicoseconds)) + +posixDaySeconds :: (Num a) => a +posixDaySeconds = 86400 + +posixDayPicoseconds :: Integer +posixDayPicoseconds = posixDaySeconds * secondPicoseconds + +unixEpochMJD :: ModJulianDay +unixEpochMJD = 40587 + +posixPicosecondsToUTCTime :: Integer -> UTCTime +posixPicosecondsToUTCTime i = let + (d,t) = divMod i posixDayPicoseconds + in UTCTime (d + unixEpochMJD) (siPicosecondsToTime t) + +utcTimeToPOSIXPicoseconds :: UTCTime -> Integer +utcTimeToPOSIXPicoseconds (UTCTime d t) = + ((d - unixEpochMJD) * posixDayPicoseconds) + min posixDayPicoseconds (timeToSIPicoseconds t) + +addUTCTime :: UTCDiffTime -> UTCTime -> UTCTime +addUTCTime x t = posixPicosecondsToUTCTime ((utcTimeToUTCPicoseconds x) + (utcTimeToPOSIXPicoseconds t)) + +diffUTCTime :: UTCTime -> UTCTime -> UTCDiffTime +diffUTCTime a b = utcPicosecondsToUTCTime ((utcTimeToPOSIXPicoseconds a) - (utcTimeToPOSIXPicoseconds b)) + + +-- Get current time + +data CTimeval = MkCTimeval CLong CLong + +ctimevalToPosixPicoseconds :: CTimeval -> Integer +ctimevalToPosixPicoseconds (MkCTimeval s mus) = ((fromIntegral s) * 1000000 + (fromIntegral mus)) * 1000000 + +instance Storable CTimeval where + sizeOf _ = (sizeOf (undefined :: CLong)) * 2 + alignment _ = alignment (undefined :: CLong) + peek p = do + s <- peekElemOff (castPtr p) 0 + mus <- peekElemOff (castPtr p) 1 + return (MkCTimeval s mus) + poke p (MkCTimeval s mus) = do + pokeElemOff (castPtr p) 0 s + pokeElemOff (castPtr p) 1 mus + +foreign import ccall unsafe "sys/time.h gettimeofday" gettimeofday :: Ptr CTimeval -> Ptr () -> IO CInt + +getCurrentTime :: IO UTCTime +getCurrentTime = with (MkCTimeval 0 0) (\ptval -> do + result <- gettimeofday ptval nullPtr + if (result == 0) + then do + tval <- peek ptval + return (posixPicosecondsToUTCTime (ctimevalToPosixPicoseconds tval)) + else fail ("error in gettimeofday: " ++ (show result)) + ) diff --git a/System/Time/TAI.hs b/System/Time/TAI.hs new file mode 100644 index 0000000..fb5df5a --- /dev/null +++ b/System/Time/TAI.hs @@ -0,0 +1,33 @@ +-- | most people won't need this module +module System.Time.TAI +( + -- TAI arithmetic + AbsoluteTime,addAbsoluteTime,diffAbsoluteTime, + + -- leap-second table type + LeapSecondTable, + + -- conversion between UTC and TAI with table + utcDayLength,utcToTAITime,taiToUTCTime +) where + +import System.Time.Clock + +-- | TAI +type AbsoluteTime = MkAbsoluteTime Integer + +addAbsoluteTime :: DiffTime -> AbsoluteTime -> AbsoluteTime + +diffAbsoluteTime :: AbsoluteTime -> AbsoluteTime -> DiffTime + +-- | TAI - UTC during this day +type LeapSecondTable = ModJulianDay -> Int + +utcDayLength :: LeapSecondTable -> ModJulianDay -> DiffTime +utcDayLength table day = siSecondsToTime (86400 + (table (day + 1)) - (table day)) + +utcToTAITime :: LeapSecondTable -> UTCTime -> TAITime +utcToTAITime table (UTCTime day dtime) = siSecondsToTime (table day) + + +taiToUTCTime :: LeapSecondTable -> TAITime -> UTCTime + diff --git a/TestTime.hs b/TestTime.hs new file mode 100644 index 0000000..77dff58 --- /dev/null +++ b/TestTime.hs @@ -0,0 +1,11 @@ +module Main where + +import System.Time.Clock +--import System.Time.TAI +--import System.Time.Calendar + +main :: IO () +main = do + now <- getCurrentTime + putStrLn (show (utctDay now) ++ "," ++ show (utctDayTime now)) +-- putStrLn (show (utcToCalendar (60 * -8) now)) From git at git.haskell.org Fri Jan 23 22:52:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:33 +0000 (UTC) Subject: [commit: packages/time] master: make diff times instances of Num (7339f64) Message-ID: <20150123225233.3C5BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/7339f6490cd349867b5cb93d8a59f31a4a92c9cd >--------------------------------------------------------------- commit 7339f6490cd349867b5cb93d8a59f31a4a92c9cd Author: Ashley Yakeley Date: Wed Feb 23 02:28:59 2005 -0800 make diff times instances of Num darcs-hash:20050223102859-ac6dd-24d8169a3ff6da7e55dc008515c04dc56e5e902d >--------------------------------------------------------------- 7339f6490cd349867b5cb93d8a59f31a4a92c9cd System/Time/Clock.hs | 36 +++++++++++++++--------------------- 1 file changed, 15 insertions(+), 21 deletions(-) diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs index 386c920..628a627 100644 --- a/System/Time/Clock.hs +++ b/System/Time/Clock.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -ffi #-} +{-# OPTIONS -ffi -fglasgow-exts #-} module System.Time.Clock ( @@ -27,38 +27,32 @@ type ModJulianDate = Rational secondPicoseconds :: (Num a) => a secondPicoseconds = 1000000000000 -newtype DiffTime = MkDiffTime Integer deriving (Eq,Ord,Show) +newtype DiffTime = MkDiffTime Integer deriving (Eq,Ord,Num,Enum,Real,Integral) -timeToSIPicoseconds :: DiffTime -> Integer -timeToSIPicoseconds (MkDiffTime ps) = ps - -siPicosecondsToTime :: Integer -> DiffTime -siPicosecondsToTime = MkDiffTime +instance Show DiffTime where + show (MkDiffTime t) = (show t) ++ "ps" timeToSISeconds :: (Fractional a) => DiffTime -> a -timeToSISeconds t = fromRational ((toRational (timeToSIPicoseconds t)) / (toRational secondPicoseconds)); +timeToSISeconds t = fromRational ((toRational t) / (toRational secondPicoseconds)); siSecondsToTime :: (Real a) => a -> DiffTime -siSecondsToTime t = siPicosecondsToTime (round ((toRational t) * secondPicoseconds)) +siSecondsToTime t = fromInteger (round ((toRational t) * secondPicoseconds)) data UTCTime = UTCTime { utctDay :: ModJulianDay, utctDayTime :: DiffTime } -newtype UTCDiffTime = MkUTCDiffTime Integer - -utcTimeToUTCPicoseconds :: UTCDiffTime -> Integer -utcTimeToUTCPicoseconds (MkUTCDiffTime ps) = ps +newtype UTCDiffTime = MkUTCDiffTime Integer deriving (Eq,Ord,Num,Enum,Real,Integral) -utcPicosecondsToUTCTime :: Integer -> UTCDiffTime -utcPicosecondsToUTCTime = MkUTCDiffTime +instance Show UTCDiffTime where + show (MkUTCDiffTime t) = (show t) ++ "ps" utcTimeToUTCSeconds :: (Fractional a) => UTCDiffTime -> a -utcTimeToUTCSeconds t = fromRational ((toRational (utcTimeToUTCPicoseconds t)) / (toRational secondPicoseconds)) +utcTimeToUTCSeconds t = fromRational ((toRational t) / (toRational secondPicoseconds)) utcSecondsToUTCTime :: (Real a) => a -> UTCDiffTime -utcSecondsToUTCTime t = utcPicosecondsToUTCTime (round ((toRational t) * secondPicoseconds)) +utcSecondsToUTCTime t = fromInteger (round ((toRational t) * secondPicoseconds)) posixDaySeconds :: (Num a) => a posixDaySeconds = 86400 @@ -72,17 +66,17 @@ unixEpochMJD = 40587 posixPicosecondsToUTCTime :: Integer -> UTCTime posixPicosecondsToUTCTime i = let (d,t) = divMod i posixDayPicoseconds - in UTCTime (d + unixEpochMJD) (siPicosecondsToTime t) + in UTCTime (d + unixEpochMJD) (fromInteger t) utcTimeToPOSIXPicoseconds :: UTCTime -> Integer utcTimeToPOSIXPicoseconds (UTCTime d t) = - ((d - unixEpochMJD) * posixDayPicoseconds) + min posixDayPicoseconds (timeToSIPicoseconds t) + ((d - unixEpochMJD) * posixDayPicoseconds) + min posixDayPicoseconds (toInteger t) addUTCTime :: UTCDiffTime -> UTCTime -> UTCTime -addUTCTime x t = posixPicosecondsToUTCTime ((utcTimeToUTCPicoseconds x) + (utcTimeToPOSIXPicoseconds t)) +addUTCTime x t = posixPicosecondsToUTCTime ((toInteger x) + (utcTimeToPOSIXPicoseconds t)) diffUTCTime :: UTCTime -> UTCTime -> UTCDiffTime -diffUTCTime a b = utcPicosecondsToUTCTime ((utcTimeToPOSIXPicoseconds a) - (utcTimeToPOSIXPicoseconds b)) +diffUTCTime a b = fromInteger ((utcTimeToPOSIXPicoseconds a) - (utcTimeToPOSIXPicoseconds b)) -- Get current time From git at git.haskell.org Fri Jan 23 22:52:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:35 +0000 (UTC) Subject: [commit: packages/time] master: export addUTCTime and diffUTCTime (3dfb0c3) Message-ID: <20150123225235.430723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3dfb0c35e8d9936bfab73a57a07bd1fcf5a70d04 >--------------------------------------------------------------- commit 3dfb0c35e8d9936bfab73a57a07bd1fcf5a70d04 Author: Ashley Yakeley Date: Wed Feb 23 02:35:17 2005 -0800 export addUTCTime and diffUTCTime darcs-hash:20050223103517-ac6dd-7c644aba8ebbe04a96df851aef01d33e1692adfc >--------------------------------------------------------------- 3dfb0c35e8d9936bfab73a57a07bd1fcf5a70d04 System/Time/Clock.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs index 628a627..9f59a8c 100644 --- a/System/Time/Clock.hs +++ b/System/Time/Clock.hs @@ -10,6 +10,7 @@ module System.Time.Clock -- UTC arithmetic UTCTime(..),UTCDiffTime,utcTimeToUTCSeconds,utcSecondsToUTCTime, + addUTCTime,diffUTCTime, -- getting the current UTC time getCurrentTime From git at git.haskell.org Fri Jan 23 22:52:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:37 +0000 (UTC) Subject: [commit: packages/time] master: get TAI to compile (cf576d3) Message-ID: <20150123225237.48EFE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/cf576d323e605122b337c64327ca047c999c7454 >--------------------------------------------------------------- commit cf576d323e605122b337c64327ca047c999c7454 Author: Ashley Yakeley Date: Wed Feb 23 02:48:25 2005 -0800 get TAI to compile darcs-hash:20050223104825-ac6dd-0a3e7a4109ecca08fb312f83deca2257b815310e >--------------------------------------------------------------- cf576d323e605122b337c64327ca047c999c7454 System/Time/TAI.hs | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/System/Time/TAI.hs b/System/Time/TAI.hs index fb5df5a..501f817 100644 --- a/System/Time/TAI.hs +++ b/System/Time/TAI.hs @@ -13,21 +13,24 @@ module System.Time.TAI import System.Time.Clock --- | TAI -type AbsoluteTime = MkAbsoluteTime Integer +-- | TAI as DiffTime from epoch +newtype AbsoluteTime = MkAbsoluteTime DiffTime deriving (Eq,Ord) addAbsoluteTime :: DiffTime -> AbsoluteTime -> AbsoluteTime +addAbsoluteTime t (MkAbsoluteTime a) = MkAbsoluteTime (t + a) diffAbsoluteTime :: AbsoluteTime -> AbsoluteTime -> DiffTime +diffAbsoluteTime (MkAbsoluteTime a) (MkAbsoluteTime b) = a - b -- | TAI - UTC during this day -type LeapSecondTable = ModJulianDay -> Int +type LeapSecondTable = ModJulianDay -> Integer utcDayLength :: LeapSecondTable -> ModJulianDay -> DiffTime utcDayLength table day = siSecondsToTime (86400 + (table (day + 1)) - (table day)) -utcToTAITime :: LeapSecondTable -> UTCTime -> TAITime -utcToTAITime table (UTCTime day dtime) = siSecondsToTime (table day) + - -taiToUTCTime :: LeapSecondTable -> TAITime -> UTCTime +utcToTAITime :: LeapSecondTable -> UTCTime -> AbsoluteTime +utcToTAITime table (UTCTime day dtime) = MkAbsoluteTime + ((siSecondsToTime (day * 86400 + (table day))) + dtime) +taiToUTCTime :: LeapSecondTable -> AbsoluteTime -> UTCTime +taiToUTCTime table (MkAbsoluteTime t) = undefined From git at git.haskell.org Fri Jan 23 22:52:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:39 +0000 (UTC) Subject: [commit: packages/time] master: clean up Makefile (cc4d5c2) Message-ID: <20150123225239.4EE333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/cc4d5c2ee1bcfc224d98a5f41054b511c5b52cfc >--------------------------------------------------------------- commit cc4d5c2ee1bcfc224d98a5f41054b511c5b52cfc Author: Ashley Yakeley Date: Wed Feb 23 02:58:07 2005 -0800 clean up Makefile darcs-hash:20050223105807-ac6dd-7d333afe8a9804e06faab7a6bebf8e07ee435d9c >--------------------------------------------------------------- cc4d5c2ee1bcfc224d98a5f41054b511c5b52cfc Makefile | 18 +++++++++++++----- TestTime.hs | 2 +- 2 files changed, 14 insertions(+), 6 deletions(-) diff --git a/Makefile b/Makefile index 4a6709f..502873c 100644 --- a/Makefile +++ b/Makefile @@ -1,12 +1,19 @@ default: TestTime.run -#TestTime: TestTime.o System/Time/Clock.o System/Time/TAI.o System/Time/Calendar.o -TestTime: TestTime.o System/Time/Clock.o +# SRCS = System/Time/Clock.hs System/Time/TAI.hs System/Time/Calendar.hs +SRCS = System/Time/Clock.hs System/Time/TAI.hs + +TestTime: TestTime.o $(patsubst %.hs,%.o,$(SRCS)) ghc $^ -o $@ clean: - rm -f TestTime *.o *.hi System/Time/*.o System/Time/*.hi Makefile.bak + rm -f TestTime *.o *.hi $(patsubst %.hs,%.o,$(SRCS)) $(patsubst %.hs,%.hi,$(SRCS)) Makefile.bak + + +doc: $(SRCS) + mkdir -p $@ + haddock -h -o $@ $^ %.run: % @@ -18,13 +25,14 @@ clean: %.o: %.hs ghc -c $< -o $@ -depend: TestTime.hs System/Time/Clock.hs System/Time/TAI.hs System/Time/Calendar.hs +depend: TestTime.hs $(SRCS) ghc -M $^ + # DO NOT DELETE: Beginning of Haskell dependencies TestTime.o : TestTime.hs +TestTime.o : ./System/Time/TAI.hi TestTime.o : ./System/Time/Clock.hi System/Time/Clock.o : System/Time/Clock.hs System/Time/TAI.o : System/Time/TAI.hs System/Time/TAI.o : System/Time/Clock.hi -System/Time/Calendar.o : System/Time/Calendar.hs # DO NOT DELETE: End of Haskell dependencies diff --git a/TestTime.hs b/TestTime.hs index 77dff58..9f7339b 100644 --- a/TestTime.hs +++ b/TestTime.hs @@ -1,7 +1,7 @@ module Main where import System.Time.Clock ---import System.Time.TAI +import System.Time.TAI --import System.Time.Calendar main :: IO () From git at git.haskell.org Fri Jan 23 22:52:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:41 +0000 (UTC) Subject: [commit: packages/time] master: get Calendar to compile, make TestTime a proper test, create CurrentTime to show the current time (d00d4f9) Message-ID: <20150123225241.562A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/d00d4f9cbc5a05f0447ed3af9f940766641117cc >--------------------------------------------------------------- commit d00d4f9cbc5a05f0447ed3af9f940766641117cc Author: Ashley Yakeley Date: Tue Mar 1 20:54:55 2005 -0800 get Calendar to compile, make TestTime a proper test, create CurrentTime to show the current time darcs-hash:20050302045455-ac6dd-61bc2b00b1cbb7f174c701b8776f73b837d5cf0f >--------------------------------------------------------------- d00d4f9cbc5a05f0447ed3af9f940766641117cc TestTime.hs => CurrentTime.hs | 2 +- Makefile | 24 +- System/Time/Calendar.hs | 71 +++- TestTime.hs | 31 +- TestTime.ref | 754 ++++++++++++++++++++++++++++++++++++++++++ 5 files changed, 857 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d00d4f9cbc5a05f0447ed3af9f940766641117cc From git at git.haskell.org Fri Jan 23 22:52:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:43 +0000 (UTC) Subject: [commit: packages/time] master: more haddock comments, timezone conversion functions (3ad0923) Message-ID: <20150123225243.5D4AF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3ad0923af5407c1bb45d6ca6ce8ba8d6614598a8 >--------------------------------------------------------------- commit 3ad0923af5407c1bb45d6ca6ce8ba8d6614598a8 Author: Ashley Yakeley Date: Wed Mar 2 02:53:53 2005 -0800 more haddock comments, timezone conversion functions darcs-hash:20050302105353-ac6dd-7e0a4765b0845ddc199bfb01fd74cb35c77fbe47 >--------------------------------------------------------------- 3ad0923af5407c1bb45d6ca6ce8ba8d6614598a8 System/Time/Calendar.hs | 22 +++++++++++++++++----- System/Time/Clock.hs | 11 +++++++++-- 2 files changed, 26 insertions(+), 7 deletions(-) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index 725398c..fa55f5a 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -1,7 +1,7 @@ module System.Time.Calendar ( -- time zones - TimeZone, + TimeZone,timezoneToMinutes,minutesToTimezone, -- getting the locale time zone @@ -19,9 +19,14 @@ import System.Time.Clock import Data.Char -- | count of minutes -newtype TimeZone = MkTimeZone Int deriving (Eq,Ord) +newtype TimeZone = MkTimeZone { + timezoneToMinutes :: Int +} deriving (Eq,Ord) +minutesToTimezone :: Int -> TimeZone +minutesToTimezone = MkTimeZone +-- | time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day data TimeOfDay = TimeOfDay { todHour :: Int, todMin :: Int, @@ -47,6 +52,7 @@ showpicodecimal i = '.':(showFraction 100000000000 i) instance Show TimeOfDay where show (TimeOfDay h m s ps) = (show2 h) ++ ":" ++ (show2 m) ++ ":" ++ (show2 s) ++ (showpicodecimal ps) +-- | a year, month and day aggregate, suitable for the Gregorian calendar data CalendarDay = CalendarDay { cdYear :: Integer, cdMonth :: Int, @@ -56,6 +62,7 @@ data CalendarDay = CalendarDay { instance Show CalendarDay where show (CalendarDay y m d) = (if y > 0 then show y else (show (1 - y) ++ "BCE")) ++ "-" ++ (show2 m) ++ "-" ++ (show2 d) +-- | straightforward date and time aggregate data CalendarTime = CalendarTime { ctDay :: CalendarDay, ctTime :: TimeOfDay @@ -83,12 +90,17 @@ findMonthDay :: [Int] -> Int -> (Int,Int) findMonthDay (n:ns) yd | yd > n = (\(m,d) -> (m + 1,d)) (findMonthDay ns (yd - n)) findMonthDay _ yd = (1,yd) + +months :: Bool -> [Int] +months isleap = + [31,if isleap then 29 else 28,31,30,31,30,31,31,30,31,30,31] + --J F M A M J J A S O N D + +-- | name the given day according to the Gregorian calendar dayToCalendar :: ModJulianDay -> CalendarDay dayToCalendar mjd = CalendarDay year month day where (year,yd,isleap) = dayToYearDay mjd - (month,day) = findMonthDay - [31,if isleap then 29 else 28,31,30,31,30,31,31,30,31,30,31] yd - --J F M A M J J A S O N D + (month,day) = findMonthDay (months isleap) yd utcToCalendar :: TimeZone -> UTCTime -> CalendarTime diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs index 9f59a8c..5a4825f 100644 --- a/System/Time/Clock.hs +++ b/System/Time/Clock.hs @@ -19,15 +19,17 @@ module System.Time.Clock import Foreign import Foreign.C --- | standard Julian count of Earth days +-- | standard Modified Julian Day, a count of Earth days type ModJulianDay = Integer --- | standard Julian dates for UT1, 1 = 1 day +-- | standard Modified Julian Date to represent UT1, 1 = 1 day type ModJulianDate = Rational +-- | the number of picoseconds in a second secondPicoseconds :: (Num a) => a secondPicoseconds = 1000000000000 +-- | a length of time newtype DiffTime = MkDiffTime Integer deriving (Eq,Ord,Num,Enum,Real,Integral) instance Show DiffTime where @@ -39,11 +41,15 @@ timeToSISeconds t = fromRational ((toRational t) / (toRational secondPicoseconds siSecondsToTime :: (Real a) => a -> DiffTime siSecondsToTime t = fromInteger (round ((toRational t) * secondPicoseconds)) +-- | time in UTC data UTCTime = UTCTime { + -- | the day utctDay :: ModJulianDay, + -- | the time from midnight, 0 <= t < 61s (because of leap-seconds) utctDayTime :: DiffTime } +-- | a length of time for UTC, ignoring leap-seconds newtype UTCDiffTime = MkUTCDiffTime Integer deriving (Eq,Ord,Num,Enum,Real,Integral) instance Show UTCDiffTime where @@ -100,6 +106,7 @@ instance Storable CTimeval where foreign import ccall unsafe "sys/time.h gettimeofday" gettimeofday :: Ptr CTimeval -> Ptr () -> IO CInt +-- | get the current time getCurrentTime :: IO UTCTime getCurrentTime = with (MkCTimeval 0 0) (\ptval -> do result <- gettimeofday ptval nullPtr From git at git.haskell.org Fri Jan 23 22:52:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:45 +0000 (UTC) Subject: [commit: packages/time] master: add dayToCalendar function, with test (266f005) Message-ID: <20150123225245.64FEC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/266f0057ecca2b00449eb0c631c6d9507b8281af >--------------------------------------------------------------- commit 266f0057ecca2b00449eb0c631c6d9507b8281af Author: Ashley Yakeley Date: Wed Mar 2 03:12:18 2005 -0800 add dayToCalendar function, with test darcs-hash:20050302111218-ac6dd-2efd1ae180bcf6b419cbab3f1a1876c5ed7b55c4 >--------------------------------------------------------------- 266f0057ecca2b00449eb0c631c6d9507b8281af System/Time/Calendar.hs | 12 +++++++++++- TestTime.hs | 6 +++++- 2 files changed, 16 insertions(+), 2 deletions(-) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index fa55f5a..a3b9e5a 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -7,7 +7,7 @@ module System.Time.Calendar -- converting times to Gregorian "calendrical" format TimeOfDay,CalendarDay,CalendarTime, - dayToCalendar + dayToCalendar,calendarToDay -- calendrical arithmetic -- e.g. "one month after March 31st" @@ -102,6 +102,16 @@ dayToCalendar mjd = CalendarDay year month day where (year,yd,isleap) = dayToYearDay mjd (month,day) = findMonthDay (months isleap) yd +-- | find out which day a given Gregorian calendar day is +calendarToDay :: CalendarDay -> ModJulianDay +-- formula from +calendarToDay (CalendarDay year month day) = + (fromIntegral day) + (div (153 * m + 2) 5) + (365 * y) + (div y 4) - (div y 100) + (div y 400) - 678882 where + month' = fromIntegral month + a = div (14 - month') 12 + y = year - a + m = month' + (12 * a) - 3 + utcToCalendar :: TimeZone -> UTCTime -> CalendarTime utcToCalendar tz utc = undefined diff --git a/TestTime.hs b/TestTime.hs index d724f89..af9ceec 100644 --- a/TestTime.hs +++ b/TestTime.hs @@ -5,7 +5,11 @@ import System.Time.TAI import System.Time.Calendar showCal :: ModJulianDay -> IO () -showCal d = putStrLn ((show d) ++ "=" ++ show (dayToCalendar d)) +showCal d = do + let cal = dayToCalendar d + let d' = calendarToDay cal + putStr ((show d) ++ "=" ++ show (dayToCalendar d)) + putStrLn (if d == d' then "" else "=" ++ (show d') ++ "!") for :: (Monad m) => (a -> m ()) -> [a] -> m () for _ [] = return () From git at git.haskell.org Fri Jan 23 22:52:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:47 +0000 (UTC) Subject: [commit: packages/time] master: more calendar functions, plus test for UTC - Calendar conversion (70e1b39) Message-ID: <20150123225247.6AF863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/70e1b39e22c8b19ab1d8bfa128c63256f8d84a9f >--------------------------------------------------------------- commit 70e1b39e22c8b19ab1d8bfa128c63256f8d84a9f Author: Ashley Yakeley Date: Thu Mar 3 22:24:46 2005 -0800 more calendar functions, plus test for UTC - Calendar conversion darcs-hash:20050304062446-ac6dd-51e7118d9d1d7e194bb7b0734a76ec9a3a0ebb88 >--------------------------------------------------------------- 70e1b39e22c8b19ab1d8bfa128c63256f8d84a9f CurrentTime.hs | 5 ++++- System/Time/Calendar.hs | 58 ++++++++++++++++++++++++++++++++++++++++++++----- System/Time/Clock.hs | 5 ++++- TestTime.hs | 21 ++++++++++++++++++ TestTime.ref | 6 +++++ 5 files changed, 88 insertions(+), 7 deletions(-) diff --git a/CurrentTime.hs b/CurrentTime.hs index aebfd6a..19e46c1 100644 --- a/CurrentTime.hs +++ b/CurrentTime.hs @@ -4,8 +4,11 @@ import System.Time.Clock import System.Time.TAI import System.Time.Calendar +myzone :: TimeZone +myzone = hoursToTimezone (- 8) + main :: IO () main = do now <- getCurrentTime putStrLn (show (utctDay now) ++ "," ++ show (utctDayTime now)) --- putStrLn (show (utcToCalendar (60 * -8) now)) + putStrLn (show (utcToCalendar myzone now)) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index a3b9e5a..60312e8 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -1,13 +1,16 @@ module System.Time.Calendar ( -- time zones - TimeZone,timezoneToMinutes,minutesToTimezone, + TimeZone,timezoneToMinutes,minutesToTimezone,hoursToTimezone,utc, -- getting the locale time zone -- converting times to Gregorian "calendrical" format - TimeOfDay,CalendarDay,CalendarTime, - dayToCalendar,calendarToDay + TimeOfDay(..),CalendarDay(..),CalendarTime(..), + dayToCalendar,calendarToDay, + utcToLocalTimeOfDay,localToUTCTimeOfDay, + timeToTimeOfDay,timeOfDayToTime, + utcToCalendar,calendarToUTC -- calendrical arithmetic -- e.g. "one month after March 31st" @@ -26,6 +29,13 @@ newtype TimeZone = MkTimeZone { minutesToTimezone :: Int -> TimeZone minutesToTimezone = MkTimeZone +hoursToTimezone :: Int -> TimeZone +hoursToTimezone i = minutesToTimezone (60 * i) + +-- | The UTC time zone +utc :: TimeZone +utc = minutesToTimezone 0 + -- | time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day data TimeOfDay = TimeOfDay { todHour :: Int, @@ -112,11 +122,49 @@ calendarToDay (CalendarDay year month day) = y = year - a m = month' + (12 * a) - 3 +-- | convert a ToD in UTC to a ToD in some timezone, together with a day adjustment +utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer,TimeOfDay) +utcToLocalTimeOfDay (MkTimeZone tz) (TimeOfDay h m s p) = (fromIntegral (div h' 24),TimeOfDay (mod h' 60) (mod m' 60) s p) where + m' = m + tz + h' = h + (div m' 60) + +-- | convert a ToD in some timezone to a ToD in UTC, together with a day adjustment +localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer,TimeOfDay) +localToUTCTimeOfDay (MkTimeZone tz) = utcToLocalTimeOfDay (MkTimeZone (negate tz)) + +-- note: this is also in System.Time.Clock. +posixDaySeconds :: (Num a) => a +posixDaySeconds = 86400 + +posixDay :: DiffTime +posixDay = siSecondsToTime posixDaySeconds + +-- | get a TimeOfDay given a time since midnight +-- | time more than 24h will be converted to leap-seconds +timeToTimeOfDay :: DiffTime -> TimeOfDay +timeToTimeOfDay dt | dt >= posixDay = TimeOfDay 23 59 (60 + s) p where + offset = dt - posixDay + s = fromIntegral (div offset siSecond) + p = fromIntegral (mod offset siSecond) +timeToTimeOfDay dt = TimeOfDay (fromInteger h) (fromInteger m) (fromInteger s) p where + p = fromIntegral (mod dt siSecond) + s' = fromIntegral (div dt siSecond) + s = mod s' 60 + m' = div s' 60 + m = mod m' 60 + h = div m' 60 + +-- | find out how much time since midnight a given TimeOfDay is +timeOfDayToTime :: TimeOfDay -> DiffTime +timeOfDayToTime (TimeOfDay h m s ps) = (((fromIntegral h) * 60 + (fromIntegral m)) * 60 + (fromIntegral s)) * siSecond + (fromIntegral ps) utcToCalendar :: TimeZone -> UTCTime -> CalendarTime -utcToCalendar tz utc = undefined +utcToCalendar tz (UTCTime day dt) = CalendarTime (dayToCalendar (day + i)) tod where + (i,tod) = utcToLocalTimeOfDay tz (timeToTimeOfDay dt) calendarToUTC :: TimeZone -> CalendarTime -> UTCTime -calendarToUTC tz cal = undefined +calendarToUTC tz (CalendarTime cday tod) = UTCTime (day + i) (timeOfDayToTime todUTC) where + day = calendarToDay cday + (i,todUTC) = localToUTCTimeOfDay tz tod diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs index 5a4825f..bfc7379 100644 --- a/System/Time/Clock.hs +++ b/System/Time/Clock.hs @@ -6,7 +6,7 @@ module System.Time.Clock ModJulianDay,ModJulianDate, -- absolute time intervals - DiffTime,timeToSISeconds,siSecondsToTime, + DiffTime,siSecond,timeToSISeconds,siSecondsToTime, -- UTC arithmetic UTCTime(..),UTCDiffTime,utcTimeToUTCSeconds,utcSecondsToUTCTime, @@ -35,6 +35,9 @@ newtype DiffTime = MkDiffTime Integer deriving (Eq,Ord,Num,Enum,Real,Integral) instance Show DiffTime where show (MkDiffTime t) = (show t) ++ "ps" +siSecond :: DiffTime +siSecond = secondPicoseconds + timeToSISeconds :: (Fractional a) => DiffTime -> a timeToSISeconds t = fromRational ((toRational t) / (toRational secondPicoseconds)); diff --git a/TestTime.hs b/TestTime.hs index af9ceec..104801e 100644 --- a/TestTime.hs +++ b/TestTime.hs @@ -11,10 +11,22 @@ showCal d = do putStr ((show d) ++ "=" ++ show (dayToCalendar d)) putStrLn (if d == d' then "" else "=" ++ (show d') ++ "!") +showUTCTime :: UTCTime -> String +showUTCTime (UTCTime d t) = show d ++ "," ++ show t + for :: (Monad m) => (a -> m ()) -> [a] -> m () for _ [] = return () for f (x:xs) = f x >> for f xs +myzone :: TimeZone +myzone = hoursToTimezone (- 8) + +leapSec1998Cal :: CalendarTime +leapSec1998Cal = CalendarTime (CalendarDay 1998 12 31) (TimeOfDay 23 59 60 500000000000) + +leapSec1998 :: UTCTime +leapSec1998 = calendarToUTC utc leapSec1998Cal + main :: IO () main = do showCal 0 @@ -36,3 +48,12 @@ main = do showCal 51604 -- years 2000 and 2001, plus some slop for showCal [51540..52280] + -- + putStrLn "" + showCal 51178 + putStrLn (show leapSec1998Cal) + putStrLn (showUTCTime leapSec1998) + let lsMineCal = utcToCalendar myzone leapSec1998 + putStrLn (show lsMineCal) + let lsMine = calendarToUTC myzone lsMineCal + putStrLn (showUTCTime lsMine) diff --git a/TestTime.ref b/TestTime.ref index c589a5d..ebe832a 100644 --- a/TestTime.ref +++ b/TestTime.ref @@ -752,3 +752,9 @@ 52278=2002-01-04 52279=2002-01-05 52280=2002-01-06 + +51178=1998-12-31 +1998-12-31 23:59:60.5 +51178,86400500000000000ps +1998-12-31 15:59:60.5 +51178,86400500000000000ps From git at git.haskell.org Fri Jan 23 22:52:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:49 +0000 (UTC) Subject: [commit: packages/time] master: UT1 calendar functions, with test (49c8b0d) Message-ID: <20150123225249.713D63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/49c8b0dd832c81ebe74516fa479bf131708e4e3b >--------------------------------------------------------------- commit 49c8b0dd832c81ebe74516fa479bf131708e4e3b Author: Ashley Yakeley Date: Mon Mar 7 15:17:45 2005 -0800 UT1 calendar functions, with test darcs-hash:20050307231745-ac6dd-24178425239c3be3a07adedddb2914b3af72353e >--------------------------------------------------------------- 49c8b0dd832c81ebe74516fa479bf131708e4e3b System/Time/Calendar.hs | 26 +++++++++++++++++++-- TestTime.hs | 61 ++++++++++++++++++++++++++++++++++--------------- TestTime.ref | 7 ++++++ 3 files changed, 74 insertions(+), 20 deletions(-) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index 60312e8..cb1862b 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -5,12 +5,17 @@ module System.Time.Calendar -- getting the locale time zone - -- converting times to Gregorian "calendrical" format + -- Gregorian "calendrical" format TimeOfDay(..),CalendarDay(..),CalendarTime(..), dayToCalendar,calendarToDay, + + -- converting UTC times to Gregorian "calendrical" format utcToLocalTimeOfDay,localToUTCTimeOfDay, timeToTimeOfDay,timeOfDayToTime, - utcToCalendar,calendarToUTC + utcToCalendar,calendarToUTC, + + -- converting UT1 times to Gregorian "calendrical" format + ut1ToCalendar,calendarToUT1 -- calendrical arithmetic -- e.g. "one month after March 31st" @@ -167,4 +172,21 @@ calendarToUTC tz (CalendarTime cday tod) = UTCTime (day + i) (timeOfDayToTime to day = calendarToDay cday (i,todUTC) = localToUTCTimeOfDay tz tod +-- | get a TimeOfDay given the fraction of a day since midnight +dayFractionToTimeOfDay :: Rational -> TimeOfDay +dayFractionToTimeOfDay df = timeToTimeOfDay (siSecondsToTime (round (df * posixDaySeconds))) + +-- | 1st arg is observation meridian in degrees, positive is East +ut1ToCalendar :: Rational -> ModJulianDate -> CalendarTime +ut1ToCalendar long date = CalendarTime (dayToCalendar localDay) (dayFractionToTimeOfDay localToDOffset) where + localTime = date + long / 360 :: Rational + localDay = floor localTime + localToDOffset = localTime - (fromIntegral localDay) + +-- | get the fraction of a day since midnight given a TimeOfDay +timeOfDayToDayFraction :: TimeOfDay -> Rational +timeOfDayToDayFraction tod = timeToSISeconds (timeOfDayToTime tod) / posixDaySeconds +-- | 1st arg is observation meridian in degrees, positive is East +calendarToUT1 :: Rational -> CalendarTime -> ModJulianDate +calendarToUT1 long (CalendarTime cday tod) = (fromIntegral (calendarToDay cday)) + (timeOfDayToDayFraction tod) - (long / 360) diff --git a/TestTime.hs b/TestTime.hs index 104801e..d2c47cb 100644 --- a/TestTime.hs +++ b/TestTime.hs @@ -11,24 +11,9 @@ showCal d = do putStr ((show d) ++ "=" ++ show (dayToCalendar d)) putStrLn (if d == d' then "" else "=" ++ (show d') ++ "!") -showUTCTime :: UTCTime -> String -showUTCTime (UTCTime d t) = show d ++ "," ++ show t - -for :: (Monad m) => (a -> m ()) -> [a] -> m () -for _ [] = return () -for f (x:xs) = f x >> for f xs -myzone :: TimeZone -myzone = hoursToTimezone (- 8) - -leapSec1998Cal :: CalendarTime -leapSec1998Cal = CalendarTime (CalendarDay 1998 12 31) (TimeOfDay 23 59 60 500000000000) - -leapSec1998 :: UTCTime -leapSec1998 = calendarToUTC utc leapSec1998Cal - -main :: IO () -main = do +testCal :: IO () +testCal = do showCal 0 showCal 40000 showCal 50000 @@ -48,7 +33,25 @@ main = do showCal 51604 -- years 2000 and 2001, plus some slop for showCal [51540..52280] - -- + +showUTCTime :: UTCTime -> String +showUTCTime (UTCTime d t) = show d ++ "," ++ show t + +for :: (Monad m) => (a -> m ()) -> [a] -> m () +for _ [] = return () +for f (x:xs) = f x >> for f xs + +myzone :: TimeZone +myzone = hoursToTimezone (- 8) + +leapSec1998Cal :: CalendarTime +leapSec1998Cal = CalendarTime (CalendarDay 1998 12 31) (TimeOfDay 23 59 60 500000000000) + +leapSec1998 :: UTCTime +leapSec1998 = calendarToUTC utc leapSec1998Cal + +testUTC :: IO () +testUTC = do putStrLn "" showCal 51178 putStrLn (show leapSec1998Cal) @@ -57,3 +60,25 @@ main = do putStrLn (show lsMineCal) let lsMine = calendarToUTC myzone lsMineCal putStrLn (showUTCTime lsMine) + +neglong :: Rational +neglong = -120 + +poslong :: Rational +poslong = 120 + +testUT1 :: IO () +testUT1 = do + putStrLn "" + putStrLn (show (ut1ToCalendar 0 51604.0)) + putStrLn (show (ut1ToCalendar 0 51604.5)) + putStrLn (show (ut1ToCalendar neglong 51604.0)) + putStrLn (show (ut1ToCalendar neglong 51604.5)) + putStrLn (show (ut1ToCalendar poslong 51604.0)) + putStrLn (show (ut1ToCalendar poslong 51604.5)) + +main :: IO () +main = do + testCal + testUTC + testUT1 diff --git a/TestTime.ref b/TestTime.ref index ebe832a..0d8e12b 100644 --- a/TestTime.ref +++ b/TestTime.ref @@ -758,3 +758,10 @@ 51178,86400500000000000ps 1998-12-31 15:59:60.5 51178,86400500000000000ps + +2000-03-01 00:00:00 +2000-03-01 12:00:00 +2000-02-29 16:00:00 +2000-03-01 04:00:00 +2000-03-01 08:00:00 +2000-03-01 20:00:00 From git at git.haskell.org Fri Jan 23 22:52:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:51 +0000 (UTC) Subject: [commit: packages/time] master: clean up Makefile (b1c2cb6) Message-ID: <20150123225251.78D2E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b1c2cb692a509647df3cc13e51aae4876dab9146 >--------------------------------------------------------------- commit b1c2cb692a509647df3cc13e51aae4876dab9146 Author: Ashley Yakeley Date: Mon Mar 7 15:47:36 2005 -0800 clean up Makefile darcs-hash:20050307234736-ac6dd-66591efb772cae81fb9bd808041e77c25388a881 >--------------------------------------------------------------- b1c2cb692a509647df3cc13e51aae4876dab9146 Makefile | 19 ++++++++++++------- 1 file changed, 12 insertions(+), 7 deletions(-) diff --git a/Makefile b/Makefile index e957529..f96ab63 100644 --- a/Makefile +++ b/Makefile @@ -1,21 +1,26 @@ -default: CurrentTime.run TestTime.diff +default: CurrentTime.run TestTime.diff doc SRCS = System/Time/Clock.hs System/Time/TAI.hs System/Time/Calendar.hs -TestTime: TestTime.o $(patsubst %.hs,%.o,$(SRCS)) +TestTime: TestTime.o libTimeLib.a ghc $^ -o $@ -CurrentTime: CurrentTime.o $(patsubst %.hs,%.o,$(SRCS)) +CurrentTime: CurrentTime.o libTimeLib.a ghc $^ -o $@ +libTimeLib.a: $(patsubst %.hs,%.o,$(SRCS)) + rm -f $@ + ar cru $@ $^ + ranlib $@ clean: - rm -f TestTime *.o *.hi $(patsubst %.hs,%.o,$(SRCS)) $(patsubst %.hs,%.hi,$(SRCS)) Makefile.bak + rm -rf TestTime doc haddock *.out *.o *.hi $(patsubst %.hs,%.o,$(SRCS)) $(patsubst %.hs,%.hi,$(SRCS)) Makefile.bak +doc: haddock/index.html -doc: $(SRCS) - mkdir -p $@ - haddock -h -o $@ $^ +haddock/index.html: $(SRCS) + mkdir -p haddock + haddock -h -o haddock $^ %.diff: %.ref %.out diff -u $^ From git at git.haskell.org Fri Jan 23 22:52:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:53 +0000 (UTC) Subject: [commit: packages/time] master: remove -fglasgow-exts, add -Wall -Werror to all library modules (8ae7ab8) Message-ID: <20150123225253.802333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/8ae7ab80ed7deb4e07ed2f6ddf1ce52620f3df35 >--------------------------------------------------------------- commit 8ae7ab80ed7deb4e07ed2f6ddf1ce52620f3df35 Author: Ashley Yakeley Date: Mon Mar 7 17:40:33 2005 -0800 remove -fglasgow-exts, add -Wall -Werror to all library modules darcs-hash:20050308014033-ac6dd-7894f665c98a12862a4af7de8f1eb49e2342aa26 >--------------------------------------------------------------- 8ae7ab80ed7deb4e07ed2f6ddf1ce52620f3df35 System/Time/Calendar.hs | 8 ++++--- System/Time/Clock.hs | 62 +++++++++++++++++++++++++++++++++++++++++++++---- System/Time/TAI.hs | 4 +++- 3 files changed, 65 insertions(+), 9 deletions(-) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index cb1862b..552f215 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -1,3 +1,5 @@ +{-# OPTIONS -Wall -Werror #-} + module System.Time.Calendar ( -- time zones @@ -57,7 +59,7 @@ show2 i = let _ -> s showFraction :: Integer -> Integer -> String -showFraction d 0 = "" +showFraction _ 0 = "" showFraction d i = (chr (fromInteger (48 + (div i d)))):showFraction (div d 10) (mod i d) showpicodecimal :: Integer -> String @@ -138,7 +140,7 @@ localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer,TimeOfDay) localToUTCTimeOfDay (MkTimeZone tz) = utcToLocalTimeOfDay (MkTimeZone (negate tz)) -- note: this is also in System.Time.Clock. -posixDaySeconds :: (Num a) => a +posixDaySeconds :: Rational posixDaySeconds = 86400 posixDay :: DiffTime @@ -174,7 +176,7 @@ calendarToUTC tz (CalendarTime cday tod) = UTCTime (day + i) (timeOfDayToTime to -- | get a TimeOfDay given the fraction of a day since midnight dayFractionToTimeOfDay :: Rational -> TimeOfDay -dayFractionToTimeOfDay df = timeToTimeOfDay (siSecondsToTime (round (df * posixDaySeconds))) +dayFractionToTimeOfDay df = timeToTimeOfDay (siSecondsToTime (round (df * posixDaySeconds) :: Integer)) -- | 1st arg is observation meridian in degrees, positive is East ut1ToCalendar :: Rational -> ModJulianDate -> CalendarTime diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs index bfc7379..63540d6 100644 --- a/System/Time/Clock.hs +++ b/System/Time/Clock.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -ffi -fglasgow-exts #-} +{-# OPTIONS -ffi -Wall -Werror #-} module System.Time.Clock ( @@ -30,16 +30,42 @@ secondPicoseconds :: (Num a) => a secondPicoseconds = 1000000000000 -- | a length of time -newtype DiffTime = MkDiffTime Integer deriving (Eq,Ord,Num,Enum,Real,Integral) +newtype DiffTime = MkDiffTime Integer deriving (Eq,Ord,Enum) instance Show DiffTime where show (MkDiffTime t) = (show t) ++ "ps" +-- necessary because H98 doesn't have "cunning newtype" derivation +instance Num DiffTime where + (MkDiffTime a) + (MkDiffTime b) = MkDiffTime (a + b) + (MkDiffTime a) - (MkDiffTime b) = MkDiffTime (a - b) + (MkDiffTime a) * (MkDiffTime b) = MkDiffTime (a * b) + negate (MkDiffTime a) = MkDiffTime (negate a) + abs (MkDiffTime a) = MkDiffTime (abs a) + signum (MkDiffTime a) = MkDiffTime (signum a) + fromInteger i = MkDiffTime (fromInteger i) + +-- necessary because H98 doesn't have "cunning newtype" derivation +instance Real DiffTime where + toRational (MkDiffTime a) = toRational a + +-- necessary because H98 doesn't have "cunning newtype" derivation +instance Integral DiffTime where + quot (MkDiffTime a) (MkDiffTime b) = MkDiffTime (quot a b) + rem (MkDiffTime a) (MkDiffTime b) = MkDiffTime (rem a b) + div (MkDiffTime a) (MkDiffTime b) = MkDiffTime (div a b) + mod (MkDiffTime a) (MkDiffTime b) = MkDiffTime (mod a b) + quotRem (MkDiffTime a) (MkDiffTime b) = (MkDiffTime p,MkDiffTime q) where + (p,q) = quotRem a b + divMod (MkDiffTime a) (MkDiffTime b) = (MkDiffTime p,MkDiffTime q) where + (p,q) = divMod a b + toInteger (MkDiffTime a) = toInteger a + siSecond :: DiffTime siSecond = secondPicoseconds timeToSISeconds :: (Fractional a) => DiffTime -> a -timeToSISeconds t = fromRational ((toRational t) / (toRational secondPicoseconds)); +timeToSISeconds t = fromRational ((toRational t) / secondPicoseconds); siSecondsToTime :: (Real a) => a -> DiffTime siSecondsToTime t = fromInteger (round ((toRational t) * secondPicoseconds)) @@ -53,13 +79,39 @@ data UTCTime = UTCTime { } -- | a length of time for UTC, ignoring leap-seconds -newtype UTCDiffTime = MkUTCDiffTime Integer deriving (Eq,Ord,Num,Enum,Real,Integral) +newtype UTCDiffTime = MkUTCDiffTime Integer deriving (Eq,Ord,Enum) instance Show UTCDiffTime where show (MkUTCDiffTime t) = (show t) ++ "ps" +-- necessary because H98 doesn't have "cunning newtype" derivation +instance Num UTCDiffTime where + (MkUTCDiffTime a) + (MkUTCDiffTime b) = MkUTCDiffTime (a + b) + (MkUTCDiffTime a) - (MkUTCDiffTime b) = MkUTCDiffTime (a - b) + (MkUTCDiffTime a) * (MkUTCDiffTime b) = MkUTCDiffTime (a * b) + negate (MkUTCDiffTime a) = MkUTCDiffTime (negate a) + abs (MkUTCDiffTime a) = MkUTCDiffTime (abs a) + signum (MkUTCDiffTime a) = MkUTCDiffTime (signum a) + fromInteger i = MkUTCDiffTime (fromInteger i) + +-- necessary because H98 doesn't have "cunning newtype" derivation +instance Real UTCDiffTime where + toRational (MkUTCDiffTime a) = toRational a + +-- necessary because H98 doesn't have "cunning newtype" derivation +instance Integral UTCDiffTime where + quot (MkUTCDiffTime a) (MkUTCDiffTime b) = MkUTCDiffTime (quot a b) + rem (MkUTCDiffTime a) (MkUTCDiffTime b) = MkUTCDiffTime (rem a b) + div (MkUTCDiffTime a) (MkUTCDiffTime b) = MkUTCDiffTime (div a b) + mod (MkUTCDiffTime a) (MkUTCDiffTime b) = MkUTCDiffTime (mod a b) + quotRem (MkUTCDiffTime a) (MkUTCDiffTime b) = (MkUTCDiffTime p,MkUTCDiffTime q) where + (p,q) = quotRem a b + divMod (MkUTCDiffTime a) (MkUTCDiffTime b) = (MkUTCDiffTime p,MkUTCDiffTime q) where + (p,q) = divMod a b + toInteger (MkUTCDiffTime a) = toInteger a + utcTimeToUTCSeconds :: (Fractional a) => UTCDiffTime -> a -utcTimeToUTCSeconds t = fromRational ((toRational t) / (toRational secondPicoseconds)) +utcTimeToUTCSeconds t = fromRational ((toRational t) / secondPicoseconds) utcSecondsToUTCTime :: (Real a) => a -> UTCDiffTime utcSecondsToUTCTime t = fromInteger (round ((toRational t) * secondPicoseconds)) diff --git a/System/Time/TAI.hs b/System/Time/TAI.hs index 501f817..0b85db8 100644 --- a/System/Time/TAI.hs +++ b/System/Time/TAI.hs @@ -1,3 +1,5 @@ +{-# OPTIONS -Wall -Werror #-} + -- | most people won't need this module module System.Time.TAI ( @@ -33,4 +35,4 @@ utcToTAITime table (UTCTime day dtime) = MkAbsoluteTime ((siSecondsToTime (day * 86400 + (table day))) + dtime) taiToUTCTime :: LeapSecondTable -> AbsoluteTime -> UTCTime -taiToUTCTime table (MkAbsoluteTime t) = undefined +taiToUTCTime table (MkAbsoluteTime t) = undefined table t From git at git.haskell.org Fri Jan 23 22:52:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:55 +0000 (UTC) Subject: [commit: packages/time] master: new Data.Fixed module with test, move System.Time.* to Fixed arithmetic (fd8f5d0) Message-ID: <20150123225255.88ADD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/fd8f5d0cfe55fbf4e4bfd36c594ee80e65704b98 >--------------------------------------------------------------- commit fd8f5d0cfe55fbf4e4bfd36c594ee80e65704b98 Author: Ashley Yakeley Date: Wed Mar 9 01:07:08 2005 -0800 new Data.Fixed module with test, move System.Time.* to Fixed arithmetic darcs-hash:20050309090708-ac6dd-967511e90aa27f86370e163ff42ee30950b27250 >--------------------------------------------------------------- fd8f5d0cfe55fbf4e4bfd36c594ee80e65704b98 Data/Fixed.hs | 118 ++++++++++++++++++++++++++++++++++++++++++++++++ Makefile | 17 +++++-- System/Time/Calendar.hs | 50 ++++++++------------ System/Time/Clock.hs | 94 +++++++++++++------------------------- System/Time/TAI.hs | 5 +- TestFixed.hs | 23 ++++++++++ TestFixed.ref | 72 +++++++++++++++++++++++++++++ TestTime.hs | 2 +- TestTime.ref | 4 +- 9 files changed, 284 insertions(+), 101 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fd8f5d0cfe55fbf4e4bfd36c594ee80e65704b98 From git at git.haskell.org Fri Jan 23 22:52:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:57 +0000 (UTC) Subject: [commit: packages/time] master: use realToFrac (dfadfd1) Message-ID: <20150123225257.8F2533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/dfadfd12a18f2fec5bdd56e47c847a9fcfb79cb2 >--------------------------------------------------------------- commit dfadfd12a18f2fec5bdd56e47c847a9fcfb79cb2 Author: Ashley Yakeley Date: Sun Mar 20 22:31:44 2005 -0800 use realToFrac darcs-hash:20050321063144-ac6dd-a67fc28e4d4dfcabaf93e5863c79e8697254d5e5 >--------------------------------------------------------------- dfadfd12a18f2fec5bdd56e47c847a9fcfb79cb2 Data/Fixed.hs | 6 +----- System/Time/Calendar.hs | 12 ++++++------ System/Time/Clock.hs | 8 ++++---- System/Time/TAI.hs | 5 ++--- 4 files changed, 13 insertions(+), 18 deletions(-) diff --git a/Data/Fixed.hs b/Data/Fixed.hs index 7e90374..971a39b 100644 --- a/Data/Fixed.hs +++ b/Data/Fixed.hs @@ -2,7 +2,7 @@ module Data.Fixed ( - fromReal,div',mod',divMod', + div',mod',divMod', Fixed,HasResolution(..), showFixed, @@ -10,10 +10,6 @@ module Data.Fixed E12,Pico ) where --- | similar idea to "fromIntegral" -fromReal :: (Real a,Fractional b) => a -> b -fromReal = fromRational . toRational - -- | like "div", but with a more useful type div' :: (Real a,Integral b) => a -> a -> b div' n d = floor ((toRational n) / (toRational d)) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index 9c434f6..5cc646a 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -127,7 +127,7 @@ calendarToDay (CalendarDay year month day) = -- | convert a ToD in UTC to a ToD in some timezone, together with a day adjustment utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer,TimeOfDay) -utcToLocalTimeOfDay (MkTimeZone tz) (TimeOfDay h m s) = (fromIntegral (div h' 24),TimeOfDay (mod h' 60) (mod m' 60) s) where +utcToLocalTimeOfDay (MkTimeZone tz) (TimeOfDay h m s) = (fromIntegral (div h' 24),TimeOfDay (mod h' 24) (mod m' 60) s) where m' = m + tz h' = h + (div m' 60) @@ -141,9 +141,9 @@ posixDay = fromInteger 86400 -- | get a TimeOfDay given a time since midnight -- | time more than 24h will be converted to leap-seconds timeToTimeOfDay :: DiffTime -> TimeOfDay -timeToTimeOfDay dt | dt >= posixDay = TimeOfDay 23 59 (60 + (fromReal (dt - posixDay))) +timeToTimeOfDay dt | dt >= posixDay = TimeOfDay 23 59 (60 + (realToFrac (dt - posixDay))) timeToTimeOfDay dt = TimeOfDay (fromInteger h) (fromInteger m) s where - s' = fromReal dt + s' = realToFrac dt s = mod' s' 60 m' = div' s' 60 m = mod' m' 60 @@ -151,7 +151,7 @@ timeToTimeOfDay dt = TimeOfDay (fromInteger h) (fromInteger m) s where -- | find out how much time since midnight a given TimeOfDay is timeOfDayToTime :: TimeOfDay -> DiffTime -timeOfDayToTime (TimeOfDay h m s) = ((fromIntegral h) * 60 + (fromIntegral m)) * 60 + (fromReal s) +timeOfDayToTime (TimeOfDay h m s) = ((fromIntegral h) * 60 + (fromIntegral m)) * 60 + (realToFrac s) -- | show a UTC time in a given time zone as a CalendarTime utcToCalendar :: TimeZone -> UTCTime -> CalendarTime @@ -166,7 +166,7 @@ calendarToUTC tz (CalendarTime cday tod) = UTCTime (day + i) (timeOfDayToTime to -- | get a TimeOfDay given the fraction of a day since midnight dayFractionToTimeOfDay :: Rational -> TimeOfDay -dayFractionToTimeOfDay df = timeToTimeOfDay (fromReal (df * 86400)) +dayFractionToTimeOfDay df = timeToTimeOfDay (realToFrac (df * 86400)) -- | 1st arg is observation meridian in degrees, positive is East ut1ToCalendar :: Rational -> ModJulianDate -> CalendarTime @@ -177,7 +177,7 @@ ut1ToCalendar long date = CalendarTime (dayToCalendar localDay) (dayFractionToTi -- | get the fraction of a day since midnight given a TimeOfDay timeOfDayToDayFraction :: TimeOfDay -> Rational -timeOfDayToDayFraction tod = fromReal (timeOfDayToTime tod / posixDay) +timeOfDayToDayFraction tod = realToFrac (timeOfDayToTime tod / posixDay) -- | 1st arg is observation meridian in degrees, positive is East calendarToUT1 :: Rational -> CalendarTime -> ModJulianDate diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs index 73b9bf3..c13fb61 100644 --- a/System/Time/Clock.hs +++ b/System/Time/Clock.hs @@ -97,18 +97,18 @@ unixEpochMJD = 40587 posixSecondsToUTCTime :: Pico -> UTCTime posixSecondsToUTCTime i = let (d,t) = divMod' i posixDaySeconds - in UTCTime (d + unixEpochMJD) (fromReal t) + in UTCTime (d + unixEpochMJD) (realToFrac t) utcTimeToPOSIXSeconds :: UTCTime -> Pico utcTimeToPOSIXSeconds (UTCTime d t) = - (fromInteger (d - unixEpochMJD) * posixDaySeconds) + min posixDaySeconds (fromReal t) + (fromInteger (d - unixEpochMJD) * posixDaySeconds) + min posixDaySeconds (realToFrac t) addUTCTime :: UTCDiffTime -> UTCTime -> UTCTime -addUTCTime x t = posixSecondsToUTCTime ((fromReal x) + (utcTimeToPOSIXSeconds t)) +addUTCTime x t = posixSecondsToUTCTime ((realToFrac x) + (utcTimeToPOSIXSeconds t)) diffUTCTime :: UTCTime -> UTCTime -> UTCDiffTime -diffUTCTime a b = fromReal ((utcTimeToPOSIXSeconds a) - (utcTimeToPOSIXSeconds b)) +diffUTCTime a b = realToFrac ((utcTimeToPOSIXSeconds a) - (utcTimeToPOSIXSeconds b)) -- Get current time diff --git a/System/Time/TAI.hs b/System/Time/TAI.hs index b21daa6..8cd7315 100644 --- a/System/Time/TAI.hs +++ b/System/Time/TAI.hs @@ -14,7 +14,6 @@ module System.Time.TAI ) where import System.Time.Clock -import Data.Fixed -- | TAI as DiffTime from epoch newtype AbsoluteTime = MkAbsoluteTime DiffTime deriving (Eq,Ord) @@ -29,11 +28,11 @@ diffAbsoluteTime (MkAbsoluteTime a) (MkAbsoluteTime b) = a - b type LeapSecondTable = ModJulianDay -> Integer utcDayLength :: LeapSecondTable -> ModJulianDay -> DiffTime -utcDayLength table day = fromReal (86400 + (table (day + 1)) - (table day)) +utcDayLength table day = realToFrac (86400 + (table (day + 1)) - (table day)) utcToTAITime :: LeapSecondTable -> UTCTime -> AbsoluteTime utcToTAITime table (UTCTime day dtime) = MkAbsoluteTime - ((fromReal (day * 86400 + (table day))) + dtime) + ((realToFrac (day * 86400 + (table day))) + dtime) taiToUTCTime :: LeapSecondTable -> AbsoluteTime -> UTCTime taiToUTCTime table (MkAbsoluteTime t) = undefined table t From git at git.haskell.org Fri Jan 23 22:52:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:52:59 +0000 (UTC) Subject: [commit: packages/time] master: getCurrentTimezone, with test (cb6d14e) Message-ID: <20150123225259.985C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/cb6d14eea0baae5259775481c8b7cc0b584b1219 >--------------------------------------------------------------- commit cb6d14eea0baae5259775481c8b7cc0b584b1219 Author: Ashley Yakeley Date: Sun Mar 20 22:37:22 2005 -0800 getCurrentTimezone, with test darcs-hash:20050321063722-ac6dd-9792ff0e686b52fa1c9770058f77e6614445f6fb >--------------------------------------------------------------- cb6d14eea0baae5259775481c8b7cc0b584b1219 CurrentTime.hs | 6 +++--- Makefile | 5 ++++- System/Time/Calendar.hs | 16 +++++++++++++++- timestuff.c | 11 +++++++++++ timestuff.h | 1 + 5 files changed, 34 insertions(+), 5 deletions(-) diff --git a/CurrentTime.hs b/CurrentTime.hs index 19e46c1..770699d 100644 --- a/CurrentTime.hs +++ b/CurrentTime.hs @@ -4,11 +4,11 @@ import System.Time.Clock import System.Time.TAI import System.Time.Calendar -myzone :: TimeZone -myzone = hoursToTimezone (- 8) - main :: IO () main = do now <- getCurrentTime putStrLn (show (utctDay now) ++ "," ++ show (utctDayTime now)) + putStrLn (show (utcToCalendar utc now)) + myzone <- getCurrentTimezone + putStrLn ("timezone minutes: " ++ show (timezoneToMinutes myzone)) putStrLn (show (utcToCalendar myzone now)) diff --git a/Makefile b/Makefile index 82f4d8a..e29aaa5 100644 --- a/Makefile +++ b/Makefile @@ -11,7 +11,10 @@ TestTime: TestTime.o libTimeLib.a CurrentTime: CurrentTime.o libTimeLib.a ghc $^ -o $@ -libTimeLib.a: $(patsubst %.hs,%.o,$(SRCS)) +timestuff.o: timestuff.c timestuff.h + gcc -o $@ -c $< + +libTimeLib.a: $(patsubst %.hs,%.o,$(SRCS)) timestuff.o rm -f $@ ar cru $@ $^ ranlib $@ diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index 5cc646a..683e017 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -Wall -Werror #-} +{-# OPTIONS -ffi -Wall -Werror #-} module System.Time.Calendar ( @@ -6,6 +6,7 @@ module System.Time.Calendar TimeZone,timezoneToMinutes,minutesToTimezone,hoursToTimezone,utc, -- getting the locale time zone + getCurrentTimezone, -- Gregorian "calendrical" format TimeOfDay(..),CalendarDay(..),CalendarTime(..), @@ -29,6 +30,9 @@ import System.Time.Clock import Data.Fixed import Data.Char +import Foreign +import Foreign.C + -- | count of minutes newtype TimeZone = MkTimeZone { timezoneToMinutes :: Int @@ -44,6 +48,16 @@ hoursToTimezone i = minutesToTimezone (60 * i) utc :: TimeZone utc = minutesToTimezone 0 +foreign import ccall unsafe "timestuff.h get_current_timezone_seconds" get_current_timezone_seconds :: IO CLong + +-- | Get the current time-zone +getCurrentTimezone :: IO TimeZone +getCurrentTimezone = do + secs <- get_current_timezone_seconds + case secs of + 0x80000000 -> fail "localtime_r failed" + _ -> return (minutesToTimezone (div (fromIntegral secs) 60)) + -- | time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day data TimeOfDay = TimeOfDay { todHour :: Int, diff --git a/timestuff.c b/timestuff.c new file mode 100644 index 0000000..79139bd --- /dev/null +++ b/timestuff.c @@ -0,0 +1,11 @@ +#include + +long int get_current_timezone_seconds () +{ + time_t t = 0; + struct tm tmd; + struct tm* ptm = localtime_r(&t,&tmd); + if (ptm) + return ptm -> tm_gmtoff; + else return 0x80000000; +} diff --git a/timestuff.h b/timestuff.h new file mode 100644 index 0000000..f58c0f1 --- /dev/null +++ b/timestuff.h @@ -0,0 +1 @@ +long int get_current_timezone_seconds (); From git at git.haskell.org Fri Jan 23 22:53:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:01 +0000 (UTC) Subject: [commit: packages/time] master: fix Enums to conform with Haskell 98 (and GHC 6.4) (59ab29a) Message-ID: <20150123225301.9DF0E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/59ab29ace05cdab48bb25566f31f56d443c5fc53 >--------------------------------------------------------------- commit 59ab29ace05cdab48bb25566f31f56d443c5fc53 Author: ashley Date: Tue Apr 12 00:02:57 2005 -0700 fix Enums to conform with Haskell 98 (and GHC 6.4) darcs-hash:20050412070257-ca2d0-fc71ddb95a4c9ca4f6c77e5a90020d194bd814c7 >--------------------------------------------------------------- 59ab29ace05cdab48bb25566f31f56d443c5fc53 Data/Fixed.hs | 12 +++++++++++- System/Time/Clock.hs | 24 ++++++++++++++++++++++-- 2 files changed, 33 insertions(+), 3 deletions(-) diff --git a/Data/Fixed.hs b/Data/Fixed.hs index 971a39b..697c460 100644 --- a/Data/Fixed.hs +++ b/Data/Fixed.hs @@ -24,7 +24,7 @@ mod' :: (Real a) => a -> a -> a mod' n d = n - (fromInteger f) * d where f = div' n d -newtype Fixed a = MkFixed Integer deriving (Eq,Ord,Enum) +newtype Fixed a = MkFixed Integer deriving (Eq,Ord) class HasResolution a where resolution :: a -> Integer @@ -40,6 +40,16 @@ withType foo = foo undefined withResolution :: (HasResolution a) => (Integer -> f a) -> f a withResolution foo = withType (foo . resolution) +instance Enum (Fixed a) where + succ (MkFixed a) = MkFixed (succ a) + pred (MkFixed a) = MkFixed (pred a) + toEnum = MkFixed . toEnum + fromEnum (MkFixed a) = fromEnum a + enumFrom (MkFixed a) = fmap MkFixed (enumFrom a) + enumFromThen (MkFixed a) (MkFixed b) = fmap MkFixed (enumFromThen a b) + enumFromTo (MkFixed a) (MkFixed b) = fmap MkFixed (enumFromTo a b) + enumFromThenTo (MkFixed a) (MkFixed b) (MkFixed c) = fmap MkFixed (enumFromThenTo a b c) + instance (HasResolution a) => Num (Fixed a) where (MkFixed a) + (MkFixed b) = MkFixed (a + b) (MkFixed a) - (MkFixed b) = MkFixed (a - b) diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs index c13fb61..44192b5 100644 --- a/System/Time/Clock.hs +++ b/System/Time/Clock.hs @@ -28,7 +28,17 @@ type ModJulianDay = Integer type ModJulianDate = Rational -- | a length of time -newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord,Enum) +newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord) + +instance Enum DiffTime where + succ (MkDiffTime a) = MkDiffTime (succ a) + pred (MkDiffTime a) = MkDiffTime (pred a) + toEnum = MkDiffTime . toEnum + fromEnum (MkDiffTime a) = fromEnum a + enumFrom (MkDiffTime a) = fmap MkDiffTime (enumFrom a) + enumFromThen (MkDiffTime a) (MkDiffTime b) = fmap MkDiffTime (enumFromThen a b) + enumFromTo (MkDiffTime a) (MkDiffTime b) = fmap MkDiffTime (enumFromTo a b) + enumFromThenTo (MkDiffTime a) (MkDiffTime b) (MkDiffTime c) = fmap MkDiffTime (enumFromThenTo a b c) instance Show DiffTime where show (MkDiffTime t) = (showFixed True t) ++ "s" @@ -62,7 +72,17 @@ data UTCTime = UTCTime { } -- | a length of time for UTC, ignoring leap-seconds -newtype UTCDiffTime = MkUTCDiffTime Pico deriving (Eq,Ord,Enum) +newtype UTCDiffTime = MkUTCDiffTime Pico deriving (Eq,Ord) + +instance Enum UTCDiffTime where + succ (MkUTCDiffTime a) = MkUTCDiffTime (succ a) + pred (MkUTCDiffTime a) = MkUTCDiffTime (pred a) + toEnum = MkUTCDiffTime . toEnum + fromEnum (MkUTCDiffTime a) = fromEnum a + enumFrom (MkUTCDiffTime a) = fmap MkUTCDiffTime (enumFrom a) + enumFromThen (MkUTCDiffTime a) (MkUTCDiffTime b) = fmap MkUTCDiffTime (enumFromThen a b) + enumFromTo (MkUTCDiffTime a) (MkUTCDiffTime b) = fmap MkUTCDiffTime (enumFromTo a b) + enumFromThenTo (MkUTCDiffTime a) (MkUTCDiffTime b) (MkUTCDiffTime c) = fmap MkUTCDiffTime (enumFromThenTo a b c) instance Show UTCDiffTime where show (MkUTCDiffTime t) = (showFixed True t) ++ "s" From git at git.haskell.org Fri Jan 23 22:53:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:03 +0000 (UTC) Subject: [commit: packages/time] master: use correct time C header (0d51531) Message-ID: <20150123225303.A3F713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/0d515313859d601ec4049d971316af1cb944928e >--------------------------------------------------------------- commit 0d515313859d601ec4049d971316af1cb944928e Author: ashley Date: Tue Apr 12 00:06:58 2005 -0700 use correct time C header darcs-hash:20050412070658-ca2d0-13155e99611adfa2e008de3b0461fde925a6b602 >--------------------------------------------------------------- 0d515313859d601ec4049d971316af1cb944928e timestuff.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/timestuff.c b/timestuff.c index 79139bd..24c6983 100644 --- a/timestuff.c +++ b/timestuff.c @@ -1,4 +1,4 @@ -#include +#include long int get_current_timezone_seconds () { From git at git.haskell.org Fri Jan 23 22:53:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:05 +0000 (UTC) Subject: [commit: packages/time] master: Makefile to clean properly (0a170a3) Message-ID: <20150123225305.AA5573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/0a170a3e84eb34fdf317328e341431536b554fda >--------------------------------------------------------------- commit 0a170a3e84eb34fdf317328e341431536b554fda Author: ashley Date: Thu Apr 14 00:46:18 2005 -0700 Makefile to clean properly darcs-hash:20050414074618-ca2d0-6b5b46879ec6f176b24a30adf5aa9c699f61de06 >--------------------------------------------------------------- 0a170a3e84eb34fdf317328e341431536b554fda Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Makefile b/Makefile index e29aaa5..3a69e06 100644 --- a/Makefile +++ b/Makefile @@ -20,7 +20,7 @@ libTimeLib.a: $(patsubst %.hs,%.o,$(SRCS)) timestuff.o ranlib $@ clean: - rm -rf TestTime TestFixed doc haddock *.out *.o *.hi $(patsubst %.hs,%.o,$(SRCS)) $(patsubst %.hs,%.hi,$(SRCS)) Makefile.bak + rm -rf CurrentTime TestTime TestFixed doc haddock *.out *.a *.o *.hi $(patsubst %.hs,%.o,$(SRCS)) $(patsubst %.hs,%.hi,$(SRCS)) Makefile.bak doc: haddock/index.html From git at git.haskell.org Fri Jan 23 22:53:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:07 +0000 (UTC) Subject: [commit: packages/time] master: convert to Cabal (a352b22) Message-ID: <20150123225307.B12303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/a352b227681d42a535e6644688fb01a27c4793f6 >--------------------------------------------------------------- commit a352b227681d42a535e6644688fb01a27c4793f6 Author: ashley Date: Thu Apr 14 00:47:06 2005 -0700 convert to Cabal darcs-hash:20050414074706-ca2d0-8991cfdebe2d192385f7bc175995e0c0d5e1f750 >--------------------------------------------------------------- a352b227681d42a535e6644688fb01a27c4793f6 Setup.hs | 2 ++ TimeLib.cabal | 15 +++++++++++++++ 2 files changed, 17 insertions(+) diff --git a/Setup.hs b/Setup.hs new file mode 100644 index 0000000..9a994af --- /dev/null +++ b/Setup.hs @@ -0,0 +1,2 @@ +import Distribution.Simple +main = defaultMain diff --git a/TimeLib.cabal b/TimeLib.cabal new file mode 100644 index 0000000..d7a8089 --- /dev/null +++ b/TimeLib.cabal @@ -0,0 +1,15 @@ +Name: TimeLib +Version: 0.1 +Stability: Alpha +-- unsure of best license +License: AllRightsReserved +Author: Ashley Yakeley +Maintainer: +Homepage: +Category: +Build-Depends: base +Synopsis: a new time library +Exposed-modules: Data.Fixed, System.Time.Clock, System.Time.TAI, System.Time.Calendar +Extensions: ForeignFunctionInterface +C-Sources: timestuff.c + From git at git.haskell.org Fri Jan 23 22:53:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:09 +0000 (UTC) Subject: [commit: packages/time] master: time-zone test (3317848) Message-ID: <20150123225309.B7D653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3317848eb12ef6881bd02614dd3baf1fd9664f1e >--------------------------------------------------------------- commit 3317848eb12ef6881bd02614dd3baf1fd9664f1e Author: Ashley Yakeley Date: Tue Apr 26 00:48:29 2005 -0700 time-zone test darcs-hash:20050426074829-ac6dd-bb8e92544838e18afe1ec6020e8fb145cfaa56e7 >--------------------------------------------------------------- 3317848eb12ef6881bd02614dd3baf1fd9664f1e Makefile | 12 ++++++++++-- System/Time/Calendar.hs | 4 ++++ TimeZone.hs | 9 +++++++++ 3 files changed, 23 insertions(+), 2 deletions(-) diff --git a/Makefile b/Makefile index 3a69e06..44f6935 100644 --- a/Makefile +++ b/Makefile @@ -1,4 +1,4 @@ -default: TestFixed.diff CurrentTime.run TestTime.diff doc +default: TestFixed.diff CurrentTime.run TestTime.diff TimeZone.diff doc SRCS = Data/Fixed.hs System/Time/Clock.hs System/Time/TAI.hs System/Time/Calendar.hs @@ -11,6 +11,12 @@ TestTime: TestTime.o libTimeLib.a CurrentTime: CurrentTime.o libTimeLib.a ghc $^ -o $@ +TimeZone: TimeZone.o libTimeLib.a + ghc $^ -o $@ + +TimeZone.ref: FORCE + date +%z > $@ + timestuff.o: timestuff.c timestuff.h gcc -o $@ -c $< @@ -20,7 +26,7 @@ libTimeLib.a: $(patsubst %.hs,%.o,$(SRCS)) timestuff.o ranlib $@ clean: - rm -rf CurrentTime TestTime TestFixed doc haddock *.out *.a *.o *.hi $(patsubst %.hs,%.o,$(SRCS)) $(patsubst %.hs,%.hi,$(SRCS)) Makefile.bak + rm -rf TimeZone TimeZone.ref CurrentTime TestTime TestFixed doc haddock *.out *.a *.o *.hi $(patsubst %.hs,%.o,$(SRCS)) $(patsubst %.hs,%.hi,$(SRCS)) Makefile.bak doc: haddock/index.html @@ -43,6 +49,8 @@ haddock/index.html: $(SRCS) %.o: %.hs ghc -c $< -o $@ +FORCE: + .SECONDARY: depend: TestFixed.hs CurrentTime.hs TestTime.hs $(SRCS) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index 683e017..ca10a6e 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -44,6 +44,10 @@ minutesToTimezone = MkTimeZone hoursToTimezone :: Int -> TimeZone hoursToTimezone i = minutesToTimezone (60 * i) +instance Show TimeZone where + show (MkTimeZone t) | t < 0 = '-':(show (MkTimeZone (negate t))) + show (MkTimeZone t) = (show2 (div t 60)) ++ (show2 (mod t 60)) + -- | The UTC time zone utc :: TimeZone utc = minutesToTimezone 0 diff --git a/TimeZone.hs b/TimeZone.hs new file mode 100644 index 0000000..3d8b8bc --- /dev/null +++ b/TimeZone.hs @@ -0,0 +1,9 @@ +module Main where + +import System.Time.Clock +import System.Time.Calendar + +main :: IO () +main = do + zone <- getCurrentTimezone + putStrLn (show zone) From git at git.haskell.org Fri Jan 23 22:53:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:11 +0000 (UTC) Subject: [commit: packages/time] master: correct time-zone handling (066e6ee) Message-ID: <20150123225311.BF2183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/066e6ee153ebb020a34f27a23c0db05f433fc5ef >--------------------------------------------------------------- commit 066e6ee153ebb020a34f27a23c0db05f433fc5ef Author: Ashley Yakeley Date: Wed Apr 27 01:47:46 2005 -0700 correct time-zone handling darcs-hash:20050427084746-ac6dd-6fe841a9a26be8954affc8cc42e5f080e4b355a2 >--------------------------------------------------------------- 066e6ee153ebb020a34f27a23c0db05f433fc5ef CurrentTime.hs | 2 +- System/Time/Calendar.hs | 17 ++++++++++++----- System/Time/Clock.hs | 35 ++++++++++++++++++++++++----------- TimeLib.cabal | 1 - timestuff.c | 5 ++--- timestuff.h | 4 +++- 6 files changed, 42 insertions(+), 22 deletions(-) diff --git a/CurrentTime.hs b/CurrentTime.hs index 770699d..62c88e5 100644 --- a/CurrentTime.hs +++ b/CurrentTime.hs @@ -10,5 +10,5 @@ main = do putStrLn (show (utctDay now) ++ "," ++ show (utctDayTime now)) putStrLn (show (utcToCalendar utc now)) myzone <- getCurrentTimezone - putStrLn ("timezone minutes: " ++ show (timezoneToMinutes myzone)) + putStrLn ("timezone: " ++ show myzone) putStrLn (show (utcToCalendar myzone now)) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index ca10a6e..58f38a3 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -52,16 +52,23 @@ instance Show TimeZone where utc :: TimeZone utc = minutesToTimezone 0 -foreign import ccall unsafe "timestuff.h get_current_timezone_seconds" get_current_timezone_seconds :: IO CLong +foreign import ccall unsafe "timestuff.h get_current_timezone_seconds" get_current_timezone_seconds :: CTime -> IO CLong --- | Get the current time-zone -getCurrentTimezone :: IO TimeZone -getCurrentTimezone = do - secs <- get_current_timezone_seconds +posixToCTime :: POSIXTime -> CTime +posixToCTime = floor + +-- | Get the local time-zone for a given time (varying as per summertime adjustments) +getTimezone :: UTCTime -> IO TimeZone +getTimezone time = do + secs <- get_current_timezone_seconds (posixToCTime (utcTimeToPOSIXSeconds time)) case secs of 0x80000000 -> fail "localtime_r failed" _ -> return (minutesToTimezone (div (fromIntegral secs) 60)) +-- | Get the current time-zone +getCurrentTimezone :: IO TimeZone +getCurrentTimezone = getCurrentTime >>= getTimezone + -- | time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day data TimeOfDay = TimeOfDay { todHour :: Int, diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs index 44192b5..2683841 100644 --- a/System/Time/Clock.hs +++ b/System/Time/Clock.hs @@ -13,7 +13,10 @@ module System.Time.Clock addUTCTime,diffUTCTime, -- getting the current UTC time - getCurrentTime + getCurrentTime, + + -- needed by System.Time.Calendar to talk to the Unix API + POSIXTime,posixSecondsToUTCTime,utcTimeToPOSIXSeconds ) where import Data.Fixed @@ -107,36 +110,46 @@ instance Fractional UTCDiffTime where recip (MkUTCDiffTime a) = MkUTCDiffTime (recip a) fromRational r = MkUTCDiffTime (fromRational r) -posixDaySeconds :: Pico -posixDaySeconds = 86400 +-- necessary because H98 doesn't have "cunning newtype" derivation +instance RealFrac UTCDiffTime where + properFraction (MkUTCDiffTime a) = (i,MkUTCDiffTime f) where + (i,f) = properFraction a + truncate (MkUTCDiffTime a) = truncate a + round (MkUTCDiffTime a) = round a + ceiling (MkUTCDiffTime a) = ceiling a + floor (MkUTCDiffTime a) = floor a + +posixDay :: UTCDiffTime +posixDay = 86400 unixEpochMJD :: ModJulianDay unixEpochMJD = 40587 +type POSIXTime = UTCDiffTime -posixSecondsToUTCTime :: Pico -> UTCTime +posixSecondsToUTCTime :: POSIXTime -> UTCTime posixSecondsToUTCTime i = let - (d,t) = divMod' i posixDaySeconds + (d,t) = divMod' i posixDay in UTCTime (d + unixEpochMJD) (realToFrac t) -utcTimeToPOSIXSeconds :: UTCTime -> Pico +utcTimeToPOSIXSeconds :: UTCTime -> POSIXTime utcTimeToPOSIXSeconds (UTCTime d t) = - (fromInteger (d - unixEpochMJD) * posixDaySeconds) + min posixDaySeconds (realToFrac t) + (fromInteger (d - unixEpochMJD) * posixDay) + min posixDay (realToFrac t) addUTCTime :: UTCDiffTime -> UTCTime -> UTCTime -addUTCTime x t = posixSecondsToUTCTime ((realToFrac x) + (utcTimeToPOSIXSeconds t)) +addUTCTime x t = posixSecondsToUTCTime (x + (utcTimeToPOSIXSeconds t)) diffUTCTime :: UTCTime -> UTCTime -> UTCDiffTime -diffUTCTime a b = realToFrac ((utcTimeToPOSIXSeconds a) - (utcTimeToPOSIXSeconds b)) +diffUTCTime a b = (utcTimeToPOSIXSeconds a) - (utcTimeToPOSIXSeconds b) -- Get current time data CTimeval = MkCTimeval CLong CLong -ctimevalToPosixSeconds :: CTimeval -> Pico -ctimevalToPosixSeconds (MkCTimeval s mus) = ((fromIntegral s) + (fromIntegral mus) / 1000000) +ctimevalToPosixSeconds :: CTimeval -> POSIXTime +ctimevalToPosixSeconds (MkCTimeval s mus) = (fromIntegral s) + (fromIntegral mus) / 1000000 instance Storable CTimeval where sizeOf _ = (sizeOf (undefined :: CLong)) * 2 diff --git a/TimeLib.cabal b/TimeLib.cabal index d7a8089..f609ac4 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -12,4 +12,3 @@ Synopsis: a new time library Exposed-modules: Data.Fixed, System.Time.Clock, System.Time.TAI, System.Time.Calendar Extensions: ForeignFunctionInterface C-Sources: timestuff.c - diff --git a/timestuff.c b/timestuff.c index 24c6983..92d9fbe 100644 --- a/timestuff.c +++ b/timestuff.c @@ -1,8 +1,7 @@ -#include +#include "timestuff.h" -long int get_current_timezone_seconds () +long int get_current_timezone_seconds (time_t t) { - time_t t = 0; struct tm tmd; struct tm* ptm = localtime_r(&t,&tmd); if (ptm) diff --git a/timestuff.h b/timestuff.h index f58c0f1..534ee67 100644 --- a/timestuff.h +++ b/timestuff.h @@ -1 +1,3 @@ -long int get_current_timezone_seconds (); +#include + +long int get_current_timezone_seconds (time_t); From git at git.haskell.org Fri Jan 23 22:53:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:13 +0000 (UTC) Subject: [commit: packages/time] master: fix posixToCTime for compile on 6.4 (81468e1) Message-ID: <20150123225313.C67BB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/81468e1dd2fe06e43bdd5368f9861b5b0c541435 >--------------------------------------------------------------- commit 81468e1dd2fe06e43bdd5368f9861b5b0c541435 Author: ashley Date: Wed Apr 27 23:02:29 2005 -0700 fix posixToCTime for compile on 6.4 darcs-hash:20050428060229-ca2d0-86daee65c2a063f72be81d04c32aa3efed47180b >--------------------------------------------------------------- 81468e1dd2fe06e43bdd5368f9861b5b0c541435 System/Time/Calendar.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index 58f38a3..97c6bac 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -55,7 +55,7 @@ utc = minutesToTimezone 0 foreign import ccall unsafe "timestuff.h get_current_timezone_seconds" get_current_timezone_seconds :: CTime -> IO CLong posixToCTime :: POSIXTime -> CTime -posixToCTime = floor +posixToCTime = fromInteger . floor -- | Get the local time-zone for a given time (varying as per summertime adjustments) getTimezone :: UTCTime -> IO TimeZone From git at git.haskell.org Fri Jan 23 22:53:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:15 +0000 (UTC) Subject: [commit: packages/time] master: expose getTimeZone (51caf03) Message-ID: <20150123225315.CC9B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/51caf0365ac20cfb829cedb18364e6891186325e >--------------------------------------------------------------- commit 51caf0365ac20cfb829cedb18364e6891186325e Author: ashley Date: Wed Apr 27 23:03:04 2005 -0700 expose getTimeZone darcs-hash:20050428060304-ca2d0-462560f690d4a8d591fc61dcf9eacdf91618b663 >--------------------------------------------------------------- 51caf0365ac20cfb829cedb18364e6891186325e System/Time/Calendar.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index 97c6bac..828a664 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -6,7 +6,7 @@ module System.Time.Calendar TimeZone,timezoneToMinutes,minutesToTimezone,hoursToTimezone,utc, -- getting the locale time zone - getCurrentTimezone, + getTimezone,getCurrentTimezone, -- Gregorian "calendrical" format TimeOfDay(..),CalendarDay(..),CalendarTime(..), From git at git.haskell.org Fri Jan 23 22:53:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:17 +0000 (UTC) Subject: [commit: packages/time] master: rename id to Timezone (126e42f) Message-ID: <20150123225317.D3AE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/126e42f0147dc3738fb5116ea1ee0062ecc91e88 >--------------------------------------------------------------- commit 126e42f0147dc3738fb5116ea1ee0062ecc91e88 Author: ashley Date: Wed Apr 27 23:03:31 2005 -0700 rename id to Timezone darcs-hash:20050428060331-ca2d0-3076a294d8177816b619226e48304a9b093c8cd5 >--------------------------------------------------------------- 126e42f0147dc3738fb5116ea1ee0062ecc91e88 System/Time/Calendar.hs | 34 +++++++++++++++++----------------- TestTime.hs | 2 +- 2 files changed, 18 insertions(+), 18 deletions(-) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index 828a664..c5aea12 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -3,7 +3,7 @@ module System.Time.Calendar ( -- time zones - TimeZone,timezoneToMinutes,minutesToTimezone,hoursToTimezone,utc, + Timezone,timezoneToMinutes,minutesToTimezone,hoursToTimezone,utc, -- getting the locale time zone getTimezone,getCurrentTimezone, @@ -34,22 +34,22 @@ import Foreign import Foreign.C -- | count of minutes -newtype TimeZone = MkTimeZone { +newtype Timezone = MkTimezone { timezoneToMinutes :: Int } deriving (Eq,Ord) -minutesToTimezone :: Int -> TimeZone -minutesToTimezone = MkTimeZone +minutesToTimezone :: Int -> Timezone +minutesToTimezone = MkTimezone -hoursToTimezone :: Int -> TimeZone +hoursToTimezone :: Int -> Timezone hoursToTimezone i = minutesToTimezone (60 * i) -instance Show TimeZone where - show (MkTimeZone t) | t < 0 = '-':(show (MkTimeZone (negate t))) - show (MkTimeZone t) = (show2 (div t 60)) ++ (show2 (mod t 60)) +instance Show Timezone where + show (MkTimezone t) | t < 0 = '-':(show (MkTimezone (negate t))) + show (MkTimezone t) = (show2 (div t 60)) ++ (show2 (mod t 60)) -- | The UTC time zone -utc :: TimeZone +utc :: Timezone utc = minutesToTimezone 0 foreign import ccall unsafe "timestuff.h get_current_timezone_seconds" get_current_timezone_seconds :: CTime -> IO CLong @@ -58,7 +58,7 @@ posixToCTime :: POSIXTime -> CTime posixToCTime = fromInteger . floor -- | Get the local time-zone for a given time (varying as per summertime adjustments) -getTimezone :: UTCTime -> IO TimeZone +getTimezone :: UTCTime -> IO Timezone getTimezone time = do secs <- get_current_timezone_seconds (posixToCTime (utcTimeToPOSIXSeconds time)) case secs of @@ -66,7 +66,7 @@ getTimezone time = do _ -> return (minutesToTimezone (div (fromIntegral secs) 60)) -- | Get the current time-zone -getCurrentTimezone :: IO TimeZone +getCurrentTimezone :: IO Timezone getCurrentTimezone = getCurrentTime >>= getTimezone -- | time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day @@ -151,14 +151,14 @@ calendarToDay (CalendarDay year month day) = m = month' + (12 * a) - 3 -- | convert a ToD in UTC to a ToD in some timezone, together with a day adjustment -utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer,TimeOfDay) -utcToLocalTimeOfDay (MkTimeZone tz) (TimeOfDay h m s) = (fromIntegral (div h' 24),TimeOfDay (mod h' 24) (mod m' 60) s) where +utcToLocalTimeOfDay :: Timezone -> TimeOfDay -> (Integer,TimeOfDay) +utcToLocalTimeOfDay (MkTimezone tz) (TimeOfDay h m s) = (fromIntegral (div h' 24),TimeOfDay (mod h' 24) (mod m' 60) s) where m' = m + tz h' = h + (div m' 60) -- | convert a ToD in some timezone to a ToD in UTC, together with a day adjustment -localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer,TimeOfDay) -localToUTCTimeOfDay (MkTimeZone tz) = utcToLocalTimeOfDay (MkTimeZone (negate tz)) +localToUTCTimeOfDay :: Timezone -> TimeOfDay -> (Integer,TimeOfDay) +localToUTCTimeOfDay (MkTimezone tz) = utcToLocalTimeOfDay (MkTimezone (negate tz)) posixDay :: DiffTime posixDay = fromInteger 86400 @@ -179,12 +179,12 @@ timeOfDayToTime :: TimeOfDay -> DiffTime timeOfDayToTime (TimeOfDay h m s) = ((fromIntegral h) * 60 + (fromIntegral m)) * 60 + (realToFrac s) -- | show a UTC time in a given time zone as a CalendarTime -utcToCalendar :: TimeZone -> UTCTime -> CalendarTime +utcToCalendar :: Timezone -> UTCTime -> CalendarTime utcToCalendar tz (UTCTime day dt) = CalendarTime (dayToCalendar (day + i)) tod where (i,tod) = utcToLocalTimeOfDay tz (timeToTimeOfDay dt) -- | find out what UTC time a given CalendarTime in a given time zone is -calendarToUTC :: TimeZone -> CalendarTime -> UTCTime +calendarToUTC :: Timezone -> CalendarTime -> UTCTime calendarToUTC tz (CalendarTime cday tod) = UTCTime (day + i) (timeOfDayToTime todUTC) where day = calendarToDay cday (i,todUTC) = localToUTCTimeOfDay tz tod diff --git a/TestTime.hs b/TestTime.hs index e4a2712..83d2141 100644 --- a/TestTime.hs +++ b/TestTime.hs @@ -41,7 +41,7 @@ for :: (Monad m) => (a -> m ()) -> [a] -> m () for _ [] = return () for f (x:xs) = f x >> for f xs -myzone :: TimeZone +myzone :: Timezone myzone = hoursToTimezone (- 8) leapSec1998Cal :: CalendarTime From git at git.haskell.org Fri Jan 23 22:53:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:19 +0000 (UTC) Subject: [commit: packages/time] master: midnight and midday (5564e25) Message-ID: <20150123225319.DDD9E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/5564e2557b48670109ae4ef8bc3cd1c72793ecf8 >--------------------------------------------------------------- commit 5564e2557b48670109ae4ef8bc3cd1c72793ecf8 Author: Ashley Yakeley Date: Thu Apr 28 02:45:26 2005 -0700 midnight and midday darcs-hash:20050428094526-ac6dd-6f5c7b8db227357b86d1f1c71d1e119404c7e985 >--------------------------------------------------------------- 5564e2557b48670109ae4ef8bc3cd1c72793ecf8 System/Time/Calendar.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index c5aea12..fa91928 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -8,8 +8,11 @@ module System.Time.Calendar -- getting the locale time zone getTimezone,getCurrentTimezone, + -- TimeOfDay + TimeOfDay(..),midnight,midday, + -- Gregorian "calendrical" format - TimeOfDay(..),CalendarDay(..),CalendarTime(..), + CalendarDay(..),CalendarTime(..), dayToCalendar,calendarToDay, -- converting UTC times to Gregorian "calendrical" format @@ -76,6 +79,12 @@ data TimeOfDay = TimeOfDay { todSec :: Pico } deriving (Eq,Ord) +midnight :: TimeOfDay +midnight = TimeOfDay 0 0 0 + +midday :: TimeOfDay +midday = TimeOfDay 12 0 0 + show2 :: Int -> String show2 i = let s = show i in From git at git.haskell.org Fri Jan 23 22:53:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:21 +0000 (UTC) Subject: [commit: packages/time] master: Eq and Ord instances for UTCTime (2ba76c8) Message-ID: <20150123225321.E5D2F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2ba76c8d8b27054af0ed3d6e84117d4669315998 >--------------------------------------------------------------- commit 2ba76c8d8b27054af0ed3d6e84117d4669315998 Author: Ashley Yakeley Date: Thu Apr 28 02:52:24 2005 -0700 Eq and Ord instances for UTCTime darcs-hash:20050428095224-ac6dd-7134a7acb637c0b575d82a6d1e96fab36e834c5a >--------------------------------------------------------------- 2ba76c8d8b27054af0ed3d6e84117d4669315998 System/Time/Clock.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs index 2683841..5cb946e 100644 --- a/System/Time/Clock.hs +++ b/System/Time/Clock.hs @@ -74,6 +74,14 @@ data UTCTime = UTCTime { utctDayTime :: DiffTime } +instance Eq UTCTime where + (UTCTime da ta) == (UTCTime db tb) = (da == db) && (ta == tb) + +instance Ord UTCTime where + compare (UTCTime da ta) (UTCTime db tb) = case (compare da db) of + EQ -> compare ta tb + cmp -> cmp + -- | a length of time for UTC, ignoring leap-seconds newtype UTCDiffTime = MkUTCDiffTime Pico deriving (Eq,Ord) From git at git.haskell.org Fri Jan 23 22:53:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:23 +0000 (UTC) Subject: [commit: packages/time] master: add ShowDST test program (445ae81) Message-ID: <20150123225323.EDE413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/445ae81631df6ed4ab222f104783cddd2d3e4737 >--------------------------------------------------------------- commit 445ae81631df6ed4ab222f104783cddd2d3e4737 Author: Ashley Yakeley Date: Thu Apr 28 03:12:16 2005 -0700 add ShowDST test program darcs-hash:20050428101216-ac6dd-b195b5ad2f9d60f5ad650762d377d465f535a991 >--------------------------------------------------------------- 445ae81631df6ed4ab222f104783cddd2d3e4737 Makefile | 7 ++++++- ShowDST.hs | 42 ++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 48 insertions(+), 1 deletion(-) diff --git a/Makefile b/Makefile index 44f6935..46f48b9 100644 --- a/Makefile +++ b/Makefile @@ -1,4 +1,4 @@ -default: TestFixed.diff CurrentTime.run TestTime.diff TimeZone.diff doc +default: test doc CurrentTime.run ShowDST.run SRCS = Data/Fixed.hs System/Time/Clock.hs System/Time/TAI.hs System/Time/Calendar.hs @@ -11,6 +11,9 @@ TestTime: TestTime.o libTimeLib.a CurrentTime: CurrentTime.o libTimeLib.a ghc $^ -o $@ +ShowDST: ShowDST.o libTimeLib.a + ghc $^ -o $@ + TimeZone: TimeZone.o libTimeLib.a ghc $^ -o $@ @@ -25,6 +28,8 @@ libTimeLib.a: $(patsubst %.hs,%.o,$(SRCS)) timestuff.o ar cru $@ $^ ranlib $@ +test: TestFixed.diff TestTime.diff TimeZone.diff + clean: rm -rf TimeZone TimeZone.ref CurrentTime TestTime TestFixed doc haddock *.out *.a *.o *.hi $(patsubst %.hs,%.o,$(SRCS)) $(patsubst %.hs,%.hi,$(SRCS)) Makefile.bak diff --git a/ShowDST.hs b/ShowDST.hs new file mode 100644 index 0000000..7b2dda1 --- /dev/null +++ b/ShowDST.hs @@ -0,0 +1,42 @@ +module Main where + +import System.Time.Clock +import System.Time.Calendar + +monthBeginning :: Timezone -> Integer -> Int -> UTCTime +monthBeginning zone year month = calendarToUTC zone + (CalendarTime (CalendarDay year month 1) midnight) + +findTransition :: UTCTime -> UTCTime -> IO [(UTCTime,Timezone,Timezone)] +findTransition a b = do + za <- getTimezone a + zb <- getTimezone b + if za == zb then return [] else do + let c = addUTCTime ((diffUTCTime b a) / 2) a + if a == c then return [(b,za,zb)] else do + tp <- findTransition a c + tq <- findTransition c b + return (tp ++ tq) + +showZoneTime :: Timezone -> UTCTime -> String +showZoneTime zone time = (show (utcToCalendar zone time)) ++ " " ++ (show zone) + +showTransition :: (UTCTime,Timezone,Timezone) -> String +showTransition (time,zone1,zone2) = (showZoneTime zone1 time) ++ " => " ++ (showZoneTime zone2 time) + +main :: IO () +main = do + now <- getCurrentTime + zone <- getTimezone now + let year = cdYear (ctDay (utcToCalendar zone now)) + putStrLn ("DST adjustments for " ++ show year ++ ":") + let t0 = monthBeginning zone year 1 + let t1 = monthBeginning zone year 4 + let t2 = monthBeginning zone year 7 + let t3 = monthBeginning zone year 10 + let t4 = monthBeginning zone (year + 1) 1 + tr1 <- findTransition t0 t1 + tr2 <- findTransition t1 t2 + tr3 <- findTransition t2 t3 + tr4 <- findTransition t3 t4 + mapM_ (putStrLn . showTransition) (tr1 ++ tr2 ++ tr3 ++ tr4) From git at git.haskell.org Fri Jan 23 22:53:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:26 +0000 (UTC) Subject: [commit: packages/time] master: generalise calendar type, split Calendar module (78c7468) Message-ID: <20150123225326.0145E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/78c7468a65657014621c6a1e8b2e0d38750c62db >--------------------------------------------------------------- commit 78c7468a65657014621c6a1e8b2e0d38750c62db Author: Ashley Yakeley Date: Thu Apr 28 23:15:53 2005 -0700 generalise calendar type, split Calendar module darcs-hash:20050429061553-ac6dd-1248b0405e1e0913b6bbf3c9abafeca5ef95f31d >--------------------------------------------------------------- 78c7468a65657014621c6a1e8b2e0d38750c62db CurrentTime.hs | 4 +- Makefile | 33 +++++- ShowDST.hs | 4 +- System/Time/Calendar.hs | 222 ++------------------------------------ System/Time/Calendar/Calendar.hs | 64 +++++++++++ System/Time/Calendar/Gregorian.hs | 61 +++++++++++ System/Time/Calendar/Private.hs | 17 +++ System/Time/Calendar/TimeOfDay.hs | 69 ++++++++++++ System/Time/Calendar/Timezone.hs | 54 ++++++++++ TestTime.hs | 22 ++-- TimeLib.cabal | 3 +- 11 files changed, 320 insertions(+), 233 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 78c7468a65657014621c6a1e8b2e0d38750c62db From git at git.haskell.org Fri Jan 23 22:53:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:28 +0000 (UTC) Subject: [commit: packages/time] master: first attempt at formatting (with failing test) (2678bff) Message-ID: <20150123225328.0C1773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2678bff94d02f6b646ce73392af6ce59d2af8aa6 >--------------------------------------------------------------- commit 2678bff94d02f6b646ce73392af6ce59d2af8aa6 Author: Ashley Yakeley Date: Sun May 1 01:35:54 2005 -0700 first attempt at formatting (with failing test) darcs-hash:20050501083554-ac6dd-bd83ee2a88e471f1e5e1a828d6de6bd9e5447b7b >--------------------------------------------------------------- 2678bff94d02f6b646ce73392af6ce59d2af8aa6 Makefile | 40 ++++++++++++++++---------- System/Time/Calendar.hs | 2 ++ System/Time/Calendar/Calendar.hs | 17 ++++++++--- System/Time/Calendar/Format.hs | 21 ++++++++++++++ System/Time/Calendar/Gregorian.hs | 50 ++++++++++++++++++++++++++++++--- System/Time/Calendar/Private.hs | 13 +++++++++ System/Time/Calendar/TimeOfDay.hs | 21 ++++++++++---- System/Time/Calendar/Timezone.hs | 16 +++++++---- System/Time/Clock.hs | 2 +- TestFormat.hs | 59 +++++++++++++++++++++++++++++++++++++++ TestFormatStuff.c | 14 ++++++++++ TestFormatStuff.h | 6 ++++ TestTime.hs | 10 ++----- TimeLib.cabal | 2 +- 14 files changed, 231 insertions(+), 42 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2678bff94d02f6b646ce73392af6ce59d2af8aa6 From git at git.haskell.org Fri Jan 23 22:53:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:30 +0000 (UTC) Subject: [commit: packages/time] master: add DST field to Timezone (471f5ea) Message-ID: <20150123225330.137863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/471f5ea9c67160d9740c63e6aab87a9b72c72747 >--------------------------------------------------------------- commit 471f5ea9c67160d9740c63e6aab87a9b72c72747 Author: Ashley Yakeley Date: Sun May 1 02:05:11 2005 -0700 add DST field to Timezone darcs-hash:20050501090511-ac6dd-7dfe69ea72cee8b3fe4bd070dd0a1065fdd30280 >--------------------------------------------------------------- 471f5ea9c67160d9740c63e6aab87a9b72c72747 System/Time/Calendar/TimeOfDay.hs | 4 ++-- System/Time/Calendar/Timezone.hs | 24 ++++++++++++++---------- TestFormat.hs | 6 +++--- timestuff.c | 5 ++++- timestuff.h | 2 +- 5 files changed, 24 insertions(+), 17 deletions(-) diff --git a/System/Time/Calendar/TimeOfDay.hs b/System/Time/Calendar/TimeOfDay.hs index d71c334..17cdc93 100644 --- a/System/Time/Calendar/TimeOfDay.hs +++ b/System/Time/Calendar/TimeOfDay.hs @@ -46,12 +46,12 @@ instance FormatTime TimeOfDay where -- | convert a ToD in UTC to a ToD in some timezone, together with a day adjustment utcToLocalTimeOfDay :: Timezone -> TimeOfDay -> (Integer,TimeOfDay) utcToLocalTimeOfDay zone (TimeOfDay h m s) = (fromIntegral (div h' 24),TimeOfDay (mod h' 24) (mod m' 60) s) where - m' = m + timezoneToMinutes zone + m' = m + timezoneMinutes zone h' = h + (div m' 60) -- | convert a ToD in some timezone to a ToD in UTC, together with a day adjustment localToUTCTimeOfDay :: Timezone -> TimeOfDay -> (Integer,TimeOfDay) -localToUTCTimeOfDay zone = utcToLocalTimeOfDay (minutesToTimezone (negate (timezoneToMinutes zone))) +localToUTCTimeOfDay zone = utcToLocalTimeOfDay (minutesToTimezone (negate (timezoneMinutes zone))) posixDay :: DiffTime posixDay = fromInteger 86400 diff --git a/System/Time/Calendar/Timezone.hs b/System/Time/Calendar/Timezone.hs index acfcad0..87defcd 100644 --- a/System/Time/Calendar/Timezone.hs +++ b/System/Time/Calendar/Timezone.hs @@ -3,7 +3,7 @@ module System.Time.Calendar.Timezone ( -- time zones - Timezone,timezoneToMinutes,minutesToTimezone,hoursToTimezone,utc, + Timezone(..),minutesToTimezone,hoursToTimezone,utc, -- getting the locale time zone getTimezone,getCurrentTimezone @@ -17,12 +17,13 @@ import Foreign import Foreign.C -- | count of minutes -newtype Timezone = MkTimezone { - timezoneToMinutes :: Int +data Timezone = MkTimezone { + timezoneDST :: Bool, + timezoneMinutes :: Int } deriving (Eq,Ord) minutesToTimezone :: Int -> Timezone -minutesToTimezone = MkTimezone +minutesToTimezone = MkTimezone False hoursToTimezone :: Int -> Timezone hoursToTimezone i = minutesToTimezone (60 * i) @@ -31,8 +32,8 @@ showT :: Int -> String showT t = (show2 (div t 60)) ++ (show2 (mod t 60)) instance Show Timezone where - show (MkTimezone t) | t < 0 = '-':(showT (negate t)) - show (MkTimezone t) = '+':(showT t) + show (MkTimezone _ t) | t < 0 = '-':(showT (negate t)) + show (MkTimezone _ t) = '+':(showT t) instance FormatTime Timezone where formatCharacter _ 'z' zone = Just (show zone) @@ -42,18 +43,21 @@ instance FormatTime Timezone where utc :: Timezone utc = minutesToTimezone 0 -foreign import ccall unsafe "timestuff.h get_current_timezone_seconds" get_current_timezone_seconds :: CTime -> IO CLong +foreign import ccall unsafe "timestuff.h get_current_timezone_seconds" get_current_timezone_seconds :: CTime -> Ptr CInt -> IO CLong posixToCTime :: POSIXTime -> CTime posixToCTime = fromInteger . floor -- | Get the local time-zone for a given time (varying as per summertime adjustments) getTimezone :: UTCTime -> IO Timezone -getTimezone time = do - secs <- get_current_timezone_seconds (posixToCTime (utcTimeToPOSIXSeconds time)) +getTimezone time = with 0 (\pdst -> do + secs <- get_current_timezone_seconds (posixToCTime (utcTimeToPOSIXSeconds time)) pdst case secs of 0x80000000 -> fail "localtime_r failed" - _ -> return (minutesToTimezone (div (fromIntegral secs) 60)) + _ -> do + dst <- peek pdst + return (MkTimezone (dst == 1) (div (fromIntegral secs) 60)) + ) -- | Get the current time-zone getCurrentTimezone :: IO Timezone diff --git a/TestFormat.hs b/TestFormat.hs index 6675884..4d7f800 100644 --- a/TestFormat.hs +++ b/TestFormat.hs @@ -26,11 +26,11 @@ withBuffer n f = withArray (replicate n 0) (\buffer -> do unixFormatTime :: String -> Timezone -> UTCTime -> IO String unixFormatTime fmt zone time = withCString fmt (\pfmt -> - withBuffer 100 (\buffer -> format_time buffer 100 pfmt 0 (fromIntegral (timezoneToMinutes zone * 60)) (fromInteger (truncate (utcTimeToPOSIXSeconds time)))) + withBuffer 100 (\buffer -> format_time buffer 100 pfmt (if timezoneDST zone then 1 else 0) (fromIntegral (timezoneMinutes zone * 60)) (fromInteger (truncate (utcTimeToPOSIXSeconds time)))) ) locale :: TimeLocale -locale = defaultTimeLocale +locale = defaultTimeLocale {dateTimeFmt = "%a %b %e %H:%M:%S %Y"} zones :: [Timezone] zones = [utc,hoursToTimezone (- 7)] @@ -46,7 +46,7 @@ times = [baseTime1,addUTCTime posixDay baseTime1,addUTCTime (2 * posixDay) baseT -- as found in http://www.opengroup.org/onlinepubs/007908799/xsh/strftime.html chars :: [Char] -chars = "aAbBcCdDehHIjmMnprRStTuUVwWxXyYZ%" +chars = "aAbBcCdDehHIjmMnprRStTuUVwWxXyYzZ%" main :: IO () main = mapM_ (\char -> let fmt = '%':char:[] in mapM_ (\time -> mapM_ (\zone -> let diff --git a/timestuff.c b/timestuff.c index 92d9fbe..6968a9d 100644 --- a/timestuff.c +++ b/timestuff.c @@ -1,10 +1,13 @@ #include "timestuff.h" -long int get_current_timezone_seconds (time_t t) +long int get_current_timezone_seconds (time_t t,int* dst) { struct tm tmd; struct tm* ptm = localtime_r(&t,&tmd); if (ptm) + { + *dst = ptm -> tm_isdst; return ptm -> tm_gmtoff; + } else return 0x80000000; } diff --git a/timestuff.h b/timestuff.h index 534ee67..6eaf614 100644 --- a/timestuff.h +++ b/timestuff.h @@ -1,3 +1,3 @@ #include -long int get_current_timezone_seconds (time_t); +long int get_current_timezone_seconds (time_t,int* dst); From git at git.haskell.org Fri Jan 23 22:53:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:32 +0000 (UTC) Subject: [commit: packages/time] master: add GNU and other extensions to formatting (ce92c0a) Message-ID: <20150123225332.1A9203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ce92c0a6f8d88ab2f1aa6de6dce271b1d790ce1b >--------------------------------------------------------------- commit ce92c0a6f8d88ab2f1aa6de6dce271b1d790ce1b Author: Ashley Yakeley Date: Sun May 1 05:08:16 2005 -0700 add GNU and other extensions to formatting darcs-hash:20050501120816-ac6dd-b30e46bc30c5fae816095c2f154ea9cb5ee3c3f8 >--------------------------------------------------------------- ce92c0a6f8d88ab2f1aa6de6dce271b1d790ce1b System/Time/Calendar/Gregorian.hs | 12 +++++++++--- System/Time/Calendar/TimeOfDay.hs | 7 ++++++- TestFormat.hs | 3 ++- 3 files changed, 17 insertions(+), 5 deletions(-) diff --git a/System/Time/Calendar/Gregorian.hs b/System/Time/Calendar/Gregorian.hs index 3d0dcce..b10c509 100644 --- a/System/Time/Calendar/Gregorian.hs +++ b/System/Time/Calendar/Gregorian.hs @@ -39,8 +39,11 @@ weekNumber day = (div (dayOfYear day) 7) + 1 weekNumber' :: ModJulianDay -> Int weekNumber' day = (div (dayOfYear day) 7) + 1 -weekNumber'' :: ModJulianDay -> Int -weekNumber'' day = (div (dayOfYear day) 7) + 1 +isoWeekFormat :: ModJulianDay -> (Integer,Int,Int) +isoWeekFormat day = (y,div k 7,fromInteger (mod day 7) + 1) where + (year,yd,_) = dayToYearDay day + k = yd -- WRONG + y = year -- WRONG instance FormatTime GregorianDay where formatCharacter locale 'a' day = Just (snd ((wDays locale) !! (weekDay (calendarToDay day)))) @@ -51,12 +54,15 @@ instance FormatTime GregorianDay where formatCharacter _ 'd' (GregorianDay _ _ d) = Just (show2 d) formatCharacter locale 'D' day = Just (formatTime locale "%m/%d/%y" day) formatCharacter _ 'e' (GregorianDay _ _ d) = Just (show2Space d) + formatCharacter locale 'F' day = Just (formatTime locale "%Y-%m-%d" day) + formatCharacter _ 'g' day = let (y,_,_) = isoWeekFormat (calendarToDay day) in Just (show2 (fromInteger (mod y 100))) + formatCharacter _ 'G' day = let (y,_,_) = isoWeekFormat (calendarToDay day) in Just (show y) formatCharacter locale 'h' (GregorianDay _ m _) = Just (snd ((months locale) !! (m - 1))) formatCharacter _ 'j' day = Just (show3 (dayOfYear (calendarToDay day))) formatCharacter _ 'm' (GregorianDay _ m _) = Just (show2 m) formatCharacter _ 'u' day = Just (show (weekDay' (calendarToDay day))) formatCharacter _ 'U' day = Just (show2 (weekNumber (calendarToDay day))) - formatCharacter _ 'V' day = Just (show2 (weekNumber'' (calendarToDay day))) + formatCharacter _ 'V' day = let (_,n,_) = isoWeekFormat (calendarToDay day) in Just (show2 n) formatCharacter _ 'w' day = Just (show (weekDay (calendarToDay day))) formatCharacter _ 'W' day = Just (show2 (weekNumber' (calendarToDay day))) formatCharacter locale 'x' day = Just (formatTime locale (dateFmt locale) day) diff --git a/System/Time/Calendar/TimeOfDay.hs b/System/Time/Calendar/TimeOfDay.hs index 17cdc93..ba1c891 100644 --- a/System/Time/Calendar/TimeOfDay.hs +++ b/System/Time/Calendar/TimeOfDay.hs @@ -12,9 +12,11 @@ import System.Time.Calendar.Timezone import System.Time.Calendar.Format import System.Time.Calendar.Private import System.Time.Clock -import System.Locale import Data.Fixed +import System.Locale +import Data.Char + -- | time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day data TimeOfDay = TimeOfDay { todHour :: Int, @@ -34,8 +36,11 @@ instance Show TimeOfDay where instance FormatTime TimeOfDay where formatCharacter _ 'H' (TimeOfDay h _ _) = Just (show2 h) formatCharacter _ 'I' (TimeOfDay h _ _) = Just (show2 ((mod (h - 1) 12) + 1)) + formatCharacter _ 'k' (TimeOfDay h _ _) = Just (show2Space h) + formatCharacter _ 'l' (TimeOfDay h _ _) = Just (show2Space ((mod (h - 1) 12) + 1)) formatCharacter _ 'M' (TimeOfDay _ m _) = Just (show2 m) formatCharacter locale 'p' (TimeOfDay h _ _) = Just ((if h < 12 then fst else snd) (amPm locale)) + formatCharacter locale 'P' (TimeOfDay h _ _) = Just (map toLower ((if h < 12 then fst else snd) (amPm locale))) formatCharacter locale 'r' time = Just (formatTime locale (time12Fmt locale) time) formatCharacter locale 'R' time = Just (formatTime locale "%H:%M" time) formatCharacter _ 'S' (TimeOfDay _ _ s) = Just (show2Fixed s) diff --git a/TestFormat.hs b/TestFormat.hs index 4d7f800..8534c77 100644 --- a/TestFormat.hs +++ b/TestFormat.hs @@ -45,8 +45,9 @@ times :: [UTCTime] times = [baseTime1,addUTCTime posixDay baseTime1,addUTCTime (2 * posixDay) baseTime1] -- as found in http://www.opengroup.org/onlinepubs/007908799/xsh/strftime.html +-- plus FgGklPsz chars :: [Char] -chars = "aAbBcCdDehHIjmMnprRStTuUVwWxXyYzZ%" +chars = "aAbBcCdDeFgGhHIjklmMnpPrRsStTuUVwWxXyYzZ%" main :: IO () main = mapM_ (\char -> let fmt = '%':char:[] in mapM_ (\time -> mapM_ (\zone -> let From git at git.haskell.org Fri Jan 23 22:53:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:34 +0000 (UTC) Subject: [commit: packages/time] master: generalise types with classes, introduce zoned time (1c076bc) Message-ID: <20150123225334.220773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1c076bc2e6ad37b2ae5b282aed23327079c38515 >--------------------------------------------------------------- commit 1c076bc2e6ad37b2ae5b282aed23327079c38515 Author: Ashley Yakeley Date: Mon May 2 04:09:40 2005 -0700 generalise types with classes, introduce zoned time darcs-hash:20050502110940-ac6dd-e290f92541cf1b0119110b49889535312f931af7 >--------------------------------------------------------------- 1c076bc2e6ad37b2ae5b282aed23327079c38515 CurrentTime.hs | 4 +- ShowDST.hs | 6 +-- System/Time/Calendar/Calendar.hs | 95 +++++++++++++++++++++++---------------- System/Time/Calendar/Gregorian.hs | 35 ++++++++------- TestFormat.hs | 4 +- TestTime.hs | 24 +++++----- 6 files changed, 95 insertions(+), 73 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1c076bc2e6ad37b2ae5b282aed23327079c38515 From git at git.haskell.org Fri Jan 23 22:53:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:36 +0000 (UTC) Subject: [commit: packages/time] master: fix for Makefile (86fca98) Message-ID: <20150123225336.28F723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/86fca98754ee7a052b61dafbcac863b0abf4eac0 >--------------------------------------------------------------- commit 86fca98754ee7a052b61dafbcac863b0abf4eac0 Author: ashley Date: Mon May 2 15:33:00 2005 -0700 fix for Makefile darcs-hash:20050502223300-ca2d0-85d0e358de00b9468f419c2a43a87f1ad8498d5c >--------------------------------------------------------------- 86fca98754ee7a052b61dafbcac863b0abf4eac0 Makefile | 2 ++ 1 file changed, 2 insertions(+) diff --git a/Makefile b/Makefile index b269e58..878f7e4 100644 --- a/Makefile +++ b/Makefile @@ -81,6 +81,8 @@ depend: $(SRCS) TestTime.o TestFormat.o CurrentTime.o ShowDST.o TimeZone.o: $(patsubst %.hs,%.hi,$(SRCS)) +TestFixed.o: Data/Fixed.hi + # DO NOT DELETE: Beginning of Haskell dependencies System/Time/Calendar/Format.o : System/Time/Calendar/Format.hs Data/Fixed.o : Data/Fixed.hs From git at git.haskell.org Fri Jan 23 22:53:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:38 +0000 (UTC) Subject: [commit: packages/time] master: add %s format option to ZonedTime (18b9d5a) Message-ID: <20150123225338.31A853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/18b9d5aea26a1701d120f0003fbae80b3739a577 >--------------------------------------------------------------- commit 18b9d5aea26a1701d120f0003fbae80b3739a577 Author: ashley Date: Wed May 4 01:15:17 2005 -0700 add %s format option to ZonedTime darcs-hash:20050504081517-ca2d0-1e7afb6180a65e6451b094468b1ae503acc8469b >--------------------------------------------------------------- 18b9d5aea26a1701d120f0003fbae80b3739a577 System/Time/Calendar/Calendar.hs | 3 ++- TestFormat.hs | 7 +++++-- 2 files changed, 7 insertions(+), 3 deletions(-) diff --git a/System/Time/Calendar/Calendar.hs b/System/Time/Calendar/Calendar.hs index c0bc502..9283094 100644 --- a/System/Time/Calendar/Calendar.hs +++ b/System/Time/Calendar/Calendar.hs @@ -85,6 +85,7 @@ decodeUTC (ZonedTime t zone) = decodeLocalUTC zone t instance (Show t) => Show (ZonedTime t) where show (ZonedTime t zone) = show t ++ " " ++ show zone -instance (FormatTime t) => FormatTime (ZonedTime t) where +instance (FormatTime t,LocalTimeEncoding t) => FormatTime (ZonedTime t) where + formatCharacter _ 's' zt = Just (show (truncate (utcTimeToPOSIXSeconds (decodeUTC zt)) :: Integer)) formatCharacter locale c (ZonedTime t zone) = melse (formatCharacter locale c t) (formatCharacter locale c zone) diff --git a/TestFormat.hs b/TestFormat.hs index 34c9892..e3f2728 100644 --- a/TestFormat.hs +++ b/TestFormat.hs @@ -38,11 +38,14 @@ zones = [utc,hoursToTimezone (- 7)] posixDay :: UTCDiffTime posixDay = 86400 +baseTime0 :: UTCTime +baseTime0 = decodeLocalUTC utc (CalendarTime (GregorianDay 1970 01 01) midnight) + baseTime1 :: UTCTime baseTime1 = decodeLocalUTC utc (CalendarTime (GregorianDay 2005 05 01) midnight) times :: [UTCTime] -times = [baseTime1,addUTCTime posixDay baseTime1,addUTCTime (2 * posixDay) baseTime1] +times = [baseTime0,baseTime1,addUTCTime posixDay baseTime1,addUTCTime (2 * posixDay) baseTime1] -- as found in http://www.opengroup.org/onlinepubs/007908799/xsh/strftime.html -- plus FgGklPsz @@ -56,5 +59,5 @@ main = mapM_ (\char -> let fmt = '%':char:[] in mapM_ (\time -> mapM_ (\zone -> in do unixText <- unixFormatTime fmt zone time if haskellText == unixText then return () else - putStrLn ("Mismatch with " ++ fmt ++ " for " ++ (show ctime) ++ " " ++ (show zone) ++ ": UNIX says \"" ++ unixText ++ "\", TimeLib says \"" ++ haskellText ++ "\".") + putStrLn ("Mismatch with " ++ fmt ++ " for " ++ (show ctime) ++ ": UNIX says \"" ++ unixText ++ "\", TimeLib says \"" ++ haskellText ++ "\".") ) zones) times) chars From git at git.haskell.org Fri Jan 23 22:53:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:40 +0000 (UTC) Subject: [commit: packages/time] master: add name to Timezone (d028ced) Message-ID: <20150123225340.374F33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/d028cedc35e60de0e111a5c4318f0c41c46db52e >--------------------------------------------------------------- commit d028cedc35e60de0e111a5c4318f0c41c46db52e Author: Ashley Yakeley Date: Wed May 4 04:16:42 2005 -0700 add name to Timezone darcs-hash:20050504111642-ac6dd-aeb9239e546e584e7f6d027e7b3a70b87ea793f8 >--------------------------------------------------------------- d028cedc35e60de0e111a5c4318f0c41c46db52e System/Time/Calendar/Timezone.hs | 24 ++++++++++++++---------- TestFormat.hs | 13 +++++++++---- TestFormatStuff.c | 3 ++- TestFormatStuff.h | 2 +- timestuff.c | 3 ++- timestuff.h | 2 +- 6 files changed, 29 insertions(+), 18 deletions(-) diff --git a/System/Time/Calendar/Timezone.hs b/System/Time/Calendar/Timezone.hs index 87defcd..ec003dc 100644 --- a/System/Time/Calendar/Timezone.hs +++ b/System/Time/Calendar/Timezone.hs @@ -18,12 +18,13 @@ import Foreign.C -- | count of minutes data Timezone = MkTimezone { + timezoneMinutes :: Int, timezoneDST :: Bool, - timezoneMinutes :: Int + timezoneName :: String } deriving (Eq,Ord) minutesToTimezone :: Int -> Timezone -minutesToTimezone = MkTimezone False +minutesToTimezone m = MkTimezone m False "" hoursToTimezone :: Int -> Timezone hoursToTimezone i = minutesToTimezone (60 * i) @@ -32,32 +33,35 @@ showT :: Int -> String showT t = (show2 (div t 60)) ++ (show2 (mod t 60)) instance Show Timezone where - show (MkTimezone _ t) | t < 0 = '-':(showT (negate t)) - show (MkTimezone _ t) = '+':(showT t) + show (MkTimezone t _ _) | t < 0 = '-':(showT (negate t)) + show (MkTimezone t _ _) = '+':(showT t) instance FormatTime Timezone where formatCharacter _ 'z' zone = Just (show zone) + formatCharacter _ 'Z' (MkTimezone _ _ name) = Just name formatCharacter _ _ _ = Nothing -- | The UTC time zone utc :: Timezone -utc = minutesToTimezone 0 +utc = MkTimezone 0 False "UTC" -foreign import ccall unsafe "timestuff.h get_current_timezone_seconds" get_current_timezone_seconds :: CTime -> Ptr CInt -> IO CLong +foreign import ccall unsafe "timestuff.h get_current_timezone_seconds" get_current_timezone_seconds :: CTime -> Ptr CInt -> Ptr CString -> IO CLong posixToCTime :: POSIXTime -> CTime posixToCTime = fromInteger . floor -- | Get the local time-zone for a given time (varying as per summertime adjustments) getTimezone :: UTCTime -> IO Timezone -getTimezone time = with 0 (\pdst -> do - secs <- get_current_timezone_seconds (posixToCTime (utcTimeToPOSIXSeconds time)) pdst +getTimezone time = with 0 (\pdst -> with nullPtr (\pcname -> do + secs <- get_current_timezone_seconds (posixToCTime (utcTimeToPOSIXSeconds time)) pdst pcname case secs of 0x80000000 -> fail "localtime_r failed" _ -> do dst <- peek pdst - return (MkTimezone (dst == 1) (div (fromIntegral secs) 60)) - ) + cname <- peek pcname + name <- peekCString cname + return (MkTimezone (div (fromIntegral secs) 60) (dst == 1) name) + )) -- | Get the current time-zone getCurrentTimezone :: IO Timezone diff --git a/TestFormat.hs b/TestFormat.hs index e3f2728..21a84f7 100644 --- a/TestFormat.hs +++ b/TestFormat.hs @@ -16,7 +16,7 @@ import Foreign.C int isdst,int gmtoff,time_t t); -} -foreign import ccall unsafe "TestFormatStuff.h format_time" format_time :: CString -> CSize -> CString -> CInt -> CInt -> CTime -> IO CSize +foreign import ccall unsafe "TestFormatStuff.h format_time" format_time :: CString -> CSize -> CString -> CInt -> CInt -> CString -> CTime -> IO CSize withBuffer :: Int -> (CString -> IO CSize) -> IO String withBuffer n f = withArray (replicate n 0) (\buffer -> do @@ -25,9 +25,14 @@ withBuffer n f = withArray (replicate n 0) (\buffer -> do ) unixFormatTime :: String -> Timezone -> UTCTime -> IO String -unixFormatTime fmt zone time = withCString fmt (\pfmt -> - withBuffer 100 (\buffer -> format_time buffer 100 pfmt (if timezoneDST zone then 1 else 0) (fromIntegral (timezoneMinutes zone * 60)) (fromInteger (truncate (utcTimeToPOSIXSeconds time)))) - ) +unixFormatTime fmt zone time = withCString fmt (\pfmt -> withCString (timezoneName zone) (\pzonename -> + withBuffer 100 (\buffer -> format_time buffer 100 pfmt + (if timezoneDST zone then 1 else 0) + (fromIntegral (timezoneMinutes zone * 60)) + pzonename + (fromInteger (truncate (utcTimeToPOSIXSeconds time))) + ) + )) locale :: TimeLocale locale = defaultTimeLocale {dateTimeFmt = "%a %b %e %H:%M:%S %Y"} diff --git a/TestFormatStuff.c b/TestFormatStuff.c index 8450fb5..8d314ba 100644 --- a/TestFormatStuff.c +++ b/TestFormatStuff.c @@ -3,12 +3,13 @@ size_t format_time ( char* buffer, size_t maxsize, const char* format, - int isdst,int gmtoff,time_t t) + int isdst,int gmtoff,char* zonename,time_t t) { t += gmtoff; struct tm tmd; gmtime_r(&t,&tmd); tmd.tm_isdst = isdst; tmd.tm_gmtoff = gmtoff; + tmd.tm_zone = zonename; return strftime(buffer,maxsize,format,&tmd); } diff --git a/TestFormatStuff.h b/TestFormatStuff.h index 5f9e853..f2f7175 100644 --- a/TestFormatStuff.h +++ b/TestFormatStuff.h @@ -3,4 +3,4 @@ size_t format_time ( char *s, size_t maxsize, const char *format, - int isdst,int gmtoff,time_t t); + int isdst,int gmtoff,char* zonename,time_t t); diff --git a/timestuff.c b/timestuff.c index 6968a9d..386616e 100644 --- a/timestuff.c +++ b/timestuff.c @@ -1,12 +1,13 @@ #include "timestuff.h" -long int get_current_timezone_seconds (time_t t,int* dst) +long int get_current_timezone_seconds (time_t t,int* dst,char** name) { struct tm tmd; struct tm* ptm = localtime_r(&t,&tmd); if (ptm) { *dst = ptm -> tm_isdst; + *name = ptm -> tm_zone; return ptm -> tm_gmtoff; } else return 0x80000000; diff --git a/timestuff.h b/timestuff.h index 6eaf614..936cd84 100644 --- a/timestuff.h +++ b/timestuff.h @@ -1,3 +1,3 @@ #include -long int get_current_timezone_seconds (time_t,int* dst); +long int get_current_timezone_seconds (time_t,int* dst,char** name); From git at git.haskell.org Fri Jan 23 22:53:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:42 +0000 (UTC) Subject: [commit: packages/time] master: build/test target fiddling in Makefile (1c01493) Message-ID: <20150123225342.3E15B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1c01493fa23ff52673863e7cc4f42f01f2859c73 >--------------------------------------------------------------- commit 1c01493fa23ff52673863e7cc4f42f01f2859c73 Author: Ashley Yakeley Date: Thu May 5 00:17:36 2005 -0700 build/test target fiddling in Makefile darcs-hash:20050505071736-ac6dd-71984598fc9b9282614217eaf645e2e81fcc2a9c >--------------------------------------------------------------- 1c01493fa23ff52673863e7cc4f42f01f2859c73 Makefile | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Makefile b/Makefile index 878f7e4..14c6e54 100644 --- a/Makefile +++ b/Makefile @@ -1,4 +1,6 @@ -default: test doc CurrentTime.run ShowDST.run +default: build doc CurrentTime.run ShowDST.run test + +build: $(patsubst %.hs,%.hi,$(SRCS)) libTimeLib.a SRCS = Data/Fixed.hs \ System/Time/Clock.hs \ From git at git.haskell.org Fri Jan 23 22:53:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:44 +0000 (UTC) Subject: [commit: packages/time] master: better type for formatCharacter (a55e303) Message-ID: <20150123225344.461153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/a55e3039dfa75c7d6dc7e079b869b5eeaf345ba2 >--------------------------------------------------------------- commit a55e3039dfa75c7d6dc7e079b869b5eeaf345ba2 Author: Ashley Yakeley Date: Thu May 5 00:18:49 2005 -0700 better type for formatCharacter darcs-hash:20050505071849-ac6dd-6a0365ab76ba8bb976eb8ea8537416db492a3230 >--------------------------------------------------------------- a55e3039dfa75c7d6dc7e079b869b5eeaf345ba2 System/Time/Calendar/Calendar.hs | 22 ++++++++++--------- System/Time/Calendar/Format.hs | 6 ++--- System/Time/Calendar/Gregorian.hs | 46 +++++++++++++++++++-------------------- System/Time/Calendar/TimeOfDay.hs | 26 +++++++++++----------- System/Time/Calendar/Timezone.hs | 16 +++++++++----- TimeZone.hs | 2 +- 6 files changed, 62 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a55e3039dfa75c7d6dc7e079b869b5eeaf345ba2 From git at git.haskell.org Fri Jan 23 22:53:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:46 +0000 (UTC) Subject: [commit: packages/time] master: separate tests into dir, new ISOWeek and YearDay modules, pull Format code into module, new ConvertBack test (ffc5046) Message-ID: <20150123225346.51BBF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ffc504663a608ba94a8242b505f39a9ba7e2eff5 >--------------------------------------------------------------- commit ffc504663a608ba94a8242b505f39a9ba7e2eff5 Author: Ashley Yakeley Date: Sat May 7 18:39:22 2005 -0700 separate tests into dir, new ISOWeek and YearDay modules, pull Format code into module, new ConvertBack test darcs-hash:20050508013922-ac6dd-3a0e7a0e7248b710906427343fe829c0085ca815 >--------------------------------------------------------------- ffc504663a608ba94a8242b505f39a9ba7e2eff5 Makefile | 66 ++++++--------- System/Time/Calendar.hs | 10 ++- System/Time/Calendar/Calendar.hs | 22 +---- System/Time/Calendar/Format.hs | 119 ++++++++++++++++++++++++++++ System/Time/Calendar/Gregorian.hs | 70 +--------------- System/Time/Calendar/ISOWeek.hs | 36 +++++++++ System/Time/Calendar/Private.hs | 6 ++ System/Time/Calendar/TimeOfDay.hs | 19 ----- System/Time/Calendar/Timezone.hs | 7 +- System/Time/Calendar/YearDay.hs | 36 +++++++++ TimeLib.cabal | 2 +- test/ConvertBack.hs | 20 +++++ CurrentTime.hs => test/CurrentTime.hs | 0 test/Makefile | 59 ++++++++++++++ ShowDST.hs => test/ShowDST.hs | 0 TestFixed.hs => test/TestFixed.hs | 0 TestFixed.ref => test/TestFixed.ref | 0 TestFormat.hs => test/TestFormat.hs | 47 ++++++++--- TestFormatStuff.c => test/TestFormatStuff.c | 0 TestFormatStuff.h => test/TestFormatStuff.h | 0 TestTime.hs => test/TestTime.hs | 0 TestTime.ref => test/TestTime.ref | 0 TimeZone.hs => test/TimeZone.hs | 0 23 files changed, 352 insertions(+), 167 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ffc504663a608ba94a8242b505f39a9ba7e2eff5 From git at git.haskell.org Fri Jan 23 22:53:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:48 +0000 (UTC) Subject: [commit: packages/time] master: Clock documentation (622d6b5) Message-ID: <20150123225348.5936E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/622d6b52d402996282c403d7497215f42b117d13 >--------------------------------------------------------------- commit 622d6b52d402996282c403d7497215f42b117d13 Author: Ashley Yakeley Date: Sun May 8 05:10:59 2005 -0700 Clock documentation darcs-hash:20050508121059-ac6dd-912229bbc27e18aea3168073d4976f46e7b97aa3 >--------------------------------------------------------------- 622d6b52d402996282c403d7497215f42b117d13 System/Time/Clock.hs | 41 ++++++++++++++++++++++++++++------------- 1 file changed, 28 insertions(+), 13 deletions(-) diff --git a/System/Time/Clock.hs b/System/Time/Clock.hs index ae29dd1..5f809f1 100644 --- a/System/Time/Clock.hs +++ b/System/Time/Clock.hs @@ -1,21 +1,29 @@ {-# OPTIONS -ffi -Wall -Werror #-} +-- | Types and functions for UTC and UT1 module System.Time.Clock ( - -- Modified Julian days and dates (for UT1) + -- * Universal Time + -- | Time as measured by the earth. ModJulianDay,ModJulianDate, - -- absolute time intervals + -- * Absolute intervals DiffTime, - -- UTC arithmetic + -- * UTC + -- | UTC is time as measured by a clock, corrected to keep pace with the earth by adding or removing + -- occasional seconds, known as \"leap seconds\". + -- These corrections are not predictable and are announced with six month's notice. + -- No table of these corrections is provided, as any program compiled with it would become + -- out of date in six months. UTCTime(..),UTCDiffTime, addUTCTime,diffUTCTime, - -- getting the current UTC time + -- * Current time getCurrentTime, - -- needed by System.Time.Calendar to talk to the Unix API + -- * POSIX time + -- | This is needed by System.Time.Calendar to talk to the Unix API. POSIXTime,posixSecondsToUTCTime,utcTimeToPOSIXSeconds ) where @@ -24,13 +32,14 @@ import Data.Fixed import Foreign import Foreign.C --- | standard Modified Julian Day, a count of Earth days +-- | The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17. type ModJulianDay = Integer --- | standard Modified Julian Date to represent UT1, 1 = 1 day +-- | The Modified Julian Date is the day with the fraction of the day, measured from UT midnight. +-- It's used to represent UT1, which is time as measured by the earth's rotation, adjusted for various wobbles. type ModJulianDate = Rational --- | a length of time +-- | This is a length of time, as measured by a clock. newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord) instance Enum DiffTime where @@ -66,11 +75,13 @@ instance Fractional DiffTime where recip (MkDiffTime a) = MkDiffTime (recip a) fromRational r = MkDiffTime (fromRational r) --- | time in UTC +-- | This is the simplest representation of UTC. +-- It consists of the day number, and a time offset from midnight. +-- Note that if a day has a leap second added to it, it will have 86401 seconds. data UTCTime = UTCTime { -- | the day utctDay :: ModJulianDay, - -- | the time from midnight, 0 <= t < 61s (because of leap-seconds) + -- | the time from midnight, 0 <= t < 86401s (because of leap-seconds) utctDayTime :: DiffTime } @@ -82,7 +93,10 @@ instance Ord UTCTime where EQ -> compare ta tb cmp -> cmp --- | a length of time for UTC, ignoring leap-seconds +-- | This is a length of time, as measured by UTC. +-- It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. +-- For instance, 23:00 UTC + 2 hours of UTCDiffTime = 01:00 UTC (+ 1 day), +-- regardless of whether a leap-second intervened. newtype UTCDiffTime = MkUTCDiffTime Pico deriving (Eq,Ord) instance Enum UTCDiffTime where @@ -144,10 +158,11 @@ utcTimeToPOSIXSeconds :: UTCTime -> POSIXTime utcTimeToPOSIXSeconds (UTCTime d t) = (fromInteger (d - unixEpochMJD) * posixDay) + min posixDay (realToFrac t) - +-- | addUTCTime a b = a + b addUTCTime :: UTCDiffTime -> UTCTime -> UTCTime addUTCTime x t = posixSecondsToUTCTime (x + (utcTimeToPOSIXSeconds t)) +-- | diffUTCTime a b = a - b diffUTCTime :: UTCTime -> UTCTime -> UTCDiffTime diffUTCTime a b = (utcTimeToPOSIXSeconds a) - (utcTimeToPOSIXSeconds b) @@ -172,7 +187,7 @@ instance Storable CTimeval where foreign import ccall unsafe "time.h gettimeofday" gettimeofday :: Ptr CTimeval -> Ptr () -> IO CInt --- | get the current time +-- | Get the current UTC time from the system clock. getCurrentTime :: IO UTCTime getCurrentTime = with (MkCTimeval 0 0) (\ptval -> do result <- gettimeofday ptval nullPtr From git at git.haskell.org Fri Jan 23 22:53:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:50 +0000 (UTC) Subject: [commit: packages/time] master: TAI documentation (0782592) Message-ID: <20150123225350.60F383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/07825921e2e187d56a1e0838ea35d13d733ffb66 >--------------------------------------------------------------- commit 07825921e2e187d56a1e0838ea35d13d733ffb66 Author: Ashley Yakeley Date: Sun May 8 21:08:36 2005 -0700 TAI documentation darcs-hash:20050509040836-ac6dd-189305d5b41c695936e994099c0f6b0f5f952fbf >--------------------------------------------------------------- 07825921e2e187d56a1e0838ea35d13d733ffb66 System/Time/TAI.hs | 18 +++++++++++++----- 1 file changed, 13 insertions(+), 5 deletions(-) diff --git a/System/Time/TAI.hs b/System/Time/TAI.hs index 8cd7315..f78eab0 100644 --- a/System/Time/TAI.hs +++ b/System/Time/TAI.hs @@ -1,10 +1,10 @@ {-# OPTIONS -Wall -Werror #-} --- | most people won't need this module +-- | TAI and leap-second tables for converting to UTC: most people won't need this module. module System.Time.TAI ( -- TAI arithmetic - AbsoluteTime,addAbsoluteTime,diffAbsoluteTime, + AbsoluteTime,taiEpoch,addAbsoluteTime,diffAbsoluteTime, -- leap-second table type LeapSecondTable, @@ -15,16 +15,24 @@ module System.Time.TAI import System.Time.Clock --- | TAI as DiffTime from epoch +-- | AbsoluteTime is TAI, time as measured by a clock. newtype AbsoluteTime = MkAbsoluteTime DiffTime deriving (Eq,Ord) +-- | The epoch of TAI, which is +taiEpoch :: AbsoluteTime +taiEpoch = MkAbsoluteTime 0 + +-- | addAbsoluteTime a b = a + b addAbsoluteTime :: DiffTime -> AbsoluteTime -> AbsoluteTime addAbsoluteTime t (MkAbsoluteTime a) = MkAbsoluteTime (t + a) +-- | diffAbsoluteTime a b = a - b diffAbsoluteTime :: AbsoluteTime -> AbsoluteTime -> DiffTime diffAbsoluteTime (MkAbsoluteTime a) (MkAbsoluteTime b) = a - b --- | TAI - UTC during this day +-- | TAI - UTC during this day. +-- No table is provided, as any program compiled with it would become +-- out of date in six months. type LeapSecondTable = ModJulianDay -> Integer utcDayLength :: LeapSecondTable -> ModJulianDay -> DiffTime @@ -35,4 +43,4 @@ utcToTAITime table (UTCTime day dtime) = MkAbsoluteTime ((realToFrac (day * 86400 + (table day))) + dtime) taiToUTCTime :: LeapSecondTable -> AbsoluteTime -> UTCTime -taiToUTCTime table (MkAbsoluteTime t) = undefined table t +taiToUTCTime table (MkAbsoluteTime t) = undefined table t -- WRONG From git at git.haskell.org Fri Jan 23 22:53:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:52 +0000 (UTC) Subject: [commit: packages/time] master: test in Makefile (e12e45e) Message-ID: <20150123225352.672073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e12e45e5f42c7a8c1ec29576d4d9014edbf5d7cd >--------------------------------------------------------------- commit e12e45e5f42c7a8c1ec29576d4d9014edbf5d7cd Author: Ashley Yakeley Date: Sun May 8 21:12:05 2005 -0700 test in Makefile darcs-hash:20050509041205-ac6dd-5390ff04e98e6c097dedbafd1a1c72833014de83 >--------------------------------------------------------------- e12e45e5f42c7a8c1ec29576d4d9014edbf5d7cd Makefile | 3 +++ 1 file changed, 3 insertions(+) diff --git a/Makefile b/Makefile index e94c52d..c6c6b0b 100644 --- a/Makefile +++ b/Makefile @@ -2,6 +2,9 @@ default: build doc build: $(patsubst %.hs,%.hi,$(SRCS)) libTimeLib.a +test: build + cd test && make + SRCS = Data/Fixed.hs \ System/Time/Clock.hs \ System/Time/TAI.hs \ From git at git.haskell.org Fri Jan 23 22:53:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:54 +0000 (UTC) Subject: [commit: packages/time] master: fix decodeDay in ISOWeek, with improved ConvertBack test (899a104) Message-ID: <20150123225354.6EED13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/899a1047cf6940d1378dcc6efac9b987152ddae9 >--------------------------------------------------------------- commit 899a1047cf6940d1378dcc6efac9b987152ddae9 Author: Ashley Yakeley Date: Sun May 8 21:37:46 2005 -0700 fix decodeDay in ISOWeek, with improved ConvertBack test darcs-hash:20050509043746-ac6dd-de2745bf5dcba79c8a2e1600b9e9d2a4564d9ae7 >--------------------------------------------------------------- 899a1047cf6940d1378dcc6efac9b987152ddae9 System/Time/Calendar/ISOWeek.hs | 5 +++-- test/ConvertBack.hs | 25 ++++++++++++++++++------- 2 files changed, 21 insertions(+), 9 deletions(-) diff --git a/System/Time/Calendar/ISOWeek.hs b/System/Time/Calendar/ISOWeek.hs index 9126ac9..e6412e4 100644 --- a/System/Time/Calendar/ISOWeek.hs +++ b/System/Time/Calendar/ISOWeek.hs @@ -21,7 +21,7 @@ instance DayEncoding ISOWeek where (YearDay y0 yd) = encodeDay mjd d = mjd + 2 foo :: Integer -> Integer - foo y = bar (decodeDay (YearDay y 4) + 2) + foo y = bar (decodeDay (YearDay y 6)) bar k = (div d 7) - (div k 7) w0 = bar (d - (toInteger yd) + 4) (y1,w1) = if w0 == -1 @@ -32,5 +32,6 @@ instance DayEncoding ISOWeek where else (y0,w0) else (y0,w0) - decodeDay (ISOWeek _ _ _) = undefined -- WRONG + decodeDay (ISOWeek y w d) = k - (mod k 7) + (toInteger ((w * 7) + d)) - 10 where + k = decodeDay (YearDay y 6) maybeDecodeDay = Just . decodeDay -- WRONG diff --git a/test/ConvertBack.hs b/test/ConvertBack.hs index da3bf3e..5b4968d 100644 --- a/test/ConvertBack.hs +++ b/test/ConvertBack.hs @@ -5,16 +5,27 @@ module Main where import System.Time.Calendar import System.Time.Clock -checkDay :: ModJulianDay -> IO () -checkDay day = do - let st = encodeDay day :: YearDay +checkDay :: (DayEncoding t,Show t) => t -> ModJulianDay -> IO () +checkDay t day = do + let st = encodeDay' t day let day' = decodeDay st if day /= day' - then putStrLn ((show day) ++ " -> " ++ (show st) ++ " -> " ++ (show day')) + then putStrLn ((show day) ++ " -> " ++ (show st) ++ " -> " ++ (show day') ++ " (diff " ++ (show (day' - day)) ++ ")") else return () + where + encodeDay' :: (DayEncoding t,Show t) => t -> ModJulianDay -> t + encodeDay' _ = encodeDay +checkers :: [ModJulianDay -> IO ()] +checkers = [ + checkDay (undefined :: YearDay), + checkDay (undefined :: ISOWeek), + checkDay (undefined :: GregorianDay) + ] + +days :: [ModJulianDay] +days = [50000..50200] ++ + (fmap (\year -> (decodeDay (GregorianDay year 1 4))) [1980..2000]) main :: IO () -main = do - mapM_ checkDay [50000..50200] - mapM_ (\year -> checkDay (decodeDay (GregorianDay year 1 4))) [1980..2000] +main = mapM_ (\ch -> mapM_ ch days) checkers From git at git.haskell.org Fri Jan 23 22:53:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:56 +0000 (UTC) Subject: [commit: packages/time] master: remove maybeDecodeDay (7ece834) Message-ID: <20150123225356.778153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/7ece8344e900e08a360e85c610f3160303f47887 >--------------------------------------------------------------- commit 7ece8344e900e08a360e85c610f3160303f47887 Author: Ashley Yakeley Date: Mon May 9 01:24:16 2005 -0700 remove maybeDecodeDay darcs-hash:20050509082416-ac6dd-891eb8f17253072739f7852627b2a9de76a855c0 >--------------------------------------------------------------- 7ece8344e900e08a360e85c610f3160303f47887 System/Time/Calendar/Calendar.hs | 4 ---- System/Time/Calendar/Gregorian.hs | 1 - System/Time/Calendar/ISOWeek.hs | 1 - System/Time/Calendar/YearDay.hs | 2 -- 4 files changed, 8 deletions(-) diff --git a/System/Time/Calendar/Calendar.hs b/System/Time/Calendar/Calendar.hs index 060e43a..77f30d2 100644 --- a/System/Time/Calendar/Calendar.hs +++ b/System/Time/Calendar/Calendar.hs @@ -14,19 +14,15 @@ module System.Time.Calendar.Calendar import System.Time.Calendar.TimeOfDay import System.Time.Calendar.Timezone import System.Time.Clock -import Data.Maybe class (Eq d) => DayEncoding d where -- | name the given day according to the calendar encodeDay :: ModJulianDay -> d -- | find out which day a given calendar day is - maybeDecodeDay :: d -> Maybe ModJulianDay decodeDay :: d -> ModJulianDay - decodeDay day = fromMaybe (error "invalid day") (maybeDecodeDay day) instance DayEncoding ModJulianDay where encodeDay = id - maybeDecodeDay = Just decodeDay = id class (Eq t) => LocalTimeEncoding t where diff --git a/System/Time/Calendar/Gregorian.hs b/System/Time/Calendar/Gregorian.hs index 4422ce1..fa9b89c 100644 --- a/System/Time/Calendar/Gregorian.hs +++ b/System/Time/Calendar/Gregorian.hs @@ -47,4 +47,3 @@ instance DayEncoding GregorianDay where a = div (14 - month') 12 y = year - a m = month' + (12 * a) - 3 - maybeDecodeDay = Just . decodeDay -- WRONG diff --git a/System/Time/Calendar/ISOWeek.hs b/System/Time/Calendar/ISOWeek.hs index e6412e4..2390f01 100644 --- a/System/Time/Calendar/ISOWeek.hs +++ b/System/Time/Calendar/ISOWeek.hs @@ -34,4 +34,3 @@ instance DayEncoding ISOWeek where decodeDay (ISOWeek y w d) = k - (mod k 7) + (toInteger ((w * 7) + d)) - 10 where k = decodeDay (YearDay y 6) - maybeDecodeDay = Just . decodeDay -- WRONG diff --git a/System/Time/Calendar/YearDay.hs b/System/Time/Calendar/YearDay.hs index d9ecf53..556c913 100644 --- a/System/Time/Calendar/YearDay.hs +++ b/System/Time/Calendar/YearDay.hs @@ -29,8 +29,6 @@ instance DayEncoding YearDay where decodeDay (YearDay year day) = (fromIntegral day) + (div (1532) 5) + (365 * y) + (div y 4) - (div y 100) + (div y 400) - 678882 where y = year - 1 - maybeDecodeDay t@(YearDay year day) | (day >= 1) && (day <= if isLeapYear year then 366 else 365) = Just (decodeDay t) - maybeDecodeDay _ = Nothing isLeapYear :: Integer -> Bool isLeapYear year = (mod year 4 == 0) && ((mod year 400 == 0) || not (mod year 100 == 0)) From git at git.haskell.org Fri Jan 23 22:53:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:53:58 +0000 (UTC) Subject: [commit: packages/time] master: fix week-based formatting chars, with more testing (f61178d) Message-ID: <20150123225358.7D69A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f61178de5671ebf0006c0a9500f2b0f0d84da152 >--------------------------------------------------------------- commit f61178de5671ebf0006c0a9500f2b0f0d84da152 Author: Ashley Yakeley Date: Tue May 10 03:33:55 2005 -0700 fix week-based formatting chars, with more testing darcs-hash:20050510103355-ac6dd-319f78ca2b58fb5a381a9882cfa9727f3bfa465d >--------------------------------------------------------------- f61178de5671ebf0006c0a9500f2b0f0d84da152 System/Time/Calendar/Format.hs | 13 ++++++++----- test/TestFormat.hs | 14 ++++++-------- 2 files changed, 14 insertions(+), 13 deletions(-) diff --git a/System/Time/Calendar/Format.hs b/System/Time/Calendar/Format.hs index eba951f..a3f08d3 100644 --- a/System/Time/Calendar/Format.hs +++ b/System/Time/Calendar/Format.hs @@ -79,14 +79,17 @@ weekDay day = fromInteger (mod (day + 3) 7) weekDay' :: ModJulianDay -> Int weekDay' day = weekDay (day - 1) + 1 -dayOfYear :: ModJulianDay -> Int -dayOfYear = ydDay . encodeDay - weekNumber :: ModJulianDay -> Int -weekNumber day = (div (dayOfYear day) 7) + 1 +weekNumber mjd = fromInteger ((div d 7) - (div k 7)) where + yd = ydDay (encodeDay mjd) + d = mjd + 3 + k = d - (toInteger yd) weekNumber' :: ModJulianDay -> Int -weekNumber' day = (div (dayOfYear day) 7) + 1 +weekNumber' mjd = fromInteger ((div d 7) - (div k 7)) where + yd = ydDay (encodeDay mjd) + d = mjd + 2 + k = d - (toInteger yd) instance FormatTime ModJulianDay where -- Aggregate diff --git a/test/TestFormat.hs b/test/TestFormat.hs index 651df97..89ed600 100644 --- a/test/TestFormat.hs +++ b/test/TestFormat.hs @@ -65,7 +65,8 @@ getYearP4 :: Integer -> UTCTime getYearP4 year = decodeLocalUTC utc (CalendarTime (GregorianDay year 12 31) midnight) times :: [UTCTime] -times = [baseTime0] ++ (fmap getDay [0..23]) +times = [baseTime0] ++ (fmap getDay [0..23]) ++ (fmap getDay [0..100]) ++ + (fmap getYearP1 [1980..2000]) ++ (fmap getYearP2 [1980..2000]) ++ (fmap getYearP3 [1980..2000]) ++ (fmap getYearP4 [1980..2000]) compareFormat :: String -> Timezone -> UTCTime -> IO () compareFormat fmt zone time = let @@ -83,11 +84,8 @@ compareFormat fmt zone time = let chars :: [Char] chars = "aAbBcCdDeFgGhHIjklmMnprRStTuUVwWxXyYzZ%" +formats :: [String] +formats = ["%G-W%V-%u","%U-%w","%W-%u"] ++ (fmap (\char -> '%':char:[]) chars) + main :: IO () -main = do - mapM_ (\day -> compareFormat "%G-W%V-%u" utc (getDay day)) [0..100] - mapM_ (\year -> compareFormat "%G-W%V-%u" utc (getYearP1 year)) [1980..2000] - mapM_ (\year -> compareFormat "%G-W%V-%u" utc (getYearP2 year)) [1980..2000] - mapM_ (\year -> compareFormat "%G-W%V-%u" utc (getYearP3 year)) [1980..2000] - mapM_ (\year -> compareFormat "%G-W%V-%u" utc (getYearP4 year)) [1980..2000] - mapM_ (\char -> let fmt = '%':char:[] in mapM_ (\time -> mapM_ (\zone -> compareFormat fmt zone time) zones) times) chars +main = mapM_ (\fmt -> mapM_ (\time -> mapM_ (\zone -> compareFormat fmt zone time) zones) times) formats From git at git.haskell.org Fri Jan 23 22:54:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:00 +0000 (UTC) Subject: [commit: packages/time] master: organise week functions (73c160c) Message-ID: <20150123225400.8430D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/73c160cf9cb8289b041389470d38afaacbd31387 >--------------------------------------------------------------- commit 73c160cf9cb8289b041389470d38afaacbd31387 Author: Ashley Yakeley Date: Tue May 10 04:03:21 2005 -0700 organise week functions darcs-hash:20050510110321-ac6dd-405622ed76952493da885fb866043a8d247ac06c >--------------------------------------------------------------- 73c160cf9cb8289b041389470d38afaacbd31387 Makefile | 1 + System/Time/Calendar/Format.hs | 28 +++++----------------------- System/Time/Calendar/YearDay.hs | 19 +++++++++++++++++++ 3 files changed, 25 insertions(+), 23 deletions(-) diff --git a/Makefile b/Makefile index c6c6b0b..36a93b7 100644 --- a/Makefile +++ b/Makefile @@ -82,6 +82,7 @@ System/Time/Calendar/Calendar.o : System/Time/Clock.hi System/Time/Calendar/Calendar.o : System/Time/Calendar/Timezone.hi System/Time/Calendar/Calendar.o : System/Time/Calendar/TimeOfDay.hi System/Time/Calendar/YearDay.o : System/Time/Calendar/YearDay.hs +System/Time/Calendar/YearDay.o : System/Time/Clock.hi System/Time/Calendar/YearDay.o : System/Time/Calendar/Private.hi System/Time/Calendar/YearDay.o : System/Time/Calendar/Calendar.hi System/Time/Calendar/Gregorian.o : System/Time/Calendar/Gregorian.hs diff --git a/System/Time/Calendar/Format.hs b/System/Time/Calendar/Format.hs index a3f08d3..398c4c0 100644 --- a/System/Time/Calendar/Format.hs +++ b/System/Time/Calendar/Format.hs @@ -73,24 +73,6 @@ instance FormatTime Timezone where formatCharacter 'Z' = Just (\_ -> timezoneName) formatCharacter _ = Nothing -weekDay :: ModJulianDay -> Int -weekDay day = fromInteger (mod (day + 3) 7) - -weekDay' :: ModJulianDay -> Int -weekDay' day = weekDay (day - 1) + 1 - -weekNumber :: ModJulianDay -> Int -weekNumber mjd = fromInteger ((div d 7) - (div k 7)) where - yd = ydDay (encodeDay mjd) - d = mjd + 3 - k = d - (toInteger yd) - -weekNumber' :: ModJulianDay -> Int -weekNumber' mjd = fromInteger ((div d 7) - (div k 7)) where - yd = ydDay (encodeDay mjd) - d = mjd + 2 - k = d - (toInteger yd) - instance FormatTime ModJulianDay where -- Aggregate formatCharacter 'D' = Just (\locale -> formatTime locale "%m/%d/%y") @@ -119,11 +101,11 @@ instance FormatTime ModJulianDay where formatCharacter 'u' = Just (\_ -> show . isowDay . encodeDay) -- Day of week - formatCharacter 'a' = Just (\locale -> snd . ((wDays locale) !!) . weekDay) - formatCharacter 'A' = Just (\locale -> fst . ((wDays locale) !!) . weekDay) - formatCharacter 'U' = Just (\_ -> show2 . weekNumber) - formatCharacter 'w' = Just (\_ -> show . weekDay) - formatCharacter 'W' = Just (\_ -> show2 . weekNumber') + formatCharacter 'a' = Just (\locale -> snd . ((wDays locale) !!) . snd . sundayStartWeek) + formatCharacter 'A' = Just (\locale -> fst . ((wDays locale) !!) . snd . sundayStartWeek) + formatCharacter 'U' = Just (\_ -> show2 . fst . sundayStartWeek) + formatCharacter 'w' = Just (\_ -> show . snd . sundayStartWeek) + formatCharacter 'W' = Just (\_ -> show2 . fst . mondayStartWeek) -- Default formatCharacter _ = Nothing diff --git a/System/Time/Calendar/YearDay.hs b/System/Time/Calendar/YearDay.hs index 556c913..2c120eb 100644 --- a/System/Time/Calendar/YearDay.hs +++ b/System/Time/Calendar/YearDay.hs @@ -4,6 +4,7 @@ module System.Time.Calendar.YearDay where import System.Time.Calendar.Calendar import System.Time.Calendar.Private +import System.Time.Clock -- | ISO 8601 Ordinal Date data YearDay = YearDay { @@ -32,3 +33,21 @@ instance DayEncoding YearDay where isLeapYear :: Integer -> Bool isLeapYear year = (mod year 4 == 0) && ((mod year 400 == 0) || not (mod year 100 == 0)) + +-- | Get the number of the Monday-starting week in the year and the day of the week. +-- The first Monday is the first day of week 1, any earlier days in the year are week 0 (as \"%W\" in formatTime). +-- Monday is 1, Sunday is 7 (as \"%u\" in formatTime). +mondayStartWeek :: ModJulianDay -> (Int,Int) +mondayStartWeek mjd =(fromInteger ((div d 7) - (div k 7)),fromInteger (mod d 7) + 1) where + yd = ydDay (encodeDay mjd) + d = mjd + 2 + k = d - (toInteger yd) + +-- | Get the number of the Sunday-starting week in the year and the day of the week. +-- The first Sunday is the first day of week 1, any earlier days in the year are week 0 (as \"%U\" in formatTime). +-- Sunday is 0, Saturday is 6 (as \"%w\" in formatTime). +sundayStartWeek :: ModJulianDay -> (Int,Int) +sundayStartWeek mjd =(fromInteger ((div d 7) - (div k 7)),fromInteger (mod d 7)) where + yd = ydDay (encodeDay mjd) + d = mjd + 3 + k = d - (toInteger yd) From git at git.haskell.org Fri Jan 23 22:54:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:02 +0000 (UTC) Subject: [commit: packages/time] master: clean up some type names, more doc (23be1cb) Message-ID: <20150123225402.8C6493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/23be1cbc6f4656788094ab2356f4ebe80f81f9ec >--------------------------------------------------------------- commit 23be1cbc6f4656788094ab2356f4ebe80f81f9ec Author: Ashley Yakeley Date: Wed May 11 02:02:36 2005 -0700 clean up some type names, more doc darcs-hash:20050511090236-ac6dd-933871a97e6db2b7c089579ec25f4016211be440 >--------------------------------------------------------------- 23be1cbc6f4656788094ab2356f4ebe80f81f9ec System/Time/Calendar/Calendar.hs | 35 +++++++++++++++++++++-------------- System/Time/Calendar/Format.hs | 24 ++++++++++++------------ System/Time/Calendar/Gregorian.hs | 10 +++++----- System/Time/Calendar/TimeOfDay.hs | 16 ++++++++-------- test/ShowDST.hs | 4 ++-- test/TestFormat.hs | 12 ++++++------ test/TestTime.hs | 2 +- 7 files changed, 55 insertions(+), 48 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 23be1cbc6f4656788094ab2356f4ebe80f81f9ec From git at git.haskell.org Fri Jan 23 22:54:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:04 +0000 (UTC) Subject: [commit: packages/time] master: CalendarTime synonym with convenience functions (f853253) Message-ID: <20150123225404.945863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f8532533d788c272d59278286c021eab2b973744 >--------------------------------------------------------------- commit f8532533d788c272d59278286c021eab2b973744 Author: Ashley Yakeley Date: Wed May 11 02:30:27 2005 -0700 CalendarTime synonym with convenience functions darcs-hash:20050511093027-ac6dd-4336dabf134f48c15b0b922d4ee54d11567b7975 >--------------------------------------------------------------- f8532533d788c272d59278286c021eab2b973744 System/Time/Calendar.hs | 39 ++++++++++++++++++++++++++++++++++++++- System/Time/Calendar/Gregorian.hs | 7 +------ test/CurrentTime.hs | 5 ++--- test/ShowDST.hs | 4 ++-- test/TestFormat.hs | 2 +- test/TestTime.hs | 16 ++++++++-------- 6 files changed, 52 insertions(+), 21 deletions(-) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index 9b5d890..4b848e5 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -8,9 +8,13 @@ module System.Time.Calendar module System.Time.Calendar.YearDay, module System.Time.Calendar.Gregorian, module System.Time.Calendar.ISOWeek, - module System.Time.Calendar.Format + module System.Time.Calendar.Format, + module System.Time.Calendar ) where +import Data.Fixed +import System.Time.Clock + import System.Time.Calendar.Timezone import System.Time.Calendar.TimeOfDay import System.Time.Calendar.Calendar @@ -18,3 +22,36 @@ import System.Time.Calendar.YearDay import System.Time.Calendar.Gregorian import System.Time.Calendar.ISOWeek import System.Time.Calendar.Format + +type CalendarTime = ZonedTime (DayAndTime GregorianDay) + +calendarTime :: Timezone -> Integer -> Int -> Int -> Int -> Int -> Pico -> CalendarTime +calendarTime zone year month day hour minute second = + ZonedTime (DayAndTime (GregorianDay year month day) (TimeOfDay hour minute second)) zone + +ctZone :: CalendarTime -> Timezone +ctZone = ztZone + +ctYear :: CalendarTime -> Integer +ctYear = gregYear . dtDay . ztTime + +ctMonth :: CalendarTime -> Int +ctMonth = gregMonth . dtDay . ztTime + +ctDay :: CalendarTime -> Int +ctDay = gregDay . dtDay . ztTime + +ctHour :: CalendarTime -> Int +ctHour = todHour . dtTime . ztTime + +ctMin :: CalendarTime -> Int +ctMin = todMin . dtTime . ztTime + +ctSec :: CalendarTime -> Pico +ctSec = todSec . dtTime . ztTime + +getCalendarTime :: IO CalendarTime +getCalendarTime = do + t <- getCurrentTime + zone <- getTimezone t + return (encodeUTC zone t) diff --git a/System/Time/Calendar/Gregorian.hs b/System/Time/Calendar/Gregorian.hs index 77f389d..3e986bd 100644 --- a/System/Time/Calendar/Gregorian.hs +++ b/System/Time/Calendar/Gregorian.hs @@ -2,7 +2,7 @@ module System.Time.Calendar.Gregorian ( - GregorianDay(..),GregorianTime,ZonedGregorianTime + GregorianDay(..) -- calendrical arithmetic -- e.g. "one month after March 31st" @@ -19,10 +19,6 @@ data GregorianDay = GregorianDay { gregDay :: Int } deriving (Eq,Ord) -type GregorianTime = DayAndTime GregorianDay - -type ZonedGregorianTime = ZonedTime (DayAndTime GregorianDay) - instance Show GregorianDay where show (GregorianDay y m d) = (if y > 0 then show y else (show (1 - y) ++ "BCE")) ++ "-" ++ (show2 m) ++ "-" ++ (show2 d) @@ -30,7 +26,6 @@ findMonthDay :: [Int] -> Int -> (Int,Int) findMonthDay (n:ns) yd | yd > n = (\(m,d) -> (m + 1,d)) (findMonthDay ns (yd - n)) findMonthDay _ yd = (1,yd) - monthLengths :: Bool -> [Int] monthLengths isleap = [31,if isleap then 29 else 28,31,30,31,30,31,31,30,31,30,31] diff --git a/test/CurrentTime.hs b/test/CurrentTime.hs index 2bb3f11..ae00fae 100644 --- a/test/CurrentTime.hs +++ b/test/CurrentTime.hs @@ -8,7 +8,6 @@ main :: IO () main = do now <- getCurrentTime putStrLn (show (utctDay now) ++ "," ++ show (utctDayTime now)) - putStrLn (show (encodeLocalUTC utc now :: GregorianTime)) + putStrLn (show (encodeUTC utc now :: CalendarTime)) myzone <- getCurrentTimezone - putStrLn ("timezone: " ++ show myzone) - putStrLn (show (encodeLocalUTC myzone now :: GregorianTime)) + putStrLn (show (encodeUTC myzone now :: CalendarTime)) diff --git a/test/ShowDST.hs b/test/ShowDST.hs index 655beca..a061060 100644 --- a/test/ShowDST.hs +++ b/test/ShowDST.hs @@ -19,7 +19,7 @@ findTransition a b = do return (tp ++ tq) showZoneTime :: Timezone -> UTCTime -> String -showZoneTime zone time = (show (encodeLocalUTC zone time :: GregorianTime)) ++ " " ++ (show zone) +showZoneTime zone time = show (encodeUTC zone time :: CalendarTime) showTransition :: (UTCTime,Timezone,Timezone) -> String showTransition (time,zone1,zone2) = (showZoneTime zone1 time) ++ " => " ++ (showZoneTime zone2 time) @@ -28,7 +28,7 @@ main :: IO () main = do now <- getCurrentTime zone <- getTimezone now - let year = cdYear (dtDay (encodeLocalUTC zone now)) + let year = gregYear (dtDay (encodeLocalUTC zone now)) putStrLn ("DST adjustments for " ++ show year ++ ":") let t0 = monthBeginning zone year 1 let t1 = monthBeginning zone year 4 diff --git a/test/TestFormat.hs b/test/TestFormat.hs index fbb1b7d..d4a7675 100644 --- a/test/TestFormat.hs +++ b/test/TestFormat.hs @@ -70,7 +70,7 @@ times = [baseTime0] ++ (fmap getDay [0..23]) ++ (fmap getDay [0..100]) ++ compareFormat :: String -> Timezone -> UTCTime -> IO () compareFormat fmt zone time = let - ctime = encodeUTC zone time :: ZonedGregorianTime + ctime = encodeUTC zone time :: CalendarTime haskellText = formatTime locale fmt ctime in do unixText <- unixFormatTime fmt zone time diff --git a/test/TestTime.hs b/test/TestTime.hs index 13a1ead..908ad88 100644 --- a/test/TestTime.hs +++ b/test/TestTime.hs @@ -40,7 +40,7 @@ showUTCTime (UTCTime d t) = show d ++ "," ++ show t myzone :: Timezone myzone = hoursToTimezone (- 8) -leapSec1998Cal :: GregorianTime +leapSec1998Cal :: DayAndTime GregorianDay leapSec1998Cal = DayAndTime (GregorianDay 1998 12 31) (TimeOfDay 23 59 60.5) leapSec1998 :: UTCTime @@ -52,7 +52,7 @@ testUTC = do showCal 51178 putStrLn (show leapSec1998Cal) putStrLn (showUTCTime leapSec1998) - let lsMineCal = encodeLocalUTC myzone leapSec1998 :: GregorianTime + let lsMineCal = encodeLocalUTC myzone leapSec1998 :: DayAndTime GregorianDay putStrLn (show lsMineCal) let lsMine = decodeLocalUTC myzone lsMineCal putStrLn (showUTCTime lsMine) @@ -66,12 +66,12 @@ poslong = 120 testUT1 :: IO () testUT1 = do putStrLn "" - putStrLn (show (encodeLocalUT1 0 51604.0 :: GregorianTime)) - putStrLn (show (encodeLocalUT1 0 51604.5 :: GregorianTime)) - putStrLn (show (encodeLocalUT1 neglong 51604.0 :: GregorianTime)) - putStrLn (show (encodeLocalUT1 neglong 51604.5 :: GregorianTime)) - putStrLn (show (encodeLocalUT1 poslong 51604.0 :: GregorianTime)) - putStrLn (show (encodeLocalUT1 poslong 51604.5 :: GregorianTime)) + putStrLn (show (encodeLocalUT1 0 51604.0 :: DayAndTime GregorianDay)) + putStrLn (show (encodeLocalUT1 0 51604.5 :: DayAndTime GregorianDay)) + putStrLn (show (encodeLocalUT1 neglong 51604.0 :: DayAndTime GregorianDay)) + putStrLn (show (encodeLocalUT1 neglong 51604.5 :: DayAndTime GregorianDay)) + putStrLn (show (encodeLocalUT1 poslong 51604.0 :: DayAndTime GregorianDay)) + putStrLn (show (encodeLocalUT1 poslong 51604.5 :: DayAndTime GregorianDay)) main :: IO () main = do From git at git.haskell.org Fri Jan 23 22:54:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:06 +0000 (UTC) Subject: [commit: packages/time] master: better tz for test (865557b) Message-ID: <20150123225406.9BD293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/865557b3d37b3cba48ed1c4d4f12128f19c7f28f >--------------------------------------------------------------- commit 865557b3d37b3cba48ed1c4d4f12128f19c7f28f Author: Ashley Yakeley Date: Wed May 11 22:50:47 2005 -0700 better tz for test darcs-hash:20050512055047-ac6dd-1f4486d8b5ca0fa95be731b31b603535bb5695cc >--------------------------------------------------------------- 865557b3d37b3cba48ed1c4d4f12128f19c7f28f test/TestFormat.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/TestFormat.hs b/test/TestFormat.hs index d4a7675..a273448 100644 --- a/test/TestFormat.hs +++ b/test/TestFormat.hs @@ -38,7 +38,7 @@ locale :: TimeLocale locale = defaultTimeLocale {dateTimeFmt = "%a %b %e %H:%M:%S %Y"} zones :: [Timezone] -zones = [utc,hoursToTimezone (- 7)] +zones = [utc,MkTimezone 87 True "Fenwickian Daylight Time"] posixDay :: UTCDiffTime posixDay = 86400 From git at git.haskell.org Fri Jan 23 22:54:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:08 +0000 (UTC) Subject: [commit: packages/time] master: better C type for name param (7a52230) Message-ID: <20150123225408.A220C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/7a522300362bccc114014743d3e0d6b2823fa252 >--------------------------------------------------------------- commit 7a522300362bccc114014743d3e0d6b2823fa252 Author: Ashley Yakeley Date: Wed May 11 22:55:54 2005 -0700 better C type for name param darcs-hash:20050512055554-ac6dd-5dd656b851561c2626a5a62eaef9600aeab35490 >--------------------------------------------------------------- 7a522300362bccc114014743d3e0d6b2823fa252 timestuff.c | 2 +- timestuff.h | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/timestuff.c b/timestuff.c index 386616e..0fdbd9e 100644 --- a/timestuff.c +++ b/timestuff.c @@ -1,6 +1,6 @@ #include "timestuff.h" -long int get_current_timezone_seconds (time_t t,int* dst,char** name) +long int get_current_timezone_seconds (time_t t,int* dst,char const* * name) { struct tm tmd; struct tm* ptm = localtime_r(&t,&tmd); diff --git a/timestuff.h b/timestuff.h index 936cd84..c161fc9 100644 --- a/timestuff.h +++ b/timestuff.h @@ -1,3 +1,3 @@ #include -long int get_current_timezone_seconds (time_t,int* dst,char** name); +long int get_current_timezone_seconds (time_t,int* dst,char const* * name); From git at git.haskell.org Fri Jan 23 22:54:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:10 +0000 (UTC) Subject: [commit: packages/time] master: XCode 2.0 project (1ecbd6c) Message-ID: <20150123225410.A97293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1ecbd6c347b20e978149947e4623a62dd662193e >--------------------------------------------------------------- commit 1ecbd6c347b20e978149947e4623a62dd662193e Author: Ashley Yakeley Date: Mon May 16 01:36:36 2005 -0700 XCode 2.0 project darcs-hash:20050516083636-ac6dd-b6506418cfe358e9e64528fc691c54bd5e56fac3 >--------------------------------------------------------------- 1ecbd6c347b20e978149947e4623a62dd662193e Makefile | 7 +- TimeLib.xcode/project.pbxproj | 259 ++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 265 insertions(+), 1 deletion(-) diff --git a/Makefile b/Makefile index 36a93b7..fe5e66d 100644 --- a/Makefile +++ b/Makefile @@ -1,10 +1,13 @@ -default: build doc +default: build build: $(patsubst %.hs,%.hi,$(SRCS)) libTimeLib.a test: build cd test && make +cleantest: build + cd test && make clean + SRCS = Data/Fixed.hs \ System/Time/Clock.hs \ System/Time/TAI.hs \ @@ -54,6 +57,8 @@ FORCE: .SECONDARY: +.PHONY: default build test doc clean + depend: $(SRCS) ghc -M $^ diff --git a/TimeLib.xcode/project.pbxproj b/TimeLib.xcode/project.pbxproj new file mode 100644 index 0000000..8a889aa --- /dev/null +++ b/TimeLib.xcode/project.pbxproj @@ -0,0 +1,259 @@ +// !$*UTF8*$! +{ + archiveVersion = 1; + classes = { + }; + objectVersion = 39; + objects = { + AB01DCEA083747B1003C9EF7 = { + children = ( + AB01DCF508374807003C9EF7, + AB01DCF908374808003C9EF7, + AB01DCF808374808003C9EF7, + AB01DD0008374848003C9EF7, + AB35747F08386FCD00B5F897, + ); + isa = PBXGroup; + refType = 4; + sourceTree = ""; + }; + AB01DCEC083747B1003C9EF7 = { + buildSettings = { + COPY_PHASE_STRIP = NO; + }; + isa = PBXBuildStyle; + name = Development; + }; + AB01DCED083747B1003C9EF7 = { + buildSettings = { + COPY_PHASE_STRIP = YES; + }; + isa = PBXBuildStyle; + name = Deployment; + }; + AB01DCEE083747B1003C9EF7 = { + buildSettings = { + }; + buildStyles = ( + AB01DCEC083747B1003C9EF7, + AB01DCED083747B1003C9EF7, + ); + hasScannedForEncodings = 0; + isa = PBXProject; + mainGroup = AB01DCEA083747B1003C9EF7; + projectDirPath = ""; + targets = ( + AB01DD2108374A56003C9EF7, + AB3571F5083759B20059BD19, + ); + }; + AB01DCF508374807003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.make; + path = Makefile; + refType = 4; + sourceTree = ""; + }; + AB01DCF608374808003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = Setup.hs; + refType = 4; + sourceTree = ""; + }; + AB01DCF708374808003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = text; + path = TimeLib.cabal; + refType = 4; + sourceTree = ""; + }; + AB01DCF808374808003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.c.c; + path = timestuff.c; + refType = 4; + sourceTree = ""; + }; + AB01DCF908374808003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.c.h; + path = timestuff.h; + refType = 4; + sourceTree = ""; + }; + AB01DCFC08374838003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = Calendar.hs; + refType = 4; + sourceTree = ""; + }; + AB01DCFD08374838003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = Clock.hs; + refType = 4; + sourceTree = ""; + }; + AB01DCFE08374838003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = TAI.hs; + refType = 4; + sourceTree = ""; + }; + AB01DD0008374848003C9EF7 = { + children = ( + AB01DCFD08374838003C9EF7, + AB01DCFE08374838003C9EF7, + AB01DD0D083748C0003C9EF7, + AB01DCFC08374838003C9EF7, + ); + isa = PBXGroup; + name = Time; + path = System/Time; + refType = 4; + sourceTree = ""; + }; + AB01DD0D083748C0003C9EF7 = { + children = ( + AB01DD16083748EC003C9EF7, + AB01DD18083748EC003C9EF7, + AB01DD17083748EC003C9EF7, + AB01DD12083748EC003C9EF7, + AB01DD19083748EC003C9EF7, + AB01DD14083748EC003C9EF7, + AB01DD15083748EC003C9EF7, + AB01DD13083748EC003C9EF7, + ); + isa = PBXGroup; + path = Calendar; + refType = 4; + sourceTree = ""; + }; + AB01DD12083748EC003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = Calendar.hs; + refType = 4; + sourceTree = ""; + }; + AB01DD13083748EC003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = Format.hs; + refType = 4; + sourceTree = ""; + }; + AB01DD14083748EC003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = Gregorian.hs; + refType = 4; + sourceTree = ""; + }; + AB01DD15083748EC003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = ISOWeek.hs; + refType = 4; + sourceTree = ""; + }; + AB01DD16083748EC003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = Private.hs; + refType = 4; + sourceTree = ""; + }; + AB01DD17083748EC003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = TimeOfDay.hs; + refType = 4; + sourceTree = ""; + }; + AB01DD18083748EC003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = Timezone.hs; + refType = 4; + sourceTree = ""; + }; + AB01DD19083748EC003C9EF7 = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = YearDay.hs; + refType = 4; + sourceTree = ""; + }; + AB01DD2108374A56003C9EF7 = { + buildArgumentsString = "$(ACTION)"; + buildPhases = ( + ); + buildSettings = { + OTHER_CFLAGS = ""; + OTHER_LDFLAGS = ""; + OTHER_REZFLAGS = ""; + PRODUCT_NAME = Untitled; + SECTORDER_FLAGS = ""; + WARNING_CFLAGS = "-Wmost -Wno-four-char-constants -Wno-unknown-pragmas"; + }; + buildToolPath = /usr/bin/make; + dependencies = ( + ); + isa = PBXLegacyTarget; + name = Build; + passBuildSettingsInEnvironment = 1; + productName = Untitled; + }; + AB3571F5083759B20059BD19 = { + buildArgumentsString = "$(ACTION)test"; + buildPhases = ( + ); + buildSettings = { + OTHER_CFLAGS = ""; + OTHER_LDFLAGS = ""; + OTHER_REZFLAGS = ""; + PRODUCT_NAME = Test; + SECTORDER_FLAGS = ""; + WARNING_CFLAGS = "-Wmost -Wno-four-char-constants -Wno-unknown-pragmas"; + }; + buildToolPath = /usr/bin/make; + dependencies = ( + ); + isa = PBXLegacyTarget; + name = Test; + passBuildSettingsInEnvironment = 1; + productName = Test; + }; + AB35747F08386FCD00B5F897 = { + children = ( + AB01DCF708374808003C9EF7, + AB01DCF608374808003C9EF7, + ); + isa = PBXGroup; + name = Cabal; + refType = 4; + sourceTree = ""; + }; + }; + rootObject = AB01DCEE083747B1003C9EF7; +} From git at git.haskell.org Fri Jan 23 22:54:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:12 +0000 (UTC) Subject: [commit: packages/time] master: clean up XCode project & makefile (0bb6871) Message-ID: <20150123225412.B095F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/0bb687137246fa43f8fe42f3720463e2f105a9ac >--------------------------------------------------------------- commit 0bb687137246fa43f8fe42f3720463e2f105a9ac Author: Ashley Yakeley Date: Wed May 18 01:13:06 2005 -0700 clean up XCode project & makefile darcs-hash:20050518081306-ac6dd-2b83dc54af7951b3697bbf75aff9c2d05195992c >--------------------------------------------------------------- 0bb687137246fa43f8fe42f3720463e2f105a9ac Makefile | 13 ++- TimeLib.xcode/project.pbxproj | 217 +++++++++++++++++++++++++++++++++++++++++- 2 files changed, 225 insertions(+), 5 deletions(-) diff --git a/Makefile b/Makefile index fe5e66d..442f354 100644 --- a/Makefile +++ b/Makefile @@ -1,11 +1,11 @@ -default: build +default: build test doc build: $(patsubst %.hs,%.hi,$(SRCS)) libTimeLib.a test: build cd test && make -cleantest: build +cleantest: cd test && make clean SRCS = Data/Fixed.hs \ @@ -29,8 +29,13 @@ libTimeLib.a: $(patsubst %.hs,%.o,$(SRCS)) timestuff.o ar cru $@ $^ ranlib $@ -clean: - rm -rf doc haddock *.a *.o *.hi $(patsubst %.hs,%.o,$(SRCS)) $(patsubst %.hs,%.hi,$(SRCS)) Makefile.bak +cleanbuild: + rm -rf *.a *.o *.hi $(patsubst %.hs,%.o,$(SRCS)) $(patsubst %.hs,%.hi,$(SRCS)) Makefile.bak + +cleandoc: + rm -rf doc haddock + +clean: cleandoc cleantest cleanbuild doc: haddock/index.html diff --git a/TimeLib.xcode/project.pbxproj b/TimeLib.xcode/project.pbxproj index 8a889aa..c2742eb 100644 --- a/TimeLib.xcode/project.pbxproj +++ b/TimeLib.xcode/project.pbxproj @@ -10,8 +10,10 @@ AB01DCF508374807003C9EF7, AB01DCF908374808003C9EF7, AB01DCF808374808003C9EF7, + ABFA25DC0839F8C90096540C, AB01DD0008374848003C9EF7, AB35747F08386FCD00B5F897, + ABFA25EC0839F9FD0096540C, ); isa = PBXGroup; refType = 4; @@ -45,6 +47,8 @@ targets = ( AB01DD2108374A56003C9EF7, AB3571F5083759B20059BD19, + ABFA25E20839F9310096540C, + ABFA25E50839F99F0096540C, ); }; AB01DCF508374807003C9EF7 = { @@ -205,7 +209,7 @@ sourceTree = ""; }; AB01DD2108374A56003C9EF7 = { - buildArgumentsString = "$(ACTION)"; + buildArgumentsString = "$(ACTION)build"; buildPhases = ( ); buildSettings = { @@ -254,6 +258,217 @@ refType = 4; sourceTree = ""; }; + ABFA25DC0839F8C90096540C = { + children = ( + ABFA25DF0839F8F70096540C, + ); + isa = PBXGroup; + path = Data; + refType = 4; + sourceTree = ""; + }; + ABFA25DF0839F8F70096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = Fixed.hs; + refType = 4; + sourceTree = ""; + }; + ABFA25E20839F9310096540C = { + buildArgumentsString = "$(ACTION)doc"; + buildPhases = ( + ); + buildSettings = { + OTHER_CFLAGS = ""; + OTHER_LDFLAGS = ""; + OTHER_REZFLAGS = ""; + PRODUCT_NAME = Untitled; + SECTORDER_FLAGS = ""; + WARNING_CFLAGS = "-Wmost -Wno-four-char-constants -Wno-unknown-pragmas"; + }; + buildToolPath = /usr/bin/make; + dependencies = ( + ); + isa = PBXLegacyTarget; + name = Documentation; + passBuildSettingsInEnvironment = 1; + productName = Untitled; + }; + ABFA25E50839F99F0096540C = { + buildPhases = ( + ); + buildSettings = { + OPTIMIZATION_CFLAGS = ""; + OTHER_CFLAGS = ""; + OTHER_LDFLAGS = ""; + OTHER_REZFLAGS = ""; + PRODUCT_NAME = Everything; + SECTORDER_FLAGS = ""; + WARNING_CFLAGS = "-Wmost -Wno-four-char-constants -Wno-unknown-pragmas"; + }; + dependencies = ( + ABFA25E90839F9AF0096540C, + ABFA25EB0839F9B10096540C, + ABFA25E70839F9AD0096540C, + ); + isa = PBXAggregateTarget; + name = Everything; + productName = Everything; + }; + ABFA25E60839F9AD0096540C = { + containerPortal = AB01DCEE083747B1003C9EF7; + isa = PBXContainerItemProxy; + proxyType = 1; + remoteGlobalIDString = ABFA25E20839F9310096540C; + remoteInfo = Documentation; + }; + ABFA25E70839F9AD0096540C = { + isa = PBXTargetDependency; + target = ABFA25E20839F9310096540C; + targetProxy = ABFA25E60839F9AD0096540C; + }; + ABFA25E80839F9AF0096540C = { + containerPortal = AB01DCEE083747B1003C9EF7; + isa = PBXContainerItemProxy; + proxyType = 1; + remoteGlobalIDString = AB01DD2108374A56003C9EF7; + remoteInfo = Build; + }; + ABFA25E90839F9AF0096540C = { + isa = PBXTargetDependency; + target = AB01DD2108374A56003C9EF7; + targetProxy = ABFA25E80839F9AF0096540C; + }; + ABFA25EA0839F9B10096540C = { + containerPortal = AB01DCEE083747B1003C9EF7; + isa = PBXContainerItemProxy; + proxyType = 1; + remoteGlobalIDString = AB3571F5083759B20059BD19; + remoteInfo = Test; + }; + ABFA25EB0839F9B10096540C = { + isa = PBXTargetDependency; + target = AB3571F5083759B20059BD19; + targetProxy = ABFA25EA0839F9B10096540C; + }; + ABFA25EC0839F9FD0096540C = { + children = ( + ABFA2623083B28C00096540C, + ABFA2624083B28C00096540C, + ABFA2625083B28C00096540C, + ABFA2626083B28C00096540C, + ABFA2627083B28C00096540C, + ABFA2628083B28C00096540C, + ABFA2629083B28C00096540C, + ABFA262A083B28C00096540C, + ABFA262B083B28C00096540C, + ABFA262C083B28C00096540C, + ABFA262D083B28C00096540C, + ABFA262E083B28C00096540C, + ); + isa = PBXGroup; + name = Test; + path = test; + refType = 4; + sourceTree = ""; + }; + ABFA2623083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = ConvertBack.hs; + refType = 4; + sourceTree = ""; + }; + ABFA2624083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = CurrentTime.hs; + refType = 4; + sourceTree = ""; + }; + ABFA2625083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.make; + path = Makefile; + refType = 4; + sourceTree = ""; + }; + ABFA2626083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = ShowDST.hs; + refType = 4; + sourceTree = ""; + }; + ABFA2627083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = TestFixed.hs; + refType = 4; + sourceTree = ""; + }; + ABFA2628083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = text; + path = TestFixed.ref; + refType = 4; + sourceTree = ""; + }; + ABFA2629083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = TestFormat.hs; + refType = 4; + sourceTree = ""; + }; + ABFA262A083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.c.c; + path = TestFormatStuff.c; + refType = 4; + sourceTree = ""; + }; + ABFA262B083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.c.h; + path = TestFormatStuff.h; + refType = 4; + sourceTree = ""; + }; + ABFA262C083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = TestTime.hs; + refType = 4; + sourceTree = ""; + }; + ABFA262D083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = text; + path = TestTime.ref; + refType = 4; + sourceTree = ""; + }; + ABFA262E083B28C00096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = sourcecode.haskell; + path = TimeZone.hs; + refType = 4; + sourceTree = ""; + }; }; rootObject = AB01DCEE083747B1003C9EF7; } From git at git.haskell.org Fri Jan 23 22:54:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:14 +0000 (UTC) Subject: [commit: packages/time] master: hide submodules in Haddock docs (e128961) Message-ID: <20150123225414.B729F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e1289618cca447ca7348da0d032b1dd0dc2f5a84 >--------------------------------------------------------------- commit e1289618cca447ca7348da0d032b1dd0dc2f5a84 Author: Ashley Yakeley Date: Wed May 18 01:14:23 2005 -0700 hide submodules in Haddock docs darcs-hash:20050518081423-ac6dd-76ee3e4f8b6b1ee8e55235367594fb52d321a4ee >--------------------------------------------------------------- e1289618cca447ca7348da0d032b1dd0dc2f5a84 System/Time/Calendar.hs | 1 + System/Time/Calendar/Calendar.hs | 2 ++ System/Time/Calendar/Format.hs | 8 +++++++- System/Time/Calendar/Gregorian.hs | 2 ++ System/Time/Calendar/ISOWeek.hs | 7 ++++++- System/Time/Calendar/Private.hs | 1 + System/Time/Calendar/TimeOfDay.hs | 2 ++ System/Time/Calendar/Timezone.hs | 3 ++- System/Time/Calendar/YearDay.hs | 7 ++++++- 9 files changed, 29 insertions(+), 4 deletions(-) diff --git a/System/Time/Calendar.hs b/System/Time/Calendar.hs index 4b848e5..7035149 100644 --- a/System/Time/Calendar.hs +++ b/System/Time/Calendar.hs @@ -9,6 +9,7 @@ module System.Time.Calendar module System.Time.Calendar.Gregorian, module System.Time.Calendar.ISOWeek, module System.Time.Calendar.Format, + -- * CalendarTime module System.Time.Calendar ) where diff --git a/System/Time/Calendar/Calendar.hs b/System/Time/Calendar/Calendar.hs index f15890d..cc4e0c3 100644 --- a/System/Time/Calendar/Calendar.hs +++ b/System/Time/Calendar/Calendar.hs @@ -1,7 +1,9 @@ {-# OPTIONS -Wall -Werror #-} +-- #hide module System.Time.Calendar.Calendar ( + -- * Classes -- "Calendrical" format DayAndTime(..),DayEncoding(..), diff --git a/System/Time/Calendar/Format.hs b/System/Time/Calendar/Format.hs index db63090..e81312a 100644 --- a/System/Time/Calendar/Format.hs +++ b/System/Time/Calendar/Format.hs @@ -1,6 +1,12 @@ {-# OPTIONS -Wall -Werror #-} -module System.Time.Calendar.Format where + +-- #hide +module System.Time.Calendar.Format + ( + -- * UNIX-style formatting + module System.Time.Calendar.Format + ) where import System.Time.Calendar.ISOWeek import System.Time.Calendar.Gregorian diff --git a/System/Time/Calendar/Gregorian.hs b/System/Time/Calendar/Gregorian.hs index 3e986bd..d4cced7 100644 --- a/System/Time/Calendar/Gregorian.hs +++ b/System/Time/Calendar/Gregorian.hs @@ -1,7 +1,9 @@ {-# OPTIONS -Wall -Werror #-} +-- #hide module System.Time.Calendar.Gregorian ( + -- * Gregorian calendar GregorianDay(..) -- calendrical arithmetic diff --git a/System/Time/Calendar/ISOWeek.hs b/System/Time/Calendar/ISOWeek.hs index 2390f01..eb03a39 100644 --- a/System/Time/Calendar/ISOWeek.hs +++ b/System/Time/Calendar/ISOWeek.hs @@ -1,6 +1,11 @@ {-# OPTIONS -Wall -Werror #-} -module System.Time.Calendar.ISOWeek where +-- #hide +module System.Time.Calendar.ISOWeek + ( + -- * ISO Week calendar + module System.Time.Calendar.ISOWeek + ) where import System.Time.Calendar.YearDay import System.Time.Calendar.Calendar diff --git a/System/Time/Calendar/Private.hs b/System/Time/Calendar/Private.hs index db63216..17d2322 100644 --- a/System/Time/Calendar/Private.hs +++ b/System/Time/Calendar/Private.hs @@ -1,5 +1,6 @@ {-# OPTIONS -Wall -Werror #-} +-- #hide module System.Time.Calendar.Private where import Data.Fixed diff --git a/System/Time/Calendar/TimeOfDay.hs b/System/Time/Calendar/TimeOfDay.hs index bf04e78..9bd8213 100644 --- a/System/Time/Calendar/TimeOfDay.hs +++ b/System/Time/Calendar/TimeOfDay.hs @@ -1,7 +1,9 @@ {-# OPTIONS -Wall -Werror #-} +-- #hide module System.Time.Calendar.TimeOfDay ( + -- * Time of day TimeOfDay(..),midnight,midday, utcToLocalTimeOfDay,localToUTCTimeOfDay, timeToTimeOfDay,timeOfDayToTime, diff --git a/System/Time/Calendar/Timezone.hs b/System/Time/Calendar/Timezone.hs index dc836ca..fc2423d 100644 --- a/System/Time/Calendar/Timezone.hs +++ b/System/Time/Calendar/Timezone.hs @@ -1,8 +1,9 @@ {-# OPTIONS -ffi -Wall -Werror #-} +-- #hide module System.Time.Calendar.Timezone ( - -- time zones + -- * Time zones Timezone(..),timezoneOffsetString,minutesToTimezone,hoursToTimezone,utc, -- getting the locale time zone diff --git a/System/Time/Calendar/YearDay.hs b/System/Time/Calendar/YearDay.hs index 2c120eb..49e3c58 100644 --- a/System/Time/Calendar/YearDay.hs +++ b/System/Time/Calendar/YearDay.hs @@ -1,6 +1,11 @@ {-# OPTIONS -Wall -Werror #-} -module System.Time.Calendar.YearDay where +-- #hide +module System.Time.Calendar.YearDay + ( + -- * Year and day format + module System.Time.Calendar.YearDay + ) where import System.Time.Calendar.Calendar import System.Time.Calendar.Private From git at git.haskell.org Fri Jan 23 22:54:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:16 +0000 (UTC) Subject: [commit: packages/time] master: use "time" for package name (f323ece) Message-ID: <20150123225416.BD5843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f323ece469852fd50fc1b7edfe4bbe455a7d23ee >--------------------------------------------------------------- commit f323ece469852fd50fc1b7edfe4bbe455a7d23ee Author: Ashley Yakeley Date: Sun May 22 17:16:50 2005 -0700 use "time" for package name darcs-hash:20050523001650-ac6dd-2b3762d875eedb504f71b92ceb3c39b95edaa914 >--------------------------------------------------------------- f323ece469852fd50fc1b7edfe4bbe455a7d23ee TimeLib.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/TimeLib.cabal b/TimeLib.cabal index a4d5a21..60895d0 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -1,4 +1,4 @@ -Name: TimeLib +Name: time Version: 0.1 Stability: Alpha -- unsure of best license From git at git.haskell.org Fri Jan 23 22:54:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:18 +0000 (UTC) Subject: [commit: packages/time] master: put doc index in project (c2214f5) Message-ID: <20150123225418.C53253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c2214f530199aecbf47cf9ac0e6ed3bb3271f67e >--------------------------------------------------------------- commit c2214f530199aecbf47cf9ac0e6ed3bb3271f67e Author: Ashley Yakeley Date: Sun May 22 17:17:27 2005 -0700 put doc index in project darcs-hash:20050523001727-ac6dd-0718ea889354fccce1f2cecf75a80494a0dbe211 >--------------------------------------------------------------- c2214f530199aecbf47cf9ac0e6ed3bb3271f67e TimeLib.xcode/project.pbxproj | 32 +++++++++++++++++++++++++------- 1 file changed, 25 insertions(+), 7 deletions(-) diff --git a/TimeLib.xcode/project.pbxproj b/TimeLib.xcode/project.pbxproj index c2742eb..4e18e68 100644 --- a/TimeLib.xcode/project.pbxproj +++ b/TimeLib.xcode/project.pbxproj @@ -14,6 +14,7 @@ AB01DD0008374848003C9EF7, AB35747F08386FCD00B5F897, ABFA25EC0839F9FD0096540C, + ABFA264B083C8AA40096540C, ); isa = PBXGroup; refType = 4; @@ -299,7 +300,6 @@ buildPhases = ( ); buildSettings = { - OPTIMIZATION_CFLAGS = ""; OTHER_CFLAGS = ""; OTHER_LDFLAGS = ""; OTHER_REZFLAGS = ""; @@ -354,18 +354,18 @@ }; ABFA25EC0839F9FD0096540C = { children = ( - ABFA2623083B28C00096540C, - ABFA2624083B28C00096540C, ABFA2625083B28C00096540C, - ABFA2626083B28C00096540C, ABFA2627083B28C00096540C, ABFA2628083B28C00096540C, - ABFA2629083B28C00096540C, - ABFA262A083B28C00096540C, - ABFA262B083B28C00096540C, + ABFA2624083B28C00096540C, + ABFA2626083B28C00096540C, + ABFA2623083B28C00096540C, ABFA262C083B28C00096540C, ABFA262D083B28C00096540C, ABFA262E083B28C00096540C, + ABFA262B083B28C00096540C, + ABFA262A083B28C00096540C, + ABFA2629083B28C00096540C, ); isa = PBXGroup; name = Test; @@ -469,6 +469,24 @@ refType = 4; sourceTree = ""; }; + ABFA2649083BF6210096540C = { + fileEncoding = 4; + isa = PBXFileReference; + lastKnownFileType = text.html; + path = index.html; + refType = 4; + sourceTree = ""; + }; + ABFA264B083C8AA40096540C = { + children = ( + ABFA2649083BF6210096540C, + ); + isa = PBXGroup; + name = "Target Doc"; + path = haddock; + refType = 4; + sourceTree = ""; + }; }; rootObject = AB01DCEE083747B1003C9EF7; } From git at git.haskell.org Fri Jan 23 22:54:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:20 +0000 (UTC) Subject: [commit: packages/time] master: split up System.Time.Clock (462818f) Message-ID: <20150123225420.D06BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/462818f7aa1ffca64aa0d4346979e2fb52f48f0d >--------------------------------------------------------------- commit 462818f7aa1ffca64aa0d4346979e2fb52f48f0d Author: Ashley Yakeley Date: Sun Jul 3 17:15:58 2005 -0700 split up System.Time.Clock darcs-hash:20050704001558-ac6dd-53cb216f3d097415d6d85bffe4e23cadc8266435 >--------------------------------------------------------------- 462818f7aa1ffca64aa0d4346979e2fb52f48f0d Makefile | 21 +++- System/Time/Calendar/Format.hs | 1 + System/Time/Calendar/Timezone.hs | 1 + System/Time/Clock.hs | 200 ++------------------------------- System/Time/Clock/POSIX.hs | 11 ++ System/Time/Clock/Scale.hs | 57 ++++++++++ System/Time/{Clock.hs => Clock/UTC.hs} | 97 +--------------- TimeLib.xcode/project.pbxproj | 79 +++++++++++++ test/TestFormat.hs | 4 +- 9 files changed, 182 insertions(+), 289 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 462818f7aa1ffca64aa0d4346979e2fb52f48f0d From git at git.haskell.org Fri Jan 23 22:54:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:22 +0000 (UTC) Subject: [commit: packages/time] master: migrate to XCode 2.1 (64d9973) Message-ID: <20150123225422.D9A583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/64d997335afcb2b4334eb035f2739bc81a4f45b8 >--------------------------------------------------------------- commit 64d997335afcb2b4334eb035f2739bc81a4f45b8 Author: Ashley Yakeley Date: Sun Jul 3 17:21:10 2005 -0700 migrate to XCode 2.1 darcs-hash:20050704002110-ac6dd-06b1bdc0aefafb58e05bc7ca7bc82da13dd8c902 >--------------------------------------------------------------- 64d997335afcb2b4334eb035f2739bc81a4f45b8 TimeLib.xcode/project.pbxproj | 571 ------------------------------ TimeLib.xcodeproj/project.pbxproj | 709 ++++++++++++++++++++++++++++++++++++++ 2 files changed, 709 insertions(+), 571 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 64d997335afcb2b4334eb035f2739bc81a4f45b8 From git at git.haskell.org Fri Jan 23 22:54:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:24 +0000 (UTC) Subject: [commit: packages/time] master: use BSD license (02e4b6b) Message-ID: <20150123225424.E28D23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/02e4b6bcacc7d6c6a92ece300e8a89b684c206ca >--------------------------------------------------------------- commit 02e4b6bcacc7d6c6a92ece300e8a89b684c206ca Author: Ashley Yakeley Date: Sun Jul 3 20:41:14 2005 -0700 use BSD license darcs-hash:20050704034114-ac6dd-3e117fba8fe901eae07dbbf7462eb350e1a38931 >--------------------------------------------------------------- 02e4b6bcacc7d6c6a92ece300e8a89b684c206ca LICENSE | 10 ++++++++++ TimeLib.cabal | 4 ++-- 2 files changed, 12 insertions(+), 2 deletions(-) diff --git a/LICENSE b/LICENSE new file mode 100644 index 0000000..17f1f27 --- /dev/null +++ b/LICENSE @@ -0,0 +1,10 @@ +TimeLib is Copyright (c) Ashley Yakeley, 2004-2005. +All rights reserved. + +Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: + +- Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. + +- Neither name of the copyright holders nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. + +THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. diff --git a/TimeLib.cabal b/TimeLib.cabal index 60895d0..c4b6a45 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -1,8 +1,8 @@ Name: time Version: 0.1 Stability: Alpha --- unsure of best license -License: AllRightsReserved +License: BSD3 +License-File: LICENSE Author: Ashley Yakeley Maintainer: Homepage: From git at git.haskell.org Fri Jan 23 22:54:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:26 +0000 (UTC) Subject: [commit: packages/time] master: fix cabal file private mods (1a29bf0) Message-ID: <20150123225426.E95763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1a29bf0d401182730710d0f13d3985980b2a7012 >--------------------------------------------------------------- commit 1a29bf0d401182730710d0f13d3985980b2a7012 Author: Ashley Yakeley Date: Mon Jul 4 16:25:13 2005 -0700 fix cabal file private mods darcs-hash:20050704232513-ac6dd-b41a00c8152f74b5551fa51fb7eeb3c19b405783 >--------------------------------------------------------------- 1a29bf0d401182730710d0f13d3985980b2a7012 TimeLib.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/TimeLib.cabal b/TimeLib.cabal index c4b6a45..06ce2d7 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -12,4 +12,4 @@ Synopsis: a new time library Exposed-modules: Data.Fixed, System.Time.Clock, System.Time.TAI, System.Time.Calendar.Timezone, System.Time.Calendar.TimeOfDay, System.Time.Calendar.Calendar, System.Time.Calendar.Gregorian, System.Time.Calendar.ISOWeek, System.Time.Calendar.Format, System.Time.Calendar Extensions: ForeignFunctionInterface C-Sources: timestuff.c -Other-modules: System.Time.Calendar.Private +Other-modules: System.Time.Calendar.Private, System.Time.Clock.Scale, System.Time.Clock.UTC, System.Time.Clock.POSIX, System.Time.Clock.Current From git at git.haskell.org Fri Jan 23 22:54:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:28 +0000 (UTC) Subject: [commit: packages/time] master: add missing Current file (bcb1ac3) Message-ID: <20150123225428.F115A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/bcb1ac36593fe40e822f89c8800641bbb1c0c3ae >--------------------------------------------------------------- commit bcb1ac36593fe40e822f89c8800641bbb1c0c3ae Author: Ashley Yakeley Date: Mon Jul 4 16:27:49 2005 -0700 add missing Current file darcs-hash:20050704232749-ac6dd-643f88f66a58d3c45c317cac5d85ef31b471fbb0 >--------------------------------------------------------------- bcb1ac36593fe40e822f89c8800641bbb1c0c3ae System/Time/Clock/Current.hs | 42 ++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 42 insertions(+) diff --git a/System/Time/Clock/Current.hs b/System/Time/Clock/Current.hs new file mode 100644 index 0000000..66f4809 --- /dev/null +++ b/System/Time/Clock/Current.hs @@ -0,0 +1,42 @@ +{-# OPTIONS -ffi -Wall -Werror #-} + +-- #hide +module System.Time.Clock.Current +( + -- * Current time + getCurrentTime, +) where + +import System.Time.Clock.UTC + +import Foreign +import Foreign.C + +data CTimeval = MkCTimeval CLong CLong + +ctimevalToPosixSeconds :: CTimeval -> POSIXTime +ctimevalToPosixSeconds (MkCTimeval s mus) = (fromIntegral s) + (fromIntegral mus) / 1000000 + +instance Storable CTimeval where + sizeOf _ = (sizeOf (undefined :: CLong)) * 2 + alignment _ = alignment (undefined :: CLong) + peek p = do + s <- peekElemOff (castPtr p) 0 + mus <- peekElemOff (castPtr p) 1 + return (MkCTimeval s mus) + poke p (MkCTimeval s mus) = do + pokeElemOff (castPtr p) 0 s + pokeElemOff (castPtr p) 1 mus + +foreign import ccall unsafe "time.h gettimeofday" gettimeofday :: Ptr CTimeval -> Ptr () -> IO CInt + +-- | Get the current UTC time from the system clock. +getCurrentTime :: IO UTCTime +getCurrentTime = with (MkCTimeval 0 0) (\ptval -> do + result <- gettimeofday ptval nullPtr + if (result == 0) + then do + tval <- peek ptval + return (posixSecondsToUTCTime (ctimevalToPosixSeconds tval)) + else fail ("error in gettimeofday: " ++ (show result)) + ) From git at git.haskell.org Fri Jan 23 22:54:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:31 +0000 (UTC) Subject: [commit: packages/time] master: fix exposed/hidden module lists in cabal file (53e4437) Message-ID: <20150123225431.048A43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/53e4437d8a8d6ae470579eb4282a0384f4f6d381 >--------------------------------------------------------------- commit 53e4437d8a8d6ae470579eb4282a0384f4f6d381 Author: Ashley Yakeley Date: Thu Jul 7 01:37:32 2005 -0700 fix exposed/hidden module lists in cabal file darcs-hash:20050707083732-ac6dd-992773e72a12d14203e5decdb323b0e88219f2a2 >--------------------------------------------------------------- 53e4437d8a8d6ae470579eb4282a0384f4f6d381 TimeLib.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/TimeLib.cabal b/TimeLib.cabal index 06ce2d7..903907c 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -9,7 +9,7 @@ Homepage: Category: Build-Depends: base Synopsis: a new time library -Exposed-modules: Data.Fixed, System.Time.Clock, System.Time.TAI, System.Time.Calendar.Timezone, System.Time.Calendar.TimeOfDay, System.Time.Calendar.Calendar, System.Time.Calendar.Gregorian, System.Time.Calendar.ISOWeek, System.Time.Calendar.Format, System.Time.Calendar +Exposed-modules: Data.Fixed, System.Time.Clock, System.Time.TAI, System.Time.Calendar Extensions: ForeignFunctionInterface C-Sources: timestuff.c -Other-modules: System.Time.Calendar.Private, System.Time.Clock.Scale, System.Time.Clock.UTC, System.Time.Clock.POSIX, System.Time.Clock.Current +Other-modules: System.Time.Clock.Scale, System.Time.Clock.UTC, System.Time.Clock.POSIX, System.Time.Clock.Current, System.Time.Calendar.Private, System.Time.Calendar.Timezone, System.Time.Calendar.TimeOfDay, System.Time.Calendar.Calendar, System.Time.Calendar.Gregorian, System.Time.Calendar.ISOWeek, System.Time.Calendar.Format, System.Time.Calendar.YearDay From git at git.haskell.org Fri Jan 23 22:54:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:33 +0000 (UTC) Subject: [commit: packages/time] master: difftime doc seconds (cdfb558) Message-ID: <20150123225433.0ADAF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/cdfb558a851f8e91658a066692d711b484047f18 >--------------------------------------------------------------- commit cdfb558a851f8e91658a066692d711b484047f18 Author: Ashley Yakeley Date: Fri Jul 8 04:28:21 2005 -0700 difftime doc seconds darcs-hash:20050708112821-ac6dd-ce19449da430dad80f8cb0375be757416fc495bf >--------------------------------------------------------------- cdfb558a851f8e91658a066692d711b484047f18 System/Time/Clock/Scale.hs | 2 ++ System/Time/Clock/UTC.hs | 2 ++ 2 files changed, 4 insertions(+) diff --git a/System/Time/Clock/Scale.hs b/System/Time/Clock/Scale.hs index 3150dbc..2cb56e7 100644 --- a/System/Time/Clock/Scale.hs +++ b/System/Time/Clock/Scale.hs @@ -21,6 +21,8 @@ type ModJulianDay = Integer type ModJulianDate = Rational -- | This is a length of time, as measured by a clock. +-- Conversion functions will treat it as seconds. +-- It has an accuracy of 10^-12 s. newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord) instance Enum DiffTime where diff --git a/System/Time/Clock/UTC.hs b/System/Time/Clock/UTC.hs index 3c59fdd..1cdf8d2 100644 --- a/System/Time/Clock/UTC.hs +++ b/System/Time/Clock/UTC.hs @@ -39,6 +39,8 @@ instance Ord UTCTime where cmp -> cmp -- | This is a length of time, as measured by UTC. +-- Conversion functions will treat it as seconds. +-- It has an accuracy of 10^-12 s. -- It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. -- For instance, 23:00 UTC + 2 hours of UTCDiffTime = 01:00 UTC (+ 1 day), -- regardless of whether a leap-second intervened. From git at git.haskell.org Fri Jan 23 22:54:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:35 +0000 (UTC) Subject: [commit: packages/time] master: rename ISOWeek to ISOWeekDay (3ccb9bf) Message-ID: <20150123225435.1535A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3ccb9bf252051f8207e2726c51d843bc2e0457da >--------------------------------------------------------------- commit 3ccb9bf252051f8207e2726c51d843bc2e0457da Author: Ashley Yakeley Date: Fri Jul 8 04:29:01 2005 -0700 rename ISOWeek to ISOWeekDay darcs-hash:20050708112901-ac6dd-0a17d5e4667c94e263e72102946669ee9ae85fbe >--------------------------------------------------------------- 3ccb9bf252051f8207e2726c51d843bc2e0457da Makefile | 14 +++++++------- System/Time/Calendar.hs | 4 ++-- System/Time/Calendar/Format.hs | 6 +++--- System/Time/Calendar/{ISOWeek.hs => ISOWeekDay.hs} | 16 ++++++++-------- TimeLib.cabal | 2 +- TimeLib.xcodeproj/project.pbxproj | 4 ++-- test/ConvertBack.hs | 2 +- 7 files changed, 24 insertions(+), 24 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3ccb9bf252051f8207e2726c51d843bc2e0457da From git at git.haskell.org Fri Jan 23 22:54:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:37 +0000 (UTC) Subject: [commit: packages/time] master: Separate out DayEncoding into Days.hs (0fdf95f) Message-ID: <20150123225437.1F3E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/0fdf95fc5443c0fde004ce4b78714149c6bcad49 >--------------------------------------------------------------- commit 0fdf95fc5443c0fde004ce4b78714149c6bcad49 Author: Ashley Yakeley Date: Sun Jul 10 05:03:45 2005 -0700 Separate out DayEncoding into Days.hs darcs-hash:20050710120345-ac6dd-59f2e7e97354dd8b99ee92c3d5aebac00ce2b806 >--------------------------------------------------------------- 0fdf95fc5443c0fde004ce4b78714149c6bcad49 Makefile | 42 ++++++++++++++++++++++---------------- System/Time/Calendar.hs | 14 +++++++------ System/Time/Calendar/Calendar.hs | 15 ++------------ System/Time/Calendar/Days.hs | 22 ++++++++++++++++++++ System/Time/Calendar/Format.hs | 1 + System/Time/Calendar/Gregorian.hs | 2 +- System/Time/Calendar/ISOWeekDay.hs | 2 +- System/Time/Calendar/YearDay.hs | 2 +- TimeLib.cabal | 23 ++++++++++++++++++--- TimeLib.xcodeproj/project.pbxproj | 10 +++++---- 10 files changed, 86 insertions(+), 47 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0fdf95fc5443c0fde004ce4b78714149c6bcad49 From git at git.haskell.org Fri Jan 23 22:54:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:39 +0000 (UTC) Subject: [commit: packages/time] master: Major simplification of calendar types (3cec8f8) Message-ID: <20150123225439.296E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3cec8f830b4bf234ccc317bd44aedb5baad2f50b >--------------------------------------------------------------- commit 3cec8f830b4bf234ccc317bd44aedb5baad2f50b Author: Ashley Yakeley Date: Wed Aug 3 17:51:41 2005 -0700 Major simplification of calendar types darcs-hash:20050804005141-ac6dd-b0b617b54ea958834c74238d9096231534661cc8 >--------------------------------------------------------------- 3cec8f830b4bf234ccc317bd44aedb5baad2f50b Makefile | 9 ++--- System/Time/Calendar.hs | 12 ++---- System/Time/Calendar/Calendar.hs | 75 ++++++++++++++++++++------------------ System/Time/Calendar/Days.hs | 53 +++++++++++++++++++++------ System/Time/Calendar/Format.hs | 49 ++++++++++--------------- System/Time/Calendar/Gregorian.hs | 39 ++++++++++---------- System/Time/Calendar/ISOWeekDay.hs | 45 ++++++++++------------- System/Time/Calendar/YearDay.hs | 61 +++++++++++++++---------------- System/Time/Clock/Scale.hs | 8 ++-- System/Time/Clock/UTC.hs | 11 +++--- System/Time/TAI.hs | 9 +++-- TimeLib.xcodeproj/project.pbxproj | 4 +- test/ConvertBack.hs | 26 ++++++------- test/CurrentTime.hs | 4 +- test/ShowDST.hs | 6 +-- test/TestFormat.hs | 14 +++---- test/TestTime.hs | 33 +++++++++-------- 17 files changed, 232 insertions(+), 226 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3cec8f830b4bf234ccc317bd44aedb5baad2f50b From git at git.haskell.org Fri Jan 23 22:54:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:41 +0000 (UTC) Subject: [commit: packages/time] master: move from System to Data (64ab015) Message-ID: <20150123225441.37B653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/64ab015da821a8b9a43721683be81c8dae4e319b >--------------------------------------------------------------- commit 64ab015da821a8b9a43721683be81c8dae4e319b Author: Ashley Yakeley Date: Wed Aug 3 21:56:18 2005 -0700 move from System to Data darcs-hash:20050804045618-ac6dd-17cb2c59d50efd7409c0cad1a5a6afbfafffdb19 >--------------------------------------------------------------- 64ab015da821a8b9a43721683be81c8dae4e319b {System => Data}/Time/Calendar.hs | 40 +++---- {System => Data}/Time/Calendar/Calendar.hs | 12 +- {System => Data}/Time/Calendar/Days.hs | 2 +- {System => Data}/Time/Calendar/Format.hs | 24 ++-- {System => Data}/Time/Calendar/Gregorian.hs | 8 +- {System => Data}/Time/Calendar/ISOWeekDay.hs | 10 +- {System => Data}/Time/Calendar/Private.hs | 2 +- {System => Data}/Time/Calendar/TimeOfDay.hs | 8 +- {System => Data}/Time/Calendar/Timezone.hs | 8 +- {System => Data}/Time/Calendar/YearDay.hs | 8 +- Data/Time/Clock.hs | 13 +++ {System => Data}/Time/Clock/Current.hs | 4 +- {System => Data}/Time/Clock/POSIX.hs | 4 +- {System => Data}/Time/Clock/Scale.hs | 2 +- {System => Data}/Time/Clock/UTC.hs | 6 +- {System => Data}/Time/TAI.hs | 6 +- Makefile | 164 +++++++++++++-------------- System/Time/Clock.hs | 13 --- TimeLib.cabal | 32 +++--- TimeLib.xcodeproj/project.pbxproj | 5 +- test/ConvertBack.hs | 2 +- test/CurrentTime.hs | 6 +- test/ShowDST.hs | 4 +- test/TestFormat.hs | 6 +- test/TestTime.hs | 4 +- test/TimeZone.hs | 4 +- 26 files changed, 198 insertions(+), 199 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 64ab015da821a8b9a43721683be81c8dae4e319b From git at git.haskell.org Fri Jan 23 22:54:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:43 +0000 (UTC) Subject: [commit: packages/time] master: correct showing of years before 1000 CE, with test (869ebcc) Message-ID: <20150123225443.4248E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/869ebcc990f261502b5121373cbd6c689ac6e954 >--------------------------------------------------------------- commit 869ebcc990f261502b5121373cbd6c689ac6e954 Author: Ashley Yakeley Date: Wed Aug 3 23:27:38 2005 -0700 correct showing of years before 1000 CE, with test darcs-hash:20050804062738-ac6dd-b4c6228b0b4847944ef83f880cfa977035c1ea5c >--------------------------------------------------------------- 869ebcc990f261502b5121373cbd6c689ac6e954 Data/Time/Calendar/Format.hs | 6 +- Data/Time/Calendar/Gregorian.hs | 2 +- Data/Time/Calendar/ISOWeekDay.hs | 2 +- Data/Time/Calendar/Private.hs | 17 +- Data/Time/Calendar/YearDay.hs | 2 +- test/TestTime.hs | 9 +- test/TestTime.ref | 1612 ++++++++++++++++++++------------------ 7 files changed, 884 insertions(+), 766 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 869ebcc990f261502b5121373cbd6c689ac6e954 From git at git.haskell.org Fri Jan 23 22:54:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:45 +0000 (UTC) Subject: [commit: packages/time] master: clip incorrect values in converters, with tests (b107508) Message-ID: <20150123225445.4CAE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b107508b2e78edf6ba7b42b5e9cbd6247ed1dc7c >--------------------------------------------------------------- commit b107508b2e78edf6ba7b42b5e9cbd6247ed1dc7c Author: Ashley Yakeley Date: Fri Aug 5 23:01:28 2005 -0700 clip incorrect values in converters, with tests darcs-hash:20050806060128-ac6dd-bbc8cb9b16607d205fcf9b10a927e23c33a971e1 >--------------------------------------------------------------- b107508b2e78edf6ba7b42b5e9cbd6247ed1dc7c Data/Time/Calendar/Gregorian.hs | 10 +- Data/Time/Calendar/ISOWeekDay.hs | 13 +- Data/Time/Calendar/Private.hs | 5 + Data/Time/Calendar/YearDay.hs | 2 +- TimeLib.xcodeproj/project.pbxproj | 8 + test/ClipDates.hs | 24 ++ test/ClipDates.ref | 561 ++++++++++++++++++++++++++++++++++++++ test/LongWeekYears.hs | 17 ++ test/LongWeekYears.ref | 150 ++++++++++ test/Makefile | 8 +- 10 files changed, 787 insertions(+), 11 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b107508b2e78edf6ba7b42b5e9cbd6247ed1dc7c From git at git.haskell.org Fri Jan 23 22:54:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:47 +0000 (UTC) Subject: [commit: packages/time] master: new gregorianMonthLength function (cfab0ea) Message-ID: <20150123225447.53BED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/cfab0ea8c8107f76745a3bde61519b6bdd46c539 >--------------------------------------------------------------- commit cfab0ea8c8107f76745a3bde61519b6bdd46c539 Author: Ashley Yakeley Date: Sat Aug 6 13:38:12 2005 -0700 new gregorianMonthLength function darcs-hash:20050806203812-ac6dd-9110023cbd93ef6501f65be4439cac6093c372c9 >--------------------------------------------------------------- cfab0ea8c8107f76745a3bde61519b6bdd46c539 Data/Time/Calendar/Gregorian.hs | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/Data/Time/Calendar/Gregorian.hs b/Data/Time/Calendar/Gregorian.hs index 74b1435..9e83440 100644 --- a/Data/Time/Calendar/Gregorian.hs +++ b/Data/Time/Calendar/Gregorian.hs @@ -4,7 +4,7 @@ module Data.Time.Calendar.Gregorian ( -- * Gregorian calendar - gregorian,fromGregorian,showGregorian + gregorian,fromGregorian,showGregorian,gregorianMonthLength -- calendrical arithmetic -- e.g. "one month after March 31st" @@ -22,13 +22,13 @@ gregorian date = (year,month,day) where fromGregorian :: Integer -> Int -> Int -> Date -- formula from fromGregorian year month day = ModJulianDay - ((fromIntegral (clip 1 monthLength day)) + (div (153 * m + 2) 5) + (365 * y) + (div y 4) - (div y 100) + (div y 400) - 678882) where + (day' + (div (153 * m + 2) 5) + (365 * y) + (div y 4) - (div y 100) + (div y 400) - 678882) where month' = clip 1 12 month month'' = fromIntegral month' a = div (14 - month'') 12 y = year - a m = month'' + (12 * a) - 3 - monthLength = (monthLengths (isLeapYear year)) !! (month' - 1) + day' = fromIntegral (clip 1 (gregorianMonthLength' year month') day) showGregorian :: Date -> String showGregorian date = (show4 y) ++ "-" ++ (show2 m) ++ "-" ++ (show2 d) where @@ -38,6 +38,13 @@ findMonthDay :: [Int] -> Int -> (Int,Int) findMonthDay (n:ns) yd | yd > n = (\(m,d) -> (m + 1,d)) (findMonthDay ns (yd - n)) findMonthDay _ yd = (1,yd) +gregorianMonthLength' :: Integer -> Int -> Int +gregorianMonthLength' year month' = (monthLengths (isLeapYear year)) !! (month' - 1) + +-- | The number of days in a given month according to the proleptic Gregorian calendar. First argument is year, second is month. +gregorianMonthLength :: Integer -> Int -> Int +gregorianMonthLength year month = gregorianMonthLength' year (clip 1 12 month) + monthLengths :: Bool -> [Int] monthLengths isleap = [31,if isleap then 29 else 28,31,30,31,30,31,31,30,31,30,31] From git at git.haskell.org Fri Jan 23 22:54:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:49 +0000 (UTC) Subject: [commit: packages/time] master: conversion documentation (c2ff391) Message-ID: <20150123225449.5C64F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c2ff391a8786ebeba2e6574634ddc7d70e039822 >--------------------------------------------------------------- commit c2ff391a8786ebeba2e6574634ddc7d70e039822 Author: Ashley Yakeley Date: Sat Aug 6 13:42:34 2005 -0700 conversion documentation darcs-hash:20050806204234-ac6dd-6b698b3ab0328723f4da2ca9f22000b8792cbee8 >--------------------------------------------------------------- c2ff391a8786ebeba2e6574634ddc7d70e039822 Data/Time/Calendar/Gregorian.hs | 4 ++++ Data/Time/Calendar/ISOWeekDay.hs | 7 ++++++- Data/Time/Calendar/YearDay.hs | 7 ++++++- 3 files changed, 16 insertions(+), 2 deletions(-) diff --git a/Data/Time/Calendar/Gregorian.hs b/Data/Time/Calendar/Gregorian.hs index 9e83440..3312b29 100644 --- a/Data/Time/Calendar/Gregorian.hs +++ b/Data/Time/Calendar/Gregorian.hs @@ -14,11 +14,14 @@ import Data.Time.Calendar.YearDay import Data.Time.Calendar.Days import Data.Time.Calendar.Private +-- | convert to proleptic Gregorian calendar. First element of result is year, second month number (1-12), third day (1-31). gregorian :: Date -> (Integer,Int,Int) gregorian date = (year,month,day) where (year,yd) = yearAndDay date (month,day) = findMonthDay (monthLengths (isLeapYear year)) yd +-- | convert from proleptic Gregorian calendar. First argument is year, second month number (1-12), third day (1-31). +-- Invalid values will be clipped to the correct range, month first, then day. fromGregorian :: Integer -> Int -> Int -> Date -- formula from fromGregorian year month day = ModJulianDay @@ -30,6 +33,7 @@ fromGregorian year month day = ModJulianDay m = month'' + (12 * a) - 3 day' = fromIntegral (clip 1 (gregorianMonthLength' year month') day) +-- | show in ISO 8601 format (yyyy-mm-dd) showGregorian :: Date -> String showGregorian date = (show4 y) ++ "-" ++ (show2 m) ++ "-" ++ (show2 d) where (y,m,d) = gregorian date diff --git a/Data/Time/Calendar/ISOWeekDay.hs b/Data/Time/Calendar/ISOWeekDay.hs index 2dbd7e9..0c23495 100644 --- a/Data/Time/Calendar/ISOWeekDay.hs +++ b/Data/Time/Calendar/ISOWeekDay.hs @@ -3,7 +3,7 @@ -- #hide module Data.Time.Calendar.ISOWeekDay ( - -- * ISO Week calendar + -- * ISO 8601 Week calendar module Data.Time.Calendar.ISOWeekDay ) where @@ -11,6 +11,9 @@ import Data.Time.Calendar.YearDay import Data.Time.Calendar.Days import Data.Time.Calendar.Private +-- | convert to ISO 8601 Week format. First element of result is year, second week number (1-53), third day of week (1 for Monday to 7 for Sunday). +-- Note that "Week" years are not quite the same as Gregorian years, as the first day of the year is always a Monday. +-- The first week of a year is the first week to contain at least four days in the corresponding Gregorian year. isoWeekDay :: Date -> (Integer,Int,Int) isoWeekDay date@(ModJulianDay mjd) = (y1,fromInteger (w1 + 1),fromInteger (mod d 7) + 1) where (y0,yd) = yearAndDay date @@ -27,6 +30,7 @@ isoWeekDay date@(ModJulianDay mjd) = (y1,fromInteger (w1 + 1),fromInteger (mod d else (y0,w0) else (y0,w0) +-- | convert from ISO 8601 Week format. First argument is year, second week number (1-53), third day of week (1 for Monday to 7 for Sunday). fromISOWeekDay :: Integer -> Int -> Int -> Date fromISOWeekDay y w d = ModJulianDay (k - (mod k 7) + (toInteger (((clip 1 (if longYear then 53 else 52) w) * 7) + (clip 1 7 d))) - 10) where k = getModJulianDay (fromYearAndDay y 6) @@ -34,6 +38,7 @@ fromISOWeekDay y w d = ModJulianDay (k - (mod k 7) + (toInteger (((clip 1 (if lo (_,53,_) -> True _ -> False +-- | show in ISO 8601 Week format as yyyy-Www-dd (e.g. showISOWeekDay :: Date -> String showISOWeekDay date = (show4 y) ++ "-W" ++ (show2 w) ++ "-" ++ (show d) where (y,w,d) = isoWeekDay date diff --git a/Data/Time/Calendar/YearDay.hs b/Data/Time/Calendar/YearDay.hs index 6b8790a..68fe0da 100644 --- a/Data/Time/Calendar/YearDay.hs +++ b/Data/Time/Calendar/YearDay.hs @@ -10,6 +10,8 @@ module Data.Time.Calendar.YearDay import Data.Time.Calendar.Days import Data.Time.Calendar.Private +-- | convert to ISO 8601 Ordinal Date format. First element of result is year (proleptic Gregoran calendar), +-- second is the day of the year, with 1 for Jan 1, and 365 (or 366 in leap years) for Dec 31. yearAndDay :: Date -> (Integer,Int) yearAndDay (ModJulianDay mjd) = (year,yd) where a = mjd + 678575 @@ -23,16 +25,19 @@ yearAndDay (ModJulianDay mjd) = (year,yd) where yd = fromInteger (d - (y * 365) + 1) year = quadcent * 400 + cent * 100 + quad * 4 + y + 1 +-- | convert from ISO 8601 Ordinal Date format. +-- Invalid day numbers will be clipped to the correct range (1 to 365 or 366). fromYearAndDay :: Integer -> Int -> Date fromYearAndDay year day = ModJulianDay mjd where y = year - 1 mjd = (fromIntegral (clip 1 (if isLeapYear year then 366 else 365) day)) + (div (1532) 5) + (365 * y) + (div y 4) - (div y 100) + (div y 400) - 678882 --- | ISO 8601 Ordinal Date +-- | show in ISO 8601 Ordinal Date format (yyyy-ddd) showYearAndDay :: Date -> String showYearAndDay date = (show4 y) ++ "-" ++ (show3 d) where (y,d) = yearAndDay date +-- | Is this year a leap year according to the propleptic Gregorian calendar? isLeapYear :: Integer -> Bool isLeapYear year = (mod year 4 == 0) && ((mod year 400 == 0) || not (mod year 100 == 0)) From git at git.haskell.org Fri Jan 23 22:54:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:51 +0000 (UTC) Subject: [commit: packages/time] master: more time doc (8cea925) Message-ID: <20150123225451.63BC43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/8cea925e57e0498cab65f7d92e1aef6fc84e1d07 >--------------------------------------------------------------- commit 8cea925e57e0498cab65f7d92e1aef6fc84e1d07 Author: Ashley Yakeley Date: Sat Aug 6 14:03:50 2005 -0700 more time doc darcs-hash:20050806210350-ac6dd-137bddea624190e5df0f8db7b5eaf47662da1d26 >--------------------------------------------------------------- 8cea925e57e0498cab65f7d92e1aef6fc84e1d07 Data/Time/Calendar/ISOWeekDay.hs | 3 ++- Data/Time/Calendar/TimeOfDay.hs | 6 ++++++ Data/Time/Calendar/Timezone.hs | 8 +++++++- 3 files changed, 15 insertions(+), 2 deletions(-) diff --git a/Data/Time/Calendar/ISOWeekDay.hs b/Data/Time/Calendar/ISOWeekDay.hs index 0c23495..ea6522b 100644 --- a/Data/Time/Calendar/ISOWeekDay.hs +++ b/Data/Time/Calendar/ISOWeekDay.hs @@ -30,7 +30,8 @@ isoWeekDay date@(ModJulianDay mjd) = (y1,fromInteger (w1 + 1),fromInteger (mod d else (y0,w0) else (y0,w0) --- | convert from ISO 8601 Week format. First argument is year, second week number (1-53), third day of week (1 for Monday to 7 for Sunday). +-- | convert from ISO 8601 Week format. First argument is year, second week number (1-52 or 53), third day of week (1 for Monday to 7 for Sunday). +-- Invalid week and day values will be clipped to the correct range. fromISOWeekDay :: Integer -> Int -> Int -> Date fromISOWeekDay y w d = ModJulianDay (k - (mod k 7) + (toInteger (((clip 1 (if longYear then 53 else 52) w) * 7) + (clip 1 7 d))) - 10) where k = getModJulianDay (fromYearAndDay y 6) diff --git a/Data/Time/Calendar/TimeOfDay.hs b/Data/Time/Calendar/TimeOfDay.hs index b064048..c8598c2 100644 --- a/Data/Time/Calendar/TimeOfDay.hs +++ b/Data/Time/Calendar/TimeOfDay.hs @@ -17,14 +17,20 @@ import Data.Fixed -- | Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day. data TimeOfDay = TimeOfDay { + -- | range 0 - 23 todHour :: Int, + -- | range 0 - 59 todMin :: Int, + -- | Note that 0 <= todSec < 61, accomodating leap seconds. + -- Any local minute may have a leap second, since leap seconds happen in all zones simultaneously todSec :: Pico } deriving (Eq,Ord) +-- | Hour zero midnight :: TimeOfDay midnight = TimeOfDay 0 0 0 +-- | Hour twelve midday :: TimeOfDay midday = TimeOfDay 12 0 0 diff --git a/Data/Time/Calendar/Timezone.hs b/Data/Time/Calendar/Timezone.hs index 525b91b..f2b3ea6 100644 --- a/Data/Time/Calendar/Timezone.hs +++ b/Data/Time/Calendar/Timezone.hs @@ -18,22 +18,28 @@ import Data.Time.Clock.POSIX import Foreign import Foreign.C --- | count of minutes +-- | A Timezone is a whole number of minutes offset from UTC, together with a name and a "just for summer" flag. data Timezone = MkTimezone { + -- | The number of minutes offset from UTC. Positive means local time will be later in the day than UTC. timezoneMinutes :: Int, + -- | Is this time zone just persisting for the summer? timezoneDST :: Bool, + -- | The name of the zone, typically a three- or four-letter acronym. timezoneName :: String } deriving (Eq,Ord) +-- | Create a nameless non-summer timezone for this number of minutes minutesToTimezone :: Int -> Timezone minutesToTimezone m = MkTimezone m False "" +-- | Create a nameless non-summer timezone for this number of hours hoursToTimezone :: Int -> Timezone hoursToTimezone i = minutesToTimezone (60 * i) showT :: Int -> String showT t = (show2 (div t 60)) ++ (show2 (mod t 60)) +-- | Text representing the offset of this timezone, such as \"-0800\" or \"+0400\" (like %z in formatTime) timezoneOffsetString :: Timezone -> String timezoneOffsetString (MkTimezone t _ _) | t < 0 = '-':(showT (negate t)) timezoneOffsetString (MkTimezone t _ _) = '+':(showT t) From git at git.haskell.org Fri Jan 23 22:54:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:53 +0000 (UTC) Subject: [commit: packages/time] master: rename names in Data.Time.Calendar.Calendar (f35dd9e) Message-ID: <20150123225453.6C41B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f35dd9eab042ed2dc568555ffb131b1b8a08d264 >--------------------------------------------------------------- commit f35dd9eab042ed2dc568555ffb131b1b8a08d264 Author: Ashley Yakeley Date: Sat Aug 6 14:38:39 2005 -0700 rename names in Data.Time.Calendar.Calendar darcs-hash:20050806213839-ac6dd-24d6c932075fefea6d82a558b809686ce68757bb >--------------------------------------------------------------- f35dd9eab042ed2dc568555ffb131b1b8a08d264 Data/Time/Calendar.hs | 12 +++++----- Data/Time/Calendar/Calendar.hs | 52 +++++++++++++++++++++--------------------- Data/Time/Calendar/Format.hs | 12 +++++----- test/CurrentTime.hs | 4 ++-- test/ShowDST.hs | 8 +++---- test/TestFormat.hs | 14 ++++++------ test/TestTime.hs | 22 +++++++++--------- 7 files changed, 62 insertions(+), 62 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f35dd9eab042ed2dc568555ffb131b1b8a08d264 From git at git.haskell.org Fri Jan 23 22:54:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:55 +0000 (UTC) Subject: [commit: packages/time] master: reorg modules with new LocalTime hier (ce92c8a) Message-ID: <20150123225455.777A63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ce92c8a5ab39a42df4742655bd8d544e1d376e4c >--------------------------------------------------------------- commit ce92c8a5ab39a42df4742655bd8d544e1d376e4c Author: Ashley Yakeley Date: Sat Aug 6 15:46:20 2005 -0700 reorg modules with new LocalTime hier darcs-hash:20050806224620-ac6dd-662c819750a100ceb819d242dac41751d74c0154 >--------------------------------------------------------------- ce92c8a5ab39a42df4742655bd8d544e1d376e4c Data/Time/Calendar.hs | 44 +------------ Data/Time/{Calendar => LocalTime}/Format.hs | 10 +-- .../Calendar.hs => LocalTime/LocalTime.hs} | 11 ++-- Data/Time/{Calendar => LocalTime}/TimeOfDay.hs | 4 +- Data/Time/{Calendar => LocalTime}/Timezone.hs | 2 +- Makefile | 77 ++++++++++++---------- TimeLib.xcodeproj/project.pbxproj | 18 ++++- test/CurrentTime.hs | 6 +- test/ShowDST.hs | 5 +- test/TestFixed.hs | 2 + test/TestFormat.hs | 3 +- test/TestTime.hs | 3 +- test/TimeZone.hs | 5 +- 13 files changed, 84 insertions(+), 106 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ce92c8a5ab39a42df4742655bd8d544e1d376e4c From git at git.haskell.org Fri Jan 23 22:54:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:57 +0000 (UTC) Subject: [commit: packages/time] master: Timezone -> TimeZone (3db5c8e) Message-ID: <20150123225457.81CA43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3db5c8e08b16fd9d39dd829787c3a8d659f7d371 >--------------------------------------------------------------- commit 3db5c8e08b16fd9d39dd829787c3a8d659f7d371 Author: Ashley Yakeley Date: Sat Aug 6 16:16:46 2005 -0700 Timezone -> TimeZone darcs-hash:20050806231646-ac6dd-d82ec74508635fa1210768b6ae3a6e0ae360602c >--------------------------------------------------------------- 3db5c8e08b16fd9d39dd829787c3a8d659f7d371 Data/Time/LocalTime/Format.hs | 8 ++-- Data/Time/LocalTime/LocalTime.hs | 14 +++---- Data/Time/LocalTime/TimeOfDay.hs | 10 ++--- Data/Time/LocalTime/{Timezone.hs => TimeZone.hs} | 50 ++++++++++++------------ Makefile | 18 ++++----- TimeLib.xcodeproj/project.pbxproj | 4 +- test/CurrentTime.hs | 2 +- test/ShowDST.hs | 14 +++---- test/TestFormat.hs | 14 +++---- test/TestTime.hs | 4 +- test/TimeZone.hs | 4 +- 11 files changed, 71 insertions(+), 71 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3db5c8e08b16fd9d39dd829787c3a8d659f7d371 From git at git.haskell.org Fri Jan 23 22:54:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:54:59 +0000 (UTC) Subject: [commit: packages/time] master: fix TimeLib.cabal (aba753e) Message-ID: <20150123225459.88B3A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/aba753e95dbc55cf87493fb05960bba36841e83f >--------------------------------------------------------------- commit aba753e95dbc55cf87493fb05960bba36841e83f Author: Ashley Yakeley Date: Sat Aug 6 16:25:16 2005 -0700 fix TimeLib.cabal darcs-hash:20050806232516-ac6dd-75b60635df2f90092b75e60e72ae17fc9e47e5ff >--------------------------------------------------------------- aba753e95dbc55cf87493fb05960bba36841e83f TimeLib.cabal | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/TimeLib.cabal b/TimeLib.cabal index 42ad145..ec8e9ad 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -11,22 +11,24 @@ Build-Depends: base Synopsis: a new time library Exposed-modules: Data.Fixed, + Data.Time.Calendar, Data.Time.Clock, Data.Time.TAI, - Data.Time.Calendar + Data.Time.LocalTime, + Data.Time Extensions: ForeignFunctionInterface C-Sources: timestuff.c Other-modules: - Data.Time.Clock.Scale, - Data.Time.Clock.UTC, - Data.Time.Clock.POSIX, - Data.Time.Clock.Current, Data.Time.Calendar.Private, Data.Time.Calendar.Days, - Data.Time.Calendar.Calendar, + Data.Time.Calendar.YearDay, Data.Time.Calendar.Gregorian, Data.Time.Calendar.ISOWeekDay, - Data.Time.Calendar.Format, - Data.Time.Calendar.YearDay, - Data.Time.Calendar.Timezone, - Data.Time.Calendar.TimeOfDay + Data.Time.Clock.Scale, + Data.Time.Clock.UTC, + Data.Time.Clock.POSIX, + Data.Time.Clock.Current, + Data.Time.LocalTime.TimeZone, + Data.Time.LocalTime.TimeOfDay, + Data.Time.LocalTime.LocalTime, + Data.Time.LocalTime.Format From git at git.haskell.org Fri Jan 23 22:55:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:01 +0000 (UTC) Subject: [commit: packages/time] master: tiny doc fix (e2b7e0f) Message-ID: <20150123225501.8FA6D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e2b7e0f591aef5258142d3c739579b46c01efe8e >--------------------------------------------------------------- commit e2b7e0f591aef5258142d3c739579b46c01efe8e Author: Ashley Yakeley Date: Sat Aug 6 21:15:05 2005 -0700 tiny doc fix darcs-hash:20050807041505-ac6dd-5ab2844a54039f56f193821ca76a567683bacff9 >--------------------------------------------------------------- e2b7e0f591aef5258142d3c739579b46c01efe8e Data/Time/LocalTime/TimeZone.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Time/LocalTime/TimeZone.hs b/Data/Time/LocalTime/TimeZone.hs index f784e8e..b9a8978 100644 --- a/Data/Time/LocalTime/TimeZone.hs +++ b/Data/Time/LocalTime/TimeZone.hs @@ -18,7 +18,7 @@ import Data.Time.Clock.POSIX import Foreign import Foreign.C --- | A TimeZone is a whole number of minutes offset from UTC, together with a name and a "just for summer" flag. +-- | A TimeZone is a whole number of minutes offset from UTC, together with a name and a \"just for summer\" flag. data TimeZone = TimeZone { -- | The number of minutes offset from UTC. Positive means local time will be later in the day than UTC. timeZoneMinutes :: Int, From git at git.haskell.org Fri Jan 23 22:55:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:03 +0000 (UTC) Subject: [commit: packages/time] master: rename to-converter functions (f783b6b) Message-ID: <20150123225503.977813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f783b6b6042d26c7ac76763f5020e244dd9198c4 >--------------------------------------------------------------- commit f783b6b6042d26c7ac76763f5020e244dd9198c4 Author: Ashley Yakeley Date: Sat Aug 6 21:24:37 2005 -0700 rename to-converter functions darcs-hash:20050807042437-ac6dd-5ab571d0bdb5d64ffd32ba244050f48734dfe313 >--------------------------------------------------------------- f783b6b6042d26c7ac76763f5020e244dd9198c4 Data/Time/Calendar/Gregorian.hs | 10 +++++----- Data/Time/Calendar/ISOWeekDay.hs | 10 +++++----- Data/Time/Calendar/YearDay.hs | 10 +++++----- Data/Time/LocalTime/Format.hs | 28 ++++++++++++++-------------- test/ConvertBack.hs | 6 +++--- test/LongWeekYears.hs | 2 +- test/ShowDST.hs | 2 +- test/TestTime.hs | 2 +- 8 files changed, 35 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f783b6b6042d26c7ac76763f5020e244dd9198c4 From git at git.haskell.org Fri Jan 23 22:55:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:05 +0000 (UTC) Subject: [commit: packages/time] master: rename Date to Day (9c5fedd) Message-ID: <20150123225505.A00F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/9c5fedd97c9b3b9119f0b6c6aa302c361c7c8222 >--------------------------------------------------------------- commit 9c5fedd97c9b3b9119f0b6c6aa302c361c7c8222 Author: Ashley Yakeley Date: Sat Aug 6 22:05:37 2005 -0700 rename Date to Day darcs-hash:20050807050537-ac6dd-a7752f2f5fb0d5a80c5a9e16439635f62d7c3699 >--------------------------------------------------------------- 9c5fedd97c9b3b9119f0b6c6aa302c361c7c8222 Data/Time/Calendar/Days.hs | 68 ++++++++++++++++++++-------------------- Data/Time/Calendar/Gregorian.hs | 10 +++--- Data/Time/Calendar/ISOWeekDay.hs | 14 ++++----- Data/Time/Calendar/YearDay.hs | 24 +++++++------- Data/Time/Clock/UTC.hs | 10 +++--- Data/Time/LocalTime/Format.hs | 2 +- Data/Time/LocalTime/LocalTime.hs | 10 +++--- Data/Time/TAI.hs | 8 ++--- test/ConvertBack.hs | 10 +++--- test/TestTime.hs | 6 ++-- 10 files changed, 81 insertions(+), 81 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9c5fedd97c9b3b9119f0b6c6aa302c361c7c8222 From git at git.haskell.org Fri Jan 23 22:55:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:07 +0000 (UTC) Subject: [commit: packages/time] master: reorder modules in Makefile (bbbc983) Message-ID: <20150123225507.A76713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/bbbc983c7cc720e9c9d1a5fa60b4761359b29600 >--------------------------------------------------------------- commit bbbc983c7cc720e9c9d1a5fa60b4761359b29600 Author: Ashley Yakeley Date: Sun Aug 7 01:27:33 2005 -0700 reorder modules in Makefile darcs-hash:20050807082733-ac6dd-52df8b71fa34fa635f3c55ac1b3bdab293234355 >--------------------------------------------------------------- bbbc983c7cc720e9c9d1a5fa60b4761359b29600 Data/Time/LocalTime/TimeOfDay.hs | 2 +- Makefile | 46 ++++++++++++++++++++-------------------- 2 files changed, 24 insertions(+), 24 deletions(-) diff --git a/Data/Time/LocalTime/TimeOfDay.hs b/Data/Time/LocalTime/TimeOfDay.hs index d59919c..a4646cf 100644 --- a/Data/Time/LocalTime/TimeOfDay.hs +++ b/Data/Time/LocalTime/TimeOfDay.hs @@ -51,7 +51,7 @@ posixDay :: DiffTime posixDay = fromInteger 86400 -- | Get a TimeOfDay given a time since midnight. --- | Time more than 24h will be converted to leap-seconds. +-- Time more than 24h will be converted to leap-seconds. timeToTimeOfDay :: DiffTime -> TimeOfDay timeToTimeOfDay dt | dt >= posixDay = TimeOfDay 23 59 (60 + (realToFrac (dt - posixDay))) timeToTimeOfDay dt = TimeOfDay (fromInteger h) (fromInteger m) s where diff --git a/Makefile b/Makefile index cdee40c..95d5dc7 100644 --- a/Makefile +++ b/Makefile @@ -9,18 +9,18 @@ cleantest: cd test && make clean SRCS = Data/Fixed.hs \ - Data/Time/Clock/Scale.hs \ - Data/Time/Clock/UTC.hs \ - Data/Time/Clock/POSIX.hs \ - Data/Time/Clock/Current.hs \ - Data/Time/Clock.hs \ - Data/Time/TAI.hs \ Data/Time/Calendar/Private.hs \ Data/Time/Calendar/Days.hs \ Data/Time/Calendar/YearDay.hs \ Data/Time/Calendar/Gregorian.hs \ Data/Time/Calendar/ISOWeekDay.hs \ Data/Time/Calendar.hs \ + Data/Time/Clock/Scale.hs \ + Data/Time/Clock/UTC.hs \ + Data/Time/Clock/POSIX.hs \ + Data/Time/Clock/Current.hs \ + Data/Time/Clock.hs \ + Data/Time/TAI.hs \ Data/Time/LocalTime/TimeZone.hs \ Data/Time/LocalTime/TimeOfDay.hs \ Data/Time/LocalTime/LocalTime.hs \ @@ -81,23 +81,6 @@ TestFixed.o: Data/Fixed.hi # DO NOT DELETE: Beginning of Haskell dependencies Data/Time/Calendar/Days.o : Data/Time/Calendar/Days.hs Data/Fixed.o : Data/Fixed.hs -Data/Time/Clock/Scale.o : Data/Time/Clock/Scale.hs -Data/Time/Clock/Scale.o : Data/Fixed.hi -Data/Time/Clock/UTC.o : Data/Time/Clock/UTC.hs -Data/Time/Clock/UTC.o : Data/Fixed.hi -Data/Time/Clock/UTC.o : Data/Time/Clock/Scale.hi -Data/Time/Clock/UTC.o : Data/Time/Calendar/Days.hi -Data/Time/Clock/POSIX.o : Data/Time/Clock/POSIX.hs -Data/Time/Clock/POSIX.o : Data/Time/Clock/UTC.hi -Data/Time/Clock/Current.o : Data/Time/Clock/Current.hs -Data/Time/Clock/Current.o : Data/Time/Clock/UTC.hi -Data/Time/Clock.o : Data/Time/Clock.hs -Data/Time/Clock.o : Data/Time/Clock/Current.hi -Data/Time/Clock.o : Data/Time/Clock/UTC.hi -Data/Time/Clock.o : Data/Time/Clock/Scale.hi -Data/Time/TAI.o : Data/Time/TAI.hs -Data/Time/TAI.o : Data/Time/Clock.hi -Data/Time/TAI.o : Data/Time/Calendar/Days.hi Data/Time/Calendar/Private.o : Data/Time/Calendar/Private.hs Data/Time/Calendar/Private.o : Data/Fixed.hi Data/Time/Calendar/YearDay.o : Data/Time/Calendar/YearDay.hs @@ -116,6 +99,23 @@ Data/Time/Calendar.o : Data/Time/Calendar/ISOWeekDay.hi Data/Time/Calendar.o : Data/Time/Calendar/Gregorian.hi Data/Time/Calendar.o : Data/Time/Calendar/YearDay.hi Data/Time/Calendar.o : Data/Time/Calendar/Days.hi +Data/Time/Clock/Scale.o : Data/Time/Clock/Scale.hs +Data/Time/Clock/Scale.o : Data/Fixed.hi +Data/Time/Clock/UTC.o : Data/Time/Clock/UTC.hs +Data/Time/Clock/UTC.o : Data/Fixed.hi +Data/Time/Clock/UTC.o : Data/Time/Clock/Scale.hi +Data/Time/Clock/UTC.o : Data/Time/Calendar/Days.hi +Data/Time/Clock/POSIX.o : Data/Time/Clock/POSIX.hs +Data/Time/Clock/POSIX.o : Data/Time/Clock/UTC.hi +Data/Time/Clock/Current.o : Data/Time/Clock/Current.hs +Data/Time/Clock/Current.o : Data/Time/Clock/UTC.hi +Data/Time/Clock.o : Data/Time/Clock.hs +Data/Time/Clock.o : Data/Time/Clock/Current.hi +Data/Time/Clock.o : Data/Time/Clock/UTC.hi +Data/Time/Clock.o : Data/Time/Clock/Scale.hi +Data/Time/TAI.o : Data/Time/TAI.hs +Data/Time/TAI.o : Data/Time/Clock.hi +Data/Time/TAI.o : Data/Time/Calendar/Days.hi Data/Time/LocalTime/TimeZone.o : Data/Time/LocalTime/TimeZone.hs Data/Time/LocalTime/TimeZone.o : Data/Time/Clock/POSIX.hi Data/Time/LocalTime/TimeZone.o : Data/Time/Clock.hi From git at git.haskell.org Fri Jan 23 22:55:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:09 +0000 (UTC) Subject: [commit: packages/time] master: add months (with test) (853190e) Message-ID: <20150123225509.B47FD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/853190edc59e02e2b3bb8e1510372003c1931a11 >--------------------------------------------------------------- commit 853190edc59e02e2b3bb8e1510372003c1931a11 Author: Ashley Yakeley Date: Sun Aug 7 01:51:39 2005 -0700 add months (with test) darcs-hash:20050807085139-ac6dd-824564aeeffc6bfc7c57e76de6d2b1b3d653b293 >--------------------------------------------------------------- 853190edc59e02e2b3bb8e1510372003c1931a11 Data/Time/Calendar/Days.hs | 4 +- Data/Time/Calendar/Gregorian.hs | 41 ++++++- Data/Time/Clock/UTC.hs | 2 +- Data/Time/LocalTime/LocalTime.hs | 4 +- Data/Time/TAI.hs | 4 +- TimeLib.xcodeproj/project.pbxproj | 4 + test/AddDays.hs | 42 +++++++ test/AddDays.ref | 245 ++++++++++++++++++++++++++++++++++++++ test/Makefile | 5 +- 9 files changed, 337 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 853190edc59e02e2b3bb8e1510372003c1931a11 From git at git.haskell.org Fri Jan 23 22:55:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:11 +0000 (UTC) Subject: [commit: packages/time] master: clean up deps (957955c) Message-ID: <20150123225511.BB8CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/957955cbe73528d64b1ea8ba588ccda5dc799698 >--------------------------------------------------------------- commit 957955cbe73528d64b1ea8ba588ccda5dc799698 Author: Ashley Yakeley Date: Sun Aug 7 01:59:59 2005 -0700 clean up deps darcs-hash:20050807085959-ac6dd-d8e24b7b295204e276192302ff914792aec6e12c >--------------------------------------------------------------- 957955cbe73528d64b1ea8ba588ccda5dc799698 Data/Time/LocalTime/Format.hs | 5 +---- Data/Time/LocalTime/LocalTime.hs | 3 +-- Makefile | 8 ++------ 3 files changed, 4 insertions(+), 12 deletions(-) diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index 75cd91b..9e3385a 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -11,10 +11,7 @@ module Data.Time.LocalTime.Format import Data.Time.LocalTime.LocalTime import Data.Time.LocalTime.TimeOfDay import Data.Time.LocalTime.TimeZone -import Data.Time.Calendar.ISOWeekDay -import Data.Time.Calendar.Gregorian -import Data.Time.Calendar.YearDay -import Data.Time.Calendar.Days +import Data.Time.Calendar import Data.Time.Calendar.Private import Data.Time.Clock import Data.Time.Clock.POSIX diff --git a/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs index cbfb0d8..541a47b 100644 --- a/Data/Time/LocalTime/LocalTime.hs +++ b/Data/Time/LocalTime/LocalTime.hs @@ -14,8 +14,7 @@ module Data.Time.LocalTime.LocalTime import Data.Time.LocalTime.TimeOfDay import Data.Time.LocalTime.TimeZone -import Data.Time.Calendar.Gregorian -import Data.Time.Calendar.Days +import Data.Time.Calendar import Data.Time.Clock -- | A simple day and time aggregate, where the day is of the specified parameter, diff --git a/Makefile b/Makefile index 95d5dc7..218b096 100644 --- a/Makefile +++ b/Makefile @@ -127,18 +127,14 @@ Data/Time/LocalTime/TimeOfDay.o : Data/Time/Calendar/Private.hi Data/Time/LocalTime/TimeOfDay.o : Data/Time/LocalTime/TimeZone.hi Data/Time/LocalTime/LocalTime.o : Data/Time/LocalTime/LocalTime.hs Data/Time/LocalTime/LocalTime.o : Data/Time/Clock.hi -Data/Time/LocalTime/LocalTime.o : Data/Time/Calendar/Days.hi -Data/Time/LocalTime/LocalTime.o : Data/Time/Calendar/Gregorian.hi +Data/Time/LocalTime/LocalTime.o : Data/Time/Calendar.hi Data/Time/LocalTime/LocalTime.o : Data/Time/LocalTime/TimeZone.hi Data/Time/LocalTime/LocalTime.o : Data/Time/LocalTime/TimeOfDay.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/Format.hs Data/Time/LocalTime/Format.o : Data/Time/Clock/POSIX.hi Data/Time/LocalTime/Format.o : Data/Time/Clock.hi Data/Time/LocalTime/Format.o : Data/Time/Calendar/Private.hi -Data/Time/LocalTime/Format.o : Data/Time/Calendar/Days.hi -Data/Time/LocalTime/Format.o : Data/Time/Calendar/YearDay.hi -Data/Time/LocalTime/Format.o : Data/Time/Calendar/Gregorian.hi -Data/Time/LocalTime/Format.o : Data/Time/Calendar/ISOWeekDay.hi +Data/Time/LocalTime/Format.o : Data/Time/Calendar.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/TimeZone.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/TimeOfDay.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/LocalTime.hi From git at git.haskell.org Fri Jan 23 22:55:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:13 +0000 (UTC) Subject: [commit: packages/time] master: rename ISOWeekDay to ISO8601Week (8723c5f) Message-ID: <20150123225513.C9D0F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/8723c5f86424ee1d4c2d4b442fc10cda6ea58275 >--------------------------------------------------------------- commit 8723c5f86424ee1d4c2d4b442fc10cda6ea58275 Author: Ashley Yakeley Date: Sun Aug 7 02:04:57 2005 -0700 rename ISOWeekDay to ISO8601Week darcs-hash:20050807090457-ac6dd-413246f167e57da7cb93e7c975091f949f97f8a6 >--------------------------------------------------------------- 8723c5f86424ee1d4c2d4b442fc10cda6ea58275 Data/Time/Calendar.hs | 4 ++-- Data/Time/Calendar/{ISOWeekDay.hs => ISO8601Week.hs} | 20 ++++++++++---------- Data/Time/LocalTime/Format.hs | 8 ++++---- Makefile | 12 ++++++------ TimeLib.cabal | 2 +- TimeLib.xcodeproj/project.pbxproj | 4 ++-- test/ClipDates.hs | 2 +- test/ConvertBack.hs | 2 +- test/LongWeekYears.hs | 2 +- test/TestTime.hs | 2 +- 10 files changed, 29 insertions(+), 29 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8723c5f86424ee1d4c2d4b442fc10cda6ea58275 From git at git.haskell.org Fri Jan 23 22:55:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:15 +0000 (UTC) Subject: [commit: packages/time] master: utcToLocalZonedTime (5f330c5) Message-ID: <20150123225515.D295D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/5f330c5e312131d4fe5abce8fadb79b69601dfd8 >--------------------------------------------------------------- commit 5f330c5e312131d4fe5abce8fadb79b69601dfd8 Author: Ashley Yakeley Date: Sun Aug 7 15:36:19 2005 -0700 utcToLocalZonedTime darcs-hash:20050807223619-ac6dd-e7ba5a92ce87e506014e37539f2b14952f5b47b1 >--------------------------------------------------------------- 5f330c5e312131d4fe5abce8fadb79b69601dfd8 Data/Time/LocalTime/LocalTime.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs index 541a47b..9d718ee 100644 --- a/Data/Time/LocalTime/LocalTime.hs +++ b/Data/Time/LocalTime/LocalTime.hs @@ -9,7 +9,7 @@ module Data.Time.LocalTime.LocalTime -- converting UTC and UT1 times to LocalTime utcToLocalTime,localTimeToUTC,ut1ToLocalTime,localTimeToUT1, - ZonedTime(..),zonedTimeFromUTC,ztUTC,getZonedTime + ZonedTime(..),zonedTimeFromUTC,ztUTC,getZonedTime,utcToLocalZonedTime ) where import Data.Time.LocalTime.TimeOfDay @@ -70,3 +70,9 @@ getZonedTime = do t <- getCurrentTime zone <- getTimeZone t return (zonedTimeFromUTC zone t) + +-- | +utcToLocalZonedTime :: UTCTime -> IO ZonedTime +utcToLocalZonedTime t = do + zone <- getTimeZone t + return (zonedTimeFromUTC zone t) From git at git.haskell.org Fri Jan 23 22:55:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:17 +0000 (UTC) Subject: [commit: packages/time] master: rename UTCDiffTime to NominalDiffTime (6a21693) Message-ID: <20150123225517.DB7FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/6a216935f0b21b7f5546cfd8a2844042b5053dbf >--------------------------------------------------------------- commit 6a216935f0b21b7f5546cfd8a2844042b5053dbf Author: Ashley Yakeley Date: Sun Aug 7 15:40:56 2005 -0700 rename UTCDiffTime to NominalDiffTime darcs-hash:20050807224056-ac6dd-2a810f3e5a80c5585e6a0d2678e8729d29c1ed9b >--------------------------------------------------------------- 6a216935f0b21b7f5546cfd8a2844042b5053dbf Data/Time/Clock.hs | 2 +- Data/Time/Clock/UTC.hs | 76 +++++++++++++++++++++++++------------------------- 2 files changed, 39 insertions(+), 39 deletions(-) diff --git a/Data/Time/Clock.hs b/Data/Time/Clock.hs index 9235296..3b736b7 100644 --- a/Data/Time/Clock.hs +++ b/Data/Time/Clock.hs @@ -9,5 +9,5 @@ module Data.Time.Clock ) where import Data.Time.Clock.Scale -import Data.Time.Clock.UTC(UTCTime(..),UTCDiffTime,addUTCTime,diffUTCTime) +import Data.Time.Clock.UTC(UTCTime(..),NominalDiffTime,addUTCTime,diffUTCTime) import Data.Time.Clock.Current diff --git a/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs index 8b937e3..d1ca38d 100644 --- a/Data/Time/Clock/UTC.hs +++ b/Data/Time/Clock/UTC.hs @@ -9,7 +9,7 @@ module Data.Time.Clock.UTC -- These corrections are not predictable and are announced with six month's notice. -- No table of these corrections is provided, as any program compiled with it would become -- out of date in six months. - UTCTime(..),UTCDiffTime, + UTCTime(..),NominalDiffTime, addUTCTime,diffUTCTime, -- * POSIX time @@ -43,59 +43,59 @@ instance Ord UTCTime where -- Conversion functions will treat it as seconds. -- It has an accuracy of 10^-12 s. -- It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. --- For instance, 23:00 UTC + 2 hours of UTCDiffTime = 01:00 UTC (+ 1 day), +-- For instance, 23:00 UTC + 2 hours of NominalDiffTime = 01:00 UTC (+ 1 day), -- regardless of whether a leap-second intervened. -newtype UTCDiffTime = MkUTCDiffTime Pico deriving (Eq,Ord) +newtype NominalDiffTime = MkNominalDiffTime Pico deriving (Eq,Ord) -instance Enum UTCDiffTime where - succ (MkUTCDiffTime a) = MkUTCDiffTime (succ a) - pred (MkUTCDiffTime a) = MkUTCDiffTime (pred a) - toEnum = MkUTCDiffTime . toEnum - fromEnum (MkUTCDiffTime a) = fromEnum a - enumFrom (MkUTCDiffTime a) = fmap MkUTCDiffTime (enumFrom a) - enumFromThen (MkUTCDiffTime a) (MkUTCDiffTime b) = fmap MkUTCDiffTime (enumFromThen a b) - enumFromTo (MkUTCDiffTime a) (MkUTCDiffTime b) = fmap MkUTCDiffTime (enumFromTo a b) - enumFromThenTo (MkUTCDiffTime a) (MkUTCDiffTime b) (MkUTCDiffTime c) = fmap MkUTCDiffTime (enumFromThenTo a b c) +instance Enum NominalDiffTime where + succ (MkNominalDiffTime a) = MkNominalDiffTime (succ a) + pred (MkNominalDiffTime a) = MkNominalDiffTime (pred a) + toEnum = MkNominalDiffTime . toEnum + fromEnum (MkNominalDiffTime a) = fromEnum a + enumFrom (MkNominalDiffTime a) = fmap MkNominalDiffTime (enumFrom a) + enumFromThen (MkNominalDiffTime a) (MkNominalDiffTime b) = fmap MkNominalDiffTime (enumFromThen a b) + enumFromTo (MkNominalDiffTime a) (MkNominalDiffTime b) = fmap MkNominalDiffTime (enumFromTo a b) + enumFromThenTo (MkNominalDiffTime a) (MkNominalDiffTime b) (MkNominalDiffTime c) = fmap MkNominalDiffTime (enumFromThenTo a b c) -instance Show UTCDiffTime where - show (MkUTCDiffTime t) = (showFixed True t) ++ "s" +instance Show NominalDiffTime where + show (MkNominalDiffTime t) = (showFixed True t) ++ "s" -- necessary because H98 doesn't have "cunning newtype" derivation -instance Num UTCDiffTime where - (MkUTCDiffTime a) + (MkUTCDiffTime b) = MkUTCDiffTime (a + b) - (MkUTCDiffTime a) - (MkUTCDiffTime b) = MkUTCDiffTime (a - b) - (MkUTCDiffTime a) * (MkUTCDiffTime b) = MkUTCDiffTime (a * b) - negate (MkUTCDiffTime a) = MkUTCDiffTime (negate a) - abs (MkUTCDiffTime a) = MkUTCDiffTime (abs a) - signum (MkUTCDiffTime a) = MkUTCDiffTime (signum a) - fromInteger i = MkUTCDiffTime (fromInteger i) +instance Num NominalDiffTime where + (MkNominalDiffTime a) + (MkNominalDiffTime b) = MkNominalDiffTime (a + b) + (MkNominalDiffTime a) - (MkNominalDiffTime b) = MkNominalDiffTime (a - b) + (MkNominalDiffTime a) * (MkNominalDiffTime b) = MkNominalDiffTime (a * b) + negate (MkNominalDiffTime a) = MkNominalDiffTime (negate a) + abs (MkNominalDiffTime a) = MkNominalDiffTime (abs a) + signum (MkNominalDiffTime a) = MkNominalDiffTime (signum a) + fromInteger i = MkNominalDiffTime (fromInteger i) -- necessary because H98 doesn't have "cunning newtype" derivation -instance Real UTCDiffTime where - toRational (MkUTCDiffTime a) = toRational a +instance Real NominalDiffTime where + toRational (MkNominalDiffTime a) = toRational a -- necessary because H98 doesn't have "cunning newtype" derivation -instance Fractional UTCDiffTime where - (MkUTCDiffTime a) / (MkUTCDiffTime b) = MkUTCDiffTime (a / b) - recip (MkUTCDiffTime a) = MkUTCDiffTime (recip a) - fromRational r = MkUTCDiffTime (fromRational r) +instance Fractional NominalDiffTime where + (MkNominalDiffTime a) / (MkNominalDiffTime b) = MkNominalDiffTime (a / b) + recip (MkNominalDiffTime a) = MkNominalDiffTime (recip a) + fromRational r = MkNominalDiffTime (fromRational r) -- necessary because H98 doesn't have "cunning newtype" derivation -instance RealFrac UTCDiffTime where - properFraction (MkUTCDiffTime a) = (i,MkUTCDiffTime f) where +instance RealFrac NominalDiffTime where + properFraction (MkNominalDiffTime a) = (i,MkNominalDiffTime f) where (i,f) = properFraction a - truncate (MkUTCDiffTime a) = truncate a - round (MkUTCDiffTime a) = round a - ceiling (MkUTCDiffTime a) = ceiling a - floor (MkUTCDiffTime a) = floor a + truncate (MkNominalDiffTime a) = truncate a + round (MkNominalDiffTime a) = round a + ceiling (MkNominalDiffTime a) = ceiling a + floor (MkNominalDiffTime a) = floor a -posixDay :: UTCDiffTime +posixDay :: NominalDiffTime posixDay = 86400 unixEpochMJD :: Day unixEpochMJD = ModifiedJulianDay 40587 -type POSIXTime = UTCDiffTime +type POSIXTime = NominalDiffTime posixSecondsToUTCTime :: POSIXTime -> UTCTime posixSecondsToUTCTime i = let @@ -107,9 +107,9 @@ utcTimeToPOSIXSeconds (UTCTime d t) = (fromInteger (diffDays d unixEpochMJD) * posixDay) + min posixDay (realToFrac t) -- | addUTCTime a b = a + b -addUTCTime :: UTCDiffTime -> UTCTime -> UTCTime +addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime addUTCTime x t = posixSecondsToUTCTime (x + (utcTimeToPOSIXSeconds t)) -- | diffUTCTime a b = a - b -diffUTCTime :: UTCTime -> UTCTime -> UTCDiffTime +diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime diffUTCTime a b = (utcTimeToPOSIXSeconds a) - (utcTimeToPOSIXSeconds b) From git at git.haskell.org Fri Jan 23 22:55:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:19 +0000 (UTC) Subject: [commit: packages/time] master: use cases (as test) (68e172c) Message-ID: <20150123225519.E20573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/68e172c2fb6f6c2374edd3e759fb68499cb38e51 >--------------------------------------------------------------- commit 68e172c2fb6f6c2374edd3e759fb68499cb38e51 Author: Ashley Yakeley Date: Mon Aug 8 01:16:52 2005 -0700 use cases (as test) darcs-hash:20050808081652-ac6dd-a158d7e515bb01a942d39803b9eb5251db29ac9b >--------------------------------------------------------------- 68e172c2fb6f6c2374edd3e759fb68499cb38e51 TimeLib.xcodeproj/project.pbxproj | 2 + test/Makefile | 5 ++- test/UseCases.lhs | 82 +++++++++++++++++++++++++++++++++++++++ 3 files changed, 88 insertions(+), 1 deletion(-) diff --git a/TimeLib.xcodeproj/project.pbxproj b/TimeLib.xcodeproj/project.pbxproj index f4f5ca6..89c8c9b 100644 --- a/TimeLib.xcodeproj/project.pbxproj +++ b/TimeLib.xcodeproj/project.pbxproj @@ -108,6 +108,7 @@ AB2666F108A572520059DEC0 /* Time.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = Time.hs; sourceTree = ""; }; AB26682008A5FF0D0059DEC0 /* AddDays.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = AddDays.hs; sourceTree = ""; }; AB26682108A5FF0D0059DEC0 /* AddDays.ref */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = text; path = AddDays.ref; sourceTree = ""; }; + AB26689F08A6D7290059DEC0 /* UseCases.lhs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell.literate; path = UseCases.lhs; sourceTree = ""; }; ABD6783F084167B900CF37C0 /* POSIX.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = POSIX.hs; sourceTree = ""; }; ABD67840084167D100CF37C0 /* Current.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = Current.hs; sourceTree = ""; }; ABD67841084168B700CF37C0 /* UTC.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = UTC.hs; sourceTree = ""; }; @@ -231,6 +232,7 @@ ABFA262B083B28C00096540C /* TestFormatStuff.h */, ABFA262A083B28C00096540C /* TestFormatStuff.c */, ABFA2629083B28C00096540C /* TestFormat.hs */, + AB26689F08A6D7290059DEC0 /* UseCases.lhs */, ); name = Test; path = test; diff --git a/test/Makefile b/test/Makefile index 3e8fddd..034e2f4 100644 --- a/test/Makefile +++ b/test/Makefile @@ -36,7 +36,7 @@ TimeZone: TimeZone.o ../libTimeLib.a TimeZone.ref: FORCE date +%z > $@ -test: TestFixed.diff ConvertBack.diff0 TestTime.diff LongWeekYears.diff ClipDates.diff AddDays.diff TimeZone.diff TestFormat.diff0 +test: TestFixed.diff ConvertBack.diff0 TestTime.diff LongWeekYears.diff ClipDates.diff AddDays.diff TimeZone.diff TestFormat.diff0 UseCases.o clean: rm -rf ConvertBack TimeZone TimeZone.ref CurrentTime TestTime TestFixed ShowDST TestFormat *.out *.o *.hi Makefile.bak @@ -59,6 +59,9 @@ clean: %.o: %.hs ghc -i.. -c $< -o $@ +%.o: %.lhs + ghc -i.. -c $< -o $@ + FORCE: .SECONDARY: diff --git a/test/UseCases.lhs b/test/UseCases.lhs new file mode 100644 index 0000000..3db8834 --- /dev/null +++ b/test/UseCases.lhs @@ -0,0 +1,82 @@ +> module UseCases where +> import Data.Time +> import System.Locale + + +From Brian Smith: + + +Use cases (primarily taken from real-world corporate IT applications I have +developed) : + +* What is the equivalent (or closest aproximation) of the SQL DateTime type +(date and time without any timezone information)? What is the equivalent of +the SQL Date type (date without any timezone information)? + +> type SQLDateTime = LocalTime +> type SQLDate = Day + +* The user enters a date as "7/4/2005." How do I determine if this date is +before or after July 1st of this year? + +TODO: Parsing + +* How do I present the date "July 1st of this year" to the user in M/D/YYYY +format? + +> july1st = do +> now <- getZonedTime +> let (thisYear,_,_) = toGregorian (localDay (ztLocalTime now)) +> let day = fromGregorian thisYear 7 1 +> return (formatTime defaultTimeLocale "%m/%d/%Y" day) + +This actually gives "07/01/2005" rather than "7/1/2005". +ISSUE: Should I make additional %-codes for this? + + +* How do I truncate a datetime to midnight of the same day? How do I +truncate a date to the first of the month? How do I truncate a date to the +first day of the year it occurred in? + +> truncateToMidnight (LocalTime day _) = (LocalTime day midnight) + +> truncateToFirstOfMonth day = fromGregorian y m 1 where +> (y,m,_) = toGregorian day + +> truncateToJan1st day = fromYearAndDay y 1 where +> (y,_) = toYearAndDay day + +* Given a date X, how do I find the last day of the month that X occurs in. +For example, If X is July 4th, 2005, then I want the result to be July 31st, +2005. If X is Februrary 5, then I want the result to be Februrary 28 for +non-leap-years and February 29 for leap years. + +> lastDayOfMonth day = fromGregorian y m (gregorianMonthLength y m) where +> (y,m,_) = toGregorian day + +* The user enters a time T with no date, e.g. "17:30". How do I merge this +time onto a date D (e.g. July 4, 2005), so that the result has is a datetime +with date D and the time T (July 4, 2005 at 17:30). + +> mergeDateAndTime = LocalTime + +* Given two datetimes T1, T2, how do I determine if they are on the same +date? + +> sameDay (LocalTime d1 _) (LocalTime d2 _) = d1 == d2 + + +From Simon Marlow: + + +I just had a little look around, mainly at System.Time.Calendar. I +think the structure is rather complicated - I wanted to find out how to +get a CalendarTime for "this time tomorrow", and ended up with this: + +*System.Time.Calendar> let c' = +c{ztTime=zttime{dtDay=dtday{gregDay=day+1}}} where { zttime = ztTime c; +dtday = dtDay zttime; day = gregDay dtday } + +> thisTimeTomorrow (ZonedTime (LocalTime day tod) zone) = (ZonedTime (LocalTime (addDays 1 day) tod) zone) + + From git at git.haskell.org Fri Jan 23 22:55:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:21 +0000 (UTC) Subject: [commit: packages/time] master: add missing file (70544be) Message-ID: <20150123225521.E91B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/70544be1f29f912a032c1ba364b343d621faaa03 >--------------------------------------------------------------- commit 70544be1f29f912a032c1ba364b343d621faaa03 Author: Ashley Yakeley Date: Mon Aug 8 01:44:55 2005 -0700 add missing file darcs-hash:20050808084455-ac6dd-f30c61c5f69f22ce1764c10640dec0e564a68d01 >--------------------------------------------------------------- 70544be1f29f912a032c1ba364b343d621faaa03 Data/Time/LocalTime.hs | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/Data/Time/LocalTime.hs b/Data/Time/LocalTime.hs new file mode 100644 index 0000000..553a409 --- /dev/null +++ b/Data/Time/LocalTime.hs @@ -0,0 +1,14 @@ +{-# OPTIONS -Wall -Werror #-} + +module Data.Time.LocalTime +( + module Data.Time.LocalTime.TimeZone, + module Data.Time.LocalTime.TimeOfDay, + module Data.Time.LocalTime.LocalTime, + module Data.Time.LocalTime.Format +) where + +import Data.Time.LocalTime.TimeZone +import Data.Time.LocalTime.TimeOfDay +import Data.Time.LocalTime.LocalTime +import Data.Time.LocalTime.Format From git at git.haskell.org Fri Jan 23 22:55:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:23 +0000 (UTC) Subject: [commit: packages/time] master: add missing file (e3f3a03) Message-ID: <20150123225523.F0AD63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e3f3a0377025ebf746274e31f0651138350fa6d1 >--------------------------------------------------------------- commit e3f3a0377025ebf746274e31f0651138350fa6d1 Author: Ashley Yakeley Date: Mon Aug 8 01:45:48 2005 -0700 add missing file darcs-hash:20050808084548-ac6dd-ed5644c971cd295aeb8602214cacbe198fc0e4e8 >--------------------------------------------------------------- e3f3a0377025ebf746274e31f0651138350fa6d1 Data/Time.hs | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/Data/Time.hs b/Data/Time.hs new file mode 100644 index 0000000..65926cd --- /dev/null +++ b/Data/Time.hs @@ -0,0 +1,12 @@ +{-# OPTIONS -Wall -Werror #-} + +module Data.Time +( + module Data.Time.Calendar, + module Data.Time.Clock, + module Data.Time.LocalTime +) where + +import Data.Time.Calendar +import Data.Time.Clock +import Data.Time.LocalTime From git at git.haskell.org Fri Jan 23 22:55:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:26 +0000 (UTC) Subject: [commit: packages/time] master: get taiToUTCTime working (with test) (db06886) Message-ID: <20150123225526.067823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/db06886a8ffce339c0abb82c5d64aede7adaec8a >--------------------------------------------------------------- commit db06886a8ffce339c0abb82c5d64aede7adaec8a Author: Ashley Yakeley Date: Sun Oct 30 21:19:09 2005 -0800 get taiToUTCTime working (with test) darcs-hash:20051031051909-ac6dd-d6c3e23dfd9d8af47176829d9b08ee53bd087ff8 >--------------------------------------------------------------- db06886a8ffce339c0abb82c5d64aede7adaec8a Data/Time/TAI.hs | 90 ++++++++++++++++++++++++++++++++++++--- Makefile | 8 ++-- TimeLib.xcodeproj/project.pbxproj | 8 +++- test/Makefile | 5 ++- test/TestParseDAT.hs | 65 ++++++++++++++++++++++++++++ test/TestParseDAT.ref | 90 +++++++++++++++++++++++++++++++++++++++ test/tai-utc.dat | 37 ++++++++++++++++ 7 files changed, 293 insertions(+), 10 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc db06886a8ffce339c0abb82c5d64aede7adaec8a From git at git.haskell.org Fri Jan 23 22:55:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:28 +0000 (UTC) Subject: [commit: packages/time] master: comments (cae9a55) Message-ID: <20150123225528.0D27D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/cae9a559b5e04cf6a909e50a849701ef1a4b9ee9 >--------------------------------------------------------------- commit cae9a559b5e04cf6a909e50a849701ef1a4b9ee9 Author: Ashley Yakeley Date: Sun Oct 30 21:20:38 2005 -0800 comments darcs-hash:20051031052038-ac6dd-53d86650e4a39607f63fa4512d559cad30995bcf >--------------------------------------------------------------- cae9a559b5e04cf6a909e50a849701ef1a4b9ee9 Data/Fixed.hs | 6 +++--- Data/Time/Clock/UTC.hs | 3 +++ 2 files changed, 6 insertions(+), 3 deletions(-) diff --git a/Data/Fixed.hs b/Data/Fixed.hs index 697c460..919862b 100644 --- a/Data/Fixed.hs +++ b/Data/Fixed.hs @@ -10,16 +10,16 @@ module Data.Fixed E12,Pico ) where --- | like "div", but with a more useful type +-- | generalisation of 'div' to any instance of Real div' :: (Real a,Integral b) => a -> a -> b div' n d = floor ((toRational n) / (toRational d)) --- | like "divMod", but with a more useful type +-- | generalisation of 'divMod' to any instance of Real divMod' :: (Real a,Integral b) => a -> a -> (b,a) divMod' n d = (f,n - (fromIntegral f) * d) where f = div' n d --- | like "mod", but with a more useful type +-- | generalisation of 'mod' to any instance of Real mod' :: (Real a) => a -> a -> a mod' n d = n - (fromInteger f) * d where f = div' n d diff --git a/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs index d1ca38d..282ee4f 100644 --- a/Data/Time/Clock/UTC.hs +++ b/Data/Time/Clock/UTC.hs @@ -9,6 +9,9 @@ module Data.Time.Clock.UTC -- These corrections are not predictable and are announced with six month's notice. -- No table of these corrections is provided, as any program compiled with it would become -- out of date in six months. + -- + -- If you don't care about leap seconds, use UTCTime and NominalDiffTime for your clock calculations, + -- and you'll be fine. UTCTime(..),NominalDiffTime, addUTCTime,diffUTCTime, From git at git.haskell.org Fri Jan 23 22:55:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:30 +0000 (UTC) Subject: [commit: packages/time] master: set cabal to 0.2 (e1f3f24) Message-ID: <20150123225530.135573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e1f3f243b389395f4d50d992c2500c3815a9eb25 >--------------------------------------------------------------- commit e1f3f243b389395f4d50d992c2500c3815a9eb25 Author: Ashley Yakeley Date: Sun Oct 30 22:06:47 2005 -0800 set cabal to 0.2 darcs-hash:20051031060647-ac6dd-cae6ed88711bc94a8feeb11d2968b766ae0ce53b >--------------------------------------------------------------- e1f3f243b389395f4d50d992c2500c3815a9eb25 TimeLib.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/TimeLib.cabal b/TimeLib.cabal index dc74660..7713452 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -1,6 +1,6 @@ Name: time -Version: 0.1 -Stability: Alpha +Version: 0.2 +Stability: Beta License: BSD3 License-File: LICENSE Author: Ashley Yakeley From git at git.haskell.org Fri Jan 23 22:55:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:32 +0000 (UTC) Subject: [commit: packages/time] master: instance Show UTCTime (c03ad77) Message-ID: <20150123225532.19EC93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c03ad77480823c2e9c4cc919192a65052448ee57 >--------------------------------------------------------------- commit c03ad77480823c2e9c4cc919192a65052448ee57 Author: Ashley Yakeley Date: Tue Nov 1 23:48:56 2005 -0800 instance Show UTCTime darcs-hash:20051102074856-ac6dd-034566ea08d12d2e6bbd34390e1a7cfd7a69cac4 >--------------------------------------------------------------- c03ad77480823c2e9c4cc919192a65052448ee57 Data/Time/LocalTime/LocalTime.hs | 3 +++ test/TestParseDAT.hs | 7 ++----- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs index 9d718ee..1ac0f1f 100644 --- a/Data/Time/LocalTime/LocalTime.hs +++ b/Data/Time/LocalTime/LocalTime.hs @@ -65,6 +65,9 @@ ztUTC (ZonedTime t zone) = localTimeToUTC zone t instance Show ZonedTime where show (ZonedTime t zone) = show t ++ " " ++ show zone +instance Show UTCTime where + show t = show (zonedTimeFromUTC utc t) + getZonedTime :: IO ZonedTime getZonedTime = do t <- getCurrentTime diff --git a/test/TestParseDAT.hs b/test/TestParseDAT.hs index 48104ca..2f53fab 100644 --- a/test/TestParseDAT.hs +++ b/test/TestParseDAT.hs @@ -46,9 +46,6 @@ times = fmap (LocalTime (fromGregorian 1999 01 01)) tods ++ fmap (LocalTime (fromGregorian 1999 01 02)) tods -showUTC :: UTCTime -> String -showUTC t = show (zonedTimeFromUTC utc t) - main :: IO () main = do h <- openFile "tai-utc.dat" ReadMode @@ -60,6 +57,6 @@ main = do let taiTime = utcToTAITime lst utcTime let utcTime' = taiToUTCTime lst taiTime if utcTime == utcTime' - then putStrLn ((showUTC utcTime) ++ " == " ++ (show taiTime)) - else putStrLn ("correction: " ++ (showUTC utcTime) ++ " -> " ++ (show taiTime) ++ " -> " ++ (showUTC utcTime')) + then putStrLn ((show utcTime) ++ " == " ++ (show taiTime)) + else putStrLn ("correction: " ++ (show utcTime) ++ " -> " ++ (show taiTime) ++ " -> " ++ (show utcTime')) ) times From git at git.haskell.org Fri Jan 23 22:55:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:34 +0000 (UTC) Subject: [commit: packages/time] master: more sensible identifer names (acc1fc8) Message-ID: <20150123225534.212503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/acc1fc8124f9dbdb740c76a543421ba47ab1d456 >--------------------------------------------------------------- commit acc1fc8124f9dbdb740c76a543421ba47ab1d456 Author: Ashley Yakeley Date: Sat Nov 12 17:45:46 2005 -0800 more sensible identifer names darcs-hash:20051113014546-ac6dd-27e3b85dc58a1c0cef8b1611e17415887cc4ecc8 >--------------------------------------------------------------- acc1fc8124f9dbdb740c76a543421ba47ab1d456 Data/Time/LocalTime/Format.hs | 4 ++-- Data/Time/LocalTime/LocalTime.hs | 16 ++++++++-------- test/CurrentTime.hs | 4 ++-- test/ShowDST.hs | 2 +- test/TestFormat.hs | 2 +- 5 files changed, 14 insertions(+), 14 deletions(-) diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index 3976658..ccb72e9 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -66,7 +66,7 @@ instance FormatTime TimeOfDay where formatCharacter _ = Nothing instance FormatTime ZonedTime where - formatCharacter 's' = Just (\_ zt -> show (truncate (utcTimeToPOSIXSeconds (ztUTC zt)) :: Integer)) + formatCharacter 's' = Just (\_ zt -> show (truncate (utcTimeToPOSIXSeconds (zonedTimeToUTC zt)) :: Integer)) formatCharacter c = case (formatCharacter c) of Just f -> Just (\locale dt -> f locale (ztLocalTime dt)) Nothing -> case (formatCharacter c) of @@ -116,4 +116,4 @@ instance FormatTime Day where formatCharacter _ = Nothing instance FormatTime UTCTime where - formatCharacter c = fmap (\f locale t -> f locale (zonedTimeFromUTC utc t)) (formatCharacter c) + formatCharacter c = fmap (\f locale t -> f locale (utcToZonedTime utc t)) (formatCharacter c) diff --git a/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs index 1ac0f1f..6cb0d49 100644 --- a/Data/Time/LocalTime/LocalTime.hs +++ b/Data/Time/LocalTime/LocalTime.hs @@ -9,7 +9,7 @@ module Data.Time.LocalTime.LocalTime -- converting UTC and UT1 times to LocalTime utcToLocalTime,localTimeToUTC,ut1ToLocalTime,localTimeToUT1, - ZonedTime(..),zonedTimeFromUTC,ztUTC,getZonedTime,utcToLocalZonedTime + ZonedTime(..),utcToZonedTime,zonedTimeToUTC,getZonedTime,utcToLocalZonedTime ) where import Data.Time.LocalTime.TimeOfDay @@ -56,26 +56,26 @@ data ZonedTime = ZonedTime { ztZone :: TimeZone } -zonedTimeFromUTC :: TimeZone -> UTCTime -> ZonedTime -zonedTimeFromUTC zone time = ZonedTime (utcToLocalTime zone time) zone +utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime +utcToZonedTime zone time = ZonedTime (utcToLocalTime zone time) zone -ztUTC :: ZonedTime -> UTCTime -ztUTC (ZonedTime t zone) = localTimeToUTC zone t +zonedTimeToUTC :: ZonedTime -> UTCTime +zonedTimeToUTC (ZonedTime t zone) = localTimeToUTC zone t instance Show ZonedTime where show (ZonedTime t zone) = show t ++ " " ++ show zone instance Show UTCTime where - show t = show (zonedTimeFromUTC utc t) + show t = show (utcToZonedTime utc t) getZonedTime :: IO ZonedTime getZonedTime = do t <- getCurrentTime zone <- getTimeZone t - return (zonedTimeFromUTC zone t) + return (utcToZonedTime zone t) -- | utcToLocalZonedTime :: UTCTime -> IO ZonedTime utcToLocalZonedTime t = do zone <- getTimeZone t - return (zonedTimeFromUTC zone t) + return (utcToZonedTime zone t) diff --git a/test/CurrentTime.hs b/test/CurrentTime.hs index b0970f0..464e643 100644 --- a/test/CurrentTime.hs +++ b/test/CurrentTime.hs @@ -8,6 +8,6 @@ main :: IO () main = do now <- getCurrentTime putStrLn (show (utctDay now) ++ "," ++ show (utctDayTime now)) - putStrLn (show (zonedTimeFromUTC utc now :: ZonedTime)) + putStrLn (show (utcToZonedTime utc now :: ZonedTime)) myzone <- getCurrentTimeZone - putStrLn (show (zonedTimeFromUTC myzone now :: ZonedTime)) + putStrLn (show (utcToZonedTime myzone now :: ZonedTime)) diff --git a/test/ShowDST.hs b/test/ShowDST.hs index ed1a92f..fa7dbda 100644 --- a/test/ShowDST.hs +++ b/test/ShowDST.hs @@ -20,7 +20,7 @@ findTransition a b = do return (tp ++ tq) showZoneTime :: TimeZone -> UTCTime -> String -showZoneTime zone time = show (zonedTimeFromUTC zone time) +showZoneTime zone time = show (utcToZonedTime zone time) showTransition :: (UTCTime,TimeZone,TimeZone) -> String showTransition (time,zone1,zone2) = (showZoneTime zone1 time) ++ " => " ++ (showZoneTime zone2 time) diff --git a/test/TestFormat.hs b/test/TestFormat.hs index b4d1e70..1529dee 100644 --- a/test/TestFormat.hs +++ b/test/TestFormat.hs @@ -67,7 +67,7 @@ times = [baseTime0] ++ (fmap getDay [0..23]) ++ (fmap getDay [0..100]) ++ compareFormat :: String -> TimeZone -> UTCTime -> IO () compareFormat fmt zone time = let - ctime = zonedTimeFromUTC zone time + ctime = utcToZonedTime zone time haskellText = formatTime locale fmt ctime in do unixText <- unixFormatTime fmt zone time From git at git.haskell.org Fri Jan 23 22:55:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:36 +0000 (UTC) Subject: [commit: packages/time] master: version 0.2.1 (68b10d9) Message-ID: <20150123225536.28C753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/68b10d91802ebe97804eac22b08770e460c2c4f4 >--------------------------------------------------------------- commit 68b10d91802ebe97804eac22b08770e460c2c4f4 Author: Ashley Yakeley Date: Sat Nov 12 17:50:15 2005 -0800 version 0.2.1 darcs-hash:20051113015015-ac6dd-97e5fc55cc5d13ef0b24c75c160dfb3def05d7bb >--------------------------------------------------------------- 68b10d91802ebe97804eac22b08770e460c2c4f4 TimeLib.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/TimeLib.cabal b/TimeLib.cabal index 7713452..820035a 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -1,5 +1,5 @@ Name: time -Version: 0.2 +Version: 0.2.1 Stability: Beta License: BSD3 License-File: LICENSE From git at git.haskell.org Fri Jan 23 22:55:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:38 +0000 (UTC) Subject: [commit: packages/time] master: ZonedTime id names (e0937c8) Message-ID: <20150123225538.2EE9F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e0937c846ffaa0958d821cd2b5b040e364e5a7db >--------------------------------------------------------------- commit e0937c846ffaa0958d821cd2b5b040e364e5a7db Author: Ashley Yakeley Date: Sat Nov 12 17:54:19 2005 -0800 ZonedTime id names darcs-hash:20051113015419-ac6dd-d0f1b11eb888e9535372340ec3b4f3a38c36bd80 >--------------------------------------------------------------- e0937c846ffaa0958d821cd2b5b040e364e5a7db Data/Time/LocalTime/Format.hs | 4 ++-- Data/Time/LocalTime/LocalTime.hs | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index ccb72e9..8457086 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -68,9 +68,9 @@ instance FormatTime TimeOfDay where instance FormatTime ZonedTime where formatCharacter 's' = Just (\_ zt -> show (truncate (utcTimeToPOSIXSeconds (zonedTimeToUTC zt)) :: Integer)) formatCharacter c = case (formatCharacter c) of - Just f -> Just (\locale dt -> f locale (ztLocalTime dt)) + Just f -> Just (\locale dt -> f locale (zonedTimeToLocalTime dt)) Nothing -> case (formatCharacter c) of - Just f -> Just (\locale dt -> f locale (ztZone dt)) + Just f -> Just (\locale dt -> f locale (zonedTimeZone dt)) Nothing -> Nothing instance FormatTime TimeZone where diff --git a/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs index 6cb0d49..c902bb6 100644 --- a/Data/Time/LocalTime/LocalTime.hs +++ b/Data/Time/LocalTime/LocalTime.hs @@ -52,8 +52,8 @@ localTimeToUT1 long (LocalTime (ModifiedJulianDay localMJD) tod) = ModJulianDate -- | A local time together with a TimeZone. data ZonedTime = ZonedTime { - ztLocalTime :: LocalTime, - ztZone :: TimeZone + zonedTimeToLocalTime :: LocalTime, + zonedTimeZone :: TimeZone } utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime From git at git.haskell.org Fri Jan 23 22:55:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:40 +0000 (UTC) Subject: [commit: packages/time] master: new MonthDay module (f4e177d) Message-ID: <20150123225540.3BC803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f4e177df657acec49e90ee1fd1443827fb08e5ae >--------------------------------------------------------------- commit f4e177df657acec49e90ee1fd1443827fb08e5ae Author: Ashley Yakeley Date: Sun Nov 13 03:11:58 2005 -0800 new MonthDay module darcs-hash:20051113111158-ac6dd-0bbbd8a48c559aa87e0ec57128af814e83ee7396 >--------------------------------------------------------------- f4e177df657acec49e90ee1fd1443827fb08e5ae Data/Time/Calendar.hs | 2 + Data/Time/Calendar/Gregorian.hs | 24 +- Data/Time/Calendar/MonthDay.hs | 41 +++ Makefile | 5 + TimeLib.cabal | 1 + TimeLib.xcodeproj/project.pbxproj | 6 + test/Makefile | 16 +- test/TestMonthDay.hs | 20 + test/TestMonthDay.ref | 746 ++++++++++++++++++++++++++++++++++++++ 9 files changed, 840 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f4e177df657acec49e90ee1fd1443827fb08e5ae From git at git.haskell.org Fri Jan 23 22:55:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:42 +0000 (UTC) Subject: [commit: packages/time] master: Julian and Easter calendars (869b07f) Message-ID: <20150123225542.4984C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/869b07fbd86304b5ef9ac67cf398b7bbd232f663 >--------------------------------------------------------------- commit 869b07fbd86304b5ef9ac67cf398b7bbd232f663 Author: Ashley Yakeley Date: Mon Nov 14 01:42:01 2005 -0800 Julian and Easter calendars darcs-hash:20051114094201-ac6dd-a131f426e1d19bdf05a559ee6a110c9e9740b4c4 >--------------------------------------------------------------- 869b07fbd86304b5ef9ac67cf398b7bbd232f663 Data/Time/Calendar/Easter.hs | 38 +++++++++++++++++++++ Data/Time/Calendar/Julian.hs | 68 +++++++++++++++++++++++++++++++++++++ Data/Time/Calendar/JulianYearDay.hs | 38 +++++++++++++++++++++ Data/Time/Calendar/YearDay.hs | 2 +- Makefile | 14 ++++++++ TimeLib.cabal | 3 ++ TimeLib.xcodeproj/project.pbxproj | 14 ++++++++ test/ConvertBack.hs | 4 ++- test/Makefile | 8 +++++ test/TestCalendars.hs | 28 +++++++++++++++ test/TestCalendars.ref | 4 +++ test/TestEaster.hs | 23 +++++++++++++ test/TestEaster.ref | 57 +++++++++++++++++++++++++++++++ 13 files changed, 299 insertions(+), 2 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 869b07fbd86304b5ef9ac67cf398b7bbd232f663 From git at git.haskell.org Fri Jan 23 22:55:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:44 +0000 (UTC) Subject: [commit: packages/time] master: move ISO8601Week to separate module space (b802476) Message-ID: <20150123225544.512A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b802476ee193ac4616eb35945069fd9007aa39c6 >--------------------------------------------------------------- commit b802476ee193ac4616eb35945069fd9007aa39c6 Author: Ashley Yakeley Date: Mon Nov 14 01:49:03 2005 -0800 move ISO8601Week to separate module space darcs-hash:20051114094903-ac6dd-606f84f89b9ef911bddbed72ef80778b57d4a586 >--------------------------------------------------------------- b802476ee193ac4616eb35945069fd9007aa39c6 Data/Time/Calendar.hs | 4 +--- Data/Time/Calendar/ISO8601Week.hs | 7 +------ Data/Time/LocalTime/Format.hs | 2 +- Makefile | 10 +++++----- TimeLib.cabal | 2 +- test/ClipDates.hs | 1 + test/ConvertBack.hs | 1 + test/LongWeekYears.hs | 1 + test/TestCalendars.hs | 1 + test/TestTime.hs | 1 + 10 files changed, 14 insertions(+), 16 deletions(-) diff --git a/Data/Time/Calendar.hs b/Data/Time/Calendar.hs index 8cf43ce..db87917 100644 --- a/Data/Time/Calendar.hs +++ b/Data/Time/Calendar.hs @@ -5,12 +5,10 @@ module Data.Time.Calendar module Data.Time.Calendar.Days, module Data.Time.Calendar.YearDay, module Data.Time.Calendar.MonthDay, - module Data.Time.Calendar.Gregorian, - module Data.Time.Calendar.ISO8601Week + module Data.Time.Calendar.Gregorian ) where import Data.Time.Calendar.Days import Data.Time.Calendar.YearDay import Data.Time.Calendar.MonthDay import Data.Time.Calendar.Gregorian -import Data.Time.Calendar.ISO8601Week diff --git a/Data/Time/Calendar/ISO8601Week.hs b/Data/Time/Calendar/ISO8601Week.hs index 8a9e61f..88e8e3e 100644 --- a/Data/Time/Calendar/ISO8601Week.hs +++ b/Data/Time/Calendar/ISO8601Week.hs @@ -1,11 +1,6 @@ {-# OPTIONS -Wall -Werror #-} --- #hide -module Data.Time.Calendar.ISO8601Week - ( - -- * ISO 8601 Week calendar - module Data.Time.Calendar.ISO8601Week - ) where +module Data.Time.Calendar.ISO8601Week where import Data.Time.Calendar.YearDay import Data.Time.Calendar.Days diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index 8457086..3fbbe0e 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -1,6 +1,5 @@ {-# OPTIONS -Wall -Werror #-} - -- #hide module Data.Time.LocalTime.Format ( @@ -11,6 +10,7 @@ module Data.Time.LocalTime.Format import Data.Time.LocalTime.LocalTime import Data.Time.LocalTime.TimeOfDay import Data.Time.LocalTime.TimeZone +import Data.Time.Calendar.ISO8601Week import Data.Time.Calendar import Data.Time.Calendar.Private import Data.Time.Clock diff --git a/Makefile b/Makefile index 9bfdf0c..b387425 100644 --- a/Makefile +++ b/Makefile @@ -97,16 +97,15 @@ Data/Time/Calendar/Gregorian.o : Data/Time/Calendar/Private.hi Data/Time/Calendar/Gregorian.o : Data/Time/Calendar/Days.hi Data/Time/Calendar/Gregorian.o : Data/Time/Calendar/YearDay.hi Data/Time/Calendar/Gregorian.o : Data/Time/Calendar/MonthDay.hi -Data/Time/Calendar/ISO8601Week.o : Data/Time/Calendar/ISO8601Week.hs -Data/Time/Calendar/ISO8601Week.o : Data/Time/Calendar/Private.hi -Data/Time/Calendar/ISO8601Week.o : Data/Time/Calendar/Days.hi -Data/Time/Calendar/ISO8601Week.o : Data/Time/Calendar/YearDay.hi Data/Time/Calendar.o : Data/Time/Calendar.hs -Data/Time/Calendar.o : Data/Time/Calendar/ISO8601Week.hi Data/Time/Calendar.o : Data/Time/Calendar/Gregorian.hi Data/Time/Calendar.o : Data/Time/Calendar/MonthDay.hi Data/Time/Calendar.o : Data/Time/Calendar/YearDay.hi Data/Time/Calendar.o : Data/Time/Calendar/Days.hi +Data/Time/Calendar/ISO8601Week.o : Data/Time/Calendar/ISO8601Week.hs +Data/Time/Calendar/ISO8601Week.o : Data/Time/Calendar/Private.hi +Data/Time/Calendar/ISO8601Week.o : Data/Time/Calendar/Days.hi +Data/Time/Calendar/ISO8601Week.o : Data/Time/Calendar/YearDay.hi Data/Time/Calendar/JulianYearDay.o : Data/Time/Calendar/JulianYearDay.hs Data/Time/Calendar/JulianYearDay.o : Data/Time/Calendar/Private.hi Data/Time/Calendar/JulianYearDay.o : Data/Time/Calendar/Days.hi @@ -151,6 +150,7 @@ Data/Time/LocalTime/Format.o : Data/Time/Clock/POSIX.hi Data/Time/LocalTime/Format.o : Data/Time/Clock.hi Data/Time/LocalTime/Format.o : Data/Time/Calendar/Private.hi Data/Time/LocalTime/Format.o : Data/Time/Calendar.hi +Data/Time/LocalTime/Format.o : Data/Time/Calendar/ISO8601Week.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/TimeZone.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/TimeOfDay.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/LocalTime.hi diff --git a/TimeLib.cabal b/TimeLib.cabal index b10cb7c..16a43c7 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -12,6 +12,7 @@ Synopsis: a new time library Exposed-modules: Data.Fixed, Data.Time.Calendar, + Data.Time.Calendar.ISO8601Week, Data.Time.Calendar.Julian, Data.Time.Calendar.Easter, Data.Time.Clock, @@ -26,7 +27,6 @@ Other-modules: Data.Time.Calendar.YearDay, Data.Time.Calendar.MonthDay, Data.Time.Calendar.Gregorian, - Data.Time.Calendar.ISO8601Week, Data.Time.Calendar.JulianYearDay, Data.Time.Clock.Scale, Data.Time.Clock.UTC, diff --git a/test/ClipDates.hs b/test/ClipDates.hs index f9abb6c..cd0fe9c 100644 --- a/test/ClipDates.hs +++ b/test/ClipDates.hs @@ -2,6 +2,7 @@ module Main where +import Data.Time.Calendar.ISO8601Week import Data.Time.Calendar import Control.Monad diff --git a/test/ConvertBack.hs b/test/ConvertBack.hs index 7f3ea1e..76dda86 100644 --- a/test/ConvertBack.hs +++ b/test/ConvertBack.hs @@ -3,6 +3,7 @@ module Main where import Data.Time.Calendar.Julian +import Data.Time.Calendar.ISO8601Week import Data.Time.Calendar checkDay :: (Show t) => (Day -> t) -> (t -> Day) -> Day -> IO () diff --git a/test/LongWeekYears.hs b/test/LongWeekYears.hs index 3715b6d..674e8c6 100644 --- a/test/LongWeekYears.hs +++ b/test/LongWeekYears.hs @@ -2,6 +2,7 @@ module Main where +import Data.Time.Calendar.ISO8601Week import Data.Time.Calendar longYear :: Integer -> Bool diff --git a/test/TestCalendars.hs b/test/TestCalendars.hs index 3dd935a..d463b3a 100644 --- a/test/TestCalendars.hs +++ b/test/TestCalendars.hs @@ -3,6 +3,7 @@ module Main where import Data.Time.Calendar.Julian +import Data.Time.Calendar.ISO8601Week import Data.Time.Calendar showers :: [(String,Day -> String)] diff --git a/test/TestTime.hs b/test/TestTime.hs index 2870026..f95c4ca 100644 --- a/test/TestTime.hs +++ b/test/TestTime.hs @@ -2,6 +2,7 @@ module Main where +import Data.Time.Calendar.ISO8601Week import Data.Time showCal :: Integer -> IO () From git at git.haskell.org Fri Jan 23 22:55:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:46 +0000 (UTC) Subject: [commit: packages/time] master: fix identifier in UseCases.lhs (0e3dd85) Message-ID: <20150123225546.58EAE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/0e3dd8527b87f54d00deb8fba9806c6c49e844e4 >--------------------------------------------------------------- commit 0e3dd8527b87f54d00deb8fba9806c6c49e844e4 Author: Ashley Yakeley Date: Mon Nov 14 01:50:01 2005 -0800 fix identifier in UseCases.lhs darcs-hash:20051114095001-ac6dd-9bd1aba492639cb8de6f1b14f98ef2f7fc70a414 >--------------------------------------------------------------- 0e3dd8527b87f54d00deb8fba9806c6c49e844e4 test/UseCases.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/UseCases.lhs b/test/UseCases.lhs index 3db8834..dff4af1 100644 --- a/test/UseCases.lhs +++ b/test/UseCases.lhs @@ -26,7 +26,7 @@ format? > july1st = do > now <- getZonedTime -> let (thisYear,_,_) = toGregorian (localDay (ztLocalTime now)) +> let (thisYear,_,_) = toGregorian (localDay (zonedTimeToLocalTime now)) > let day = fromGregorian thisYear 7 1 > return (formatTime defaultTimeLocale "%m/%d/%Y" day) From git at git.haskell.org Fri Jan 23 22:55:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:48 +0000 (UTC) Subject: [commit: packages/time] master: move out MonthDay and YearDay (6f8d525) Message-ID: <20150123225548.5E9553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/6f8d525b72b83b9e7d6ae9a6a54412772827f04e >--------------------------------------------------------------- commit 6f8d525b72b83b9e7d6ae9a6a54412772827f04e Author: Ashley Yakeley Date: Sun Nov 27 19:15:30 2005 -0800 move out MonthDay and YearDay darcs-hash:20051128031530-ac6dd-3f85b81566d7460fb2faa21f0783f11b4421cf62 >--------------------------------------------------------------- 6f8d525b72b83b9e7d6ae9a6a54412772827f04e Data/Time/Calendar.hs | 4 ---- Data/Time/Calendar/ISO8601Week.hs | 2 +- Data/Time/Calendar/MonthDay.hs | 2 -- Data/Time/Calendar/YearDay.hs | 7 +------ Data/Time/LocalTime/Format.hs | 1 + Makefile | 3 +-- TimeLib.cabal | 4 ++-- 7 files changed, 6 insertions(+), 17 deletions(-) diff --git a/Data/Time/Calendar.hs b/Data/Time/Calendar.hs index db87917..30dd9bf 100644 --- a/Data/Time/Calendar.hs +++ b/Data/Time/Calendar.hs @@ -3,12 +3,8 @@ module Data.Time.Calendar ( module Data.Time.Calendar.Days, - module Data.Time.Calendar.YearDay, - module Data.Time.Calendar.MonthDay, module Data.Time.Calendar.Gregorian ) where import Data.Time.Calendar.Days -import Data.Time.Calendar.YearDay -import Data.Time.Calendar.MonthDay import Data.Time.Calendar.Gregorian diff --git a/Data/Time/Calendar/ISO8601Week.hs b/Data/Time/Calendar/ISO8601Week.hs index 88e8e3e..59e082a 100644 --- a/Data/Time/Calendar/ISO8601Week.hs +++ b/Data/Time/Calendar/ISO8601Week.hs @@ -7,7 +7,7 @@ import Data.Time.Calendar.Days import Data.Time.Calendar.Private -- | convert to ISO 8601 Week format. First element of result is year, second week number (1-53), third day of week (1 for Monday to 7 for Sunday). --- Note that "Week" years are not quite the same as Gregorian years, as the first day of the year is always a Monday. +-- Note that \"Week\" years are not quite the same as Gregorian years, as the first day of the year is always a Monday. -- The first week of a year is the first week to contain at least four days in the corresponding Gregorian year. toISO8601Week :: Day -> (Integer,Int,Int) toISO8601Week date@(ModifiedJulianDay mjd) = (y1,fromInteger (w1 + 1),fromInteger (mod d 7) + 1) where diff --git a/Data/Time/Calendar/MonthDay.hs b/Data/Time/Calendar/MonthDay.hs index 5f15d7d..ac0c4d3 100644 --- a/Data/Time/Calendar/MonthDay.hs +++ b/Data/Time/Calendar/MonthDay.hs @@ -1,9 +1,7 @@ {-# OPTIONS -Wall -Werror #-} --- #hide module Data.Time.Calendar.MonthDay ( - -- * Month and day format monthAndDayToDayOfYear,dayOfYearToMonthAndDay,monthLength ) where diff --git a/Data/Time/Calendar/YearDay.hs b/Data/Time/Calendar/YearDay.hs index f860810..f8673cc 100644 --- a/Data/Time/Calendar/YearDay.hs +++ b/Data/Time/Calendar/YearDay.hs @@ -1,11 +1,6 @@ {-# OPTIONS -Wall -Werror #-} --- #hide -module Data.Time.Calendar.YearDay - ( - -- * Year and day format - module Data.Time.Calendar.YearDay - ) where +module Data.Time.Calendar.YearDay where import Data.Time.Calendar.Days import Data.Time.Calendar.Private diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index 3fbbe0e..c459796 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -11,6 +11,7 @@ import Data.Time.LocalTime.LocalTime import Data.Time.LocalTime.TimeOfDay import Data.Time.LocalTime.TimeZone import Data.Time.Calendar.ISO8601Week +import Data.Time.Calendar.YearDay import Data.Time.Calendar import Data.Time.Calendar.Private import Data.Time.Clock diff --git a/Makefile b/Makefile index b387425..30e47b9 100644 --- a/Makefile +++ b/Makefile @@ -99,8 +99,6 @@ Data/Time/Calendar/Gregorian.o : Data/Time/Calendar/YearDay.hi Data/Time/Calendar/Gregorian.o : Data/Time/Calendar/MonthDay.hi Data/Time/Calendar.o : Data/Time/Calendar.hs Data/Time/Calendar.o : Data/Time/Calendar/Gregorian.hi -Data/Time/Calendar.o : Data/Time/Calendar/MonthDay.hi -Data/Time/Calendar.o : Data/Time/Calendar/YearDay.hi Data/Time/Calendar.o : Data/Time/Calendar/Days.hi Data/Time/Calendar/ISO8601Week.o : Data/Time/Calendar/ISO8601Week.hs Data/Time/Calendar/ISO8601Week.o : Data/Time/Calendar/Private.hi @@ -150,6 +148,7 @@ Data/Time/LocalTime/Format.o : Data/Time/Clock/POSIX.hi Data/Time/LocalTime/Format.o : Data/Time/Clock.hi Data/Time/LocalTime/Format.o : Data/Time/Calendar/Private.hi Data/Time/LocalTime/Format.o : Data/Time/Calendar.hi +Data/Time/LocalTime/Format.o : Data/Time/Calendar/YearDay.hi Data/Time/LocalTime/Format.o : Data/Time/Calendar/ISO8601Week.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/TimeZone.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/TimeOfDay.hi diff --git a/TimeLib.cabal b/TimeLib.cabal index 16a43c7..828074e 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -12,6 +12,8 @@ Synopsis: a new time library Exposed-modules: Data.Fixed, Data.Time.Calendar, + Data.Time.Calendar.MonthDay, + Data.Time.Calendar.YearDay, Data.Time.Calendar.ISO8601Week, Data.Time.Calendar.Julian, Data.Time.Calendar.Easter, @@ -24,8 +26,6 @@ C-Sources: timestuff.c Other-modules: Data.Time.Calendar.Private, Data.Time.Calendar.Days, - Data.Time.Calendar.YearDay, - Data.Time.Calendar.MonthDay, Data.Time.Calendar.Gregorian, Data.Time.Calendar.JulianYearDay, Data.Time.Clock.Scale, From git at git.haskell.org Fri Jan 23 22:55:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:50 +0000 (UTC) Subject: [commit: packages/time] master: fix tests; rename ISO 8601 modules (be389b5) Message-ID: <20150123225550.695173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/be389b5fa0e1fb037903c464139386ae87935cb2 >--------------------------------------------------------------- commit be389b5fa0e1fb037903c464139386ae87935cb2 Author: Ashley Yakeley Date: Sun Nov 27 20:06:14 2005 -0800 fix tests; rename ISO 8601 modules darcs-hash:20051128040614-ac6dd-83a5a6ba7fa4764ae4e9b8cfea18401f260f3aeb >--------------------------------------------------------------- be389b5fa0e1fb037903c464139386ae87935cb2 Data/Time/Calendar/Gregorian.hs | 2 +- Data/Time/Calendar/{YearDay.hs => OrdinalDate.hs} | 2 +- Data/Time/Calendar/{ISO8601Week.hs => WeekDate.hs} | 4 ++-- Data/Time/LocalTime/Format.hs | 4 ++-- Makefile | 24 +++++++++++----------- TimeLib.cabal | 4 ++-- TimeLib.xcodeproj/project.pbxproj | 8 ++++---- test/ClipDates.hs | 3 ++- test/ConvertBack.hs | 3 ++- test/LongWeekYears.hs | 3 ++- test/TestCalendars.hs | 2 +- test/TestMonthDay.hs | 2 +- test/TestTime.hs | 3 ++- test/UseCases.lhs | 1 + 14 files changed, 35 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc be389b5fa0e1fb037903c464139386ae87935cb2 From git at git.haskell.org Fri Jan 23 22:55:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:52 +0000 (UTC) Subject: [commit: packages/time] master: more sensible WeekDate and OrdinalDate names (4752044) Message-ID: <20150123225552.728B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/47520443fcfea4a54bd3e894584e7c1d998d9534 >--------------------------------------------------------------- commit 47520443fcfea4a54bd3e894584e7c1d998d9534 Author: Ashley Yakeley Date: Sun Nov 27 20:40:59 2005 -0800 more sensible WeekDate and OrdinalDate names darcs-hash:20051128044059-ac6dd-0840e1a031d533a71fb5e438f1e3d6bcaa67ee5a >--------------------------------------------------------------- 47520443fcfea4a54bd3e894584e7c1d998d9534 Data/Time/Calendar/Gregorian.hs | 4 ++-- Data/Time/Calendar/OrdinalDate.hs | 18 +++++++++--------- Data/Time/Calendar/WeekDate.hs | 22 +++++++++++----------- Data/Time/LocalTime/Format.hs | 16 ++++++++-------- test/ClipDates.hs | 4 ++-- test/ConvertBack.hs | 4 ++-- test/LongWeekYears.hs | 2 +- test/Makefile | 3 ++- test/TestCalendars.hs | 2 +- test/TestTime.hs | 2 +- test/UseCases.lhs | 4 ++-- 11 files changed, 41 insertions(+), 40 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 47520443fcfea4a54bd3e894584e7c1d998d9534 From git at git.haskell.org Fri Jan 23 22:55:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:54 +0000 (UTC) Subject: [commit: packages/time] master: version 0.3 (90f8854) Message-ID: <20150123225554.797863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/90f8854bf4c9ae3c59c425ea9b9bdaf6eff39bfe >--------------------------------------------------------------- commit 90f8854bf4c9ae3c59c425ea9b9bdaf6eff39bfe Author: Ashley Yakeley Date: Sun Nov 27 20:41:54 2005 -0800 version 0.3 darcs-hash:20051128044154-ac6dd-7cc2b0fc15533e050ef0dd5838501b1030940f6e >--------------------------------------------------------------- 90f8854bf4c9ae3c59c425ea9b9bdaf6eff39bfe TimeLib.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/TimeLib.cabal b/TimeLib.cabal index d8af9e5..2bdac30 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -1,5 +1,5 @@ Name: time -Version: 0.2.1 +Version: 0.3 Stability: Beta License: BSD3 License-File: LICENSE From git at git.haskell.org Fri Jan 23 22:55:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:56 +0000 (UTC) Subject: [commit: packages/time] master: haddock comments for formatTime and others (8573895) Message-ID: <20150123225556.828683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/85738953ad2b075730cf79de9c557dc42f095504 >--------------------------------------------------------------- commit 85738953ad2b075730cf79de9c557dc42f095504 Author: Ashley Yakeley Date: Sat Dec 17 14:10:53 2005 -0800 haddock comments for formatTime and others darcs-hash:20051217221053-ac6dd-21a6dfbffaf15cc895532249c0b8a9cd451a97ca >--------------------------------------------------------------- 85738953ad2b075730cf79de9c557dc42f095504 Data/Time/Calendar/OrdinalDate.hs | 7 +-- Data/Time/Calendar/WeekDate.hs | 7 +-- Data/Time/LocalTime/Format.hs | 95 ++++++++++++++++++++++++++++++++++++++- 3 files changed, 102 insertions(+), 7 deletions(-) diff --git a/Data/Time/Calendar/OrdinalDate.hs b/Data/Time/Calendar/OrdinalDate.hs index 94a1bfa..7c2099a 100644 --- a/Data/Time/Calendar/OrdinalDate.hs +++ b/Data/Time/Calendar/OrdinalDate.hs @@ -1,11 +1,12 @@ {-# OPTIONS -Wall -Werror #-} +-- | ISO 8601 Ordinal Date format module Data.Time.Calendar.OrdinalDate where import Data.Time.Calendar.Days import Data.Time.Calendar.Private --- | convert to ISO 8601 Ordinal Day format. First element of result is year (proleptic Gregoran calendar), +-- | convert to ISO 8601 Ordinal Date format. First element of result is year (proleptic Gregoran calendar), -- second is the day of the year, with 1 for Jan 1, and 365 (or 366 in leap years) for Dec 31. toOrdinalDate :: Day -> (Integer,Int) toOrdinalDate (ModifiedJulianDay mjd) = (year,yd) where @@ -20,14 +21,14 @@ toOrdinalDate (ModifiedJulianDay mjd) = (year,yd) where yd = fromInteger (d - (y * 365) + 1) year = quadcent * 400 + cent * 100 + quad * 4 + y + 1 --- | convert from ISO 8601 Ordinal Day format. +-- | convert from ISO 8601 Ordinal Date format. -- Invalid day numbers will be clipped to the correct range (1 to 365 or 366). fromOrdinalDate :: Integer -> Int -> Day fromOrdinalDate year day = ModifiedJulianDay mjd where y = year - 1 mjd = (fromIntegral (clip 1 (if isLeapYear year then 366 else 365) day)) + (365 * y) + (div y 4) - (div y 100) + (div y 400) - 678576 --- | show in ISO 8601 Ordinal Day format (yyyy-ddd) +-- | show in ISO 8601 Ordinal Date format (yyyy-ddd) showOrdinalDate :: Day -> String showOrdinalDate date = (show4 y) ++ "-" ++ (show3 d) where (y,d) = toOrdinalDate date diff --git a/Data/Time/Calendar/WeekDate.hs b/Data/Time/Calendar/WeekDate.hs index 1d4ebe5..a186ca9 100644 --- a/Data/Time/Calendar/WeekDate.hs +++ b/Data/Time/Calendar/WeekDate.hs @@ -1,12 +1,13 @@ {-# OPTIONS -Wall -Werror #-} +-- | ISO 8601 Week Date format module Data.Time.Calendar.WeekDate where import Data.Time.Calendar.OrdinalDate import Data.Time.Calendar.Days import Data.Time.Calendar.Private --- | convert to ISO 8601 Week format. First element of result is year, second week number (1-53), third day of week (1 for Monday to 7 for Sunday). +-- | convert to ISO 8601 Week Date format. First element of result is year, second week number (1-53), third day of week (1 for Monday to 7 for Sunday). -- Note that \"Week\" years are not quite the same as Gregorian years, as the first day of the year is always a Monday. -- The first week of a year is the first week to contain at least four days in the corresponding Gregorian year. toWeekDate :: Day -> (Integer,Int,Int) @@ -25,7 +26,7 @@ toWeekDate date@(ModifiedJulianDay mjd) = (y1,fromInteger (w1 + 1),fromInteger ( else (y0,w0) else (y0,w0) --- | convert from ISO 8601 Week format. First argument is year, second week number (1-52 or 53), third day of week (1 for Monday to 7 for Sunday). +-- | convert from ISO 8601 Week Date format. First argument is year, second week number (1-52 or 53), third day of week (1 for Monday to 7 for Sunday). -- Invalid week and day values will be clipped to the correct range. fromWeekDate :: Integer -> Int -> Int -> Day fromWeekDate y w d = ModifiedJulianDay (k - (mod k 7) + (toInteger (((clip 1 (if longYear then 53 else 52) w) * 7) + (clip 1 7 d))) - 10) where @@ -34,7 +35,7 @@ fromWeekDate y w d = ModifiedJulianDay (k - (mod k 7) + (toInteger (((clip 1 (if (_,53,_) -> True _ -> False --- | show in ISO 8601 Week format as yyyy-Www-dd (e.g. +-- | show in ISO 8601 Week Date format as yyyy-Www-dd (e.g. showWeekDate :: Day -> String showWeekDate date = (show4 y) ++ "-W" ++ (show2 w) ++ "-" ++ (show d) where (y,w,d) = toWeekDate date diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index 4f36f33..9564868 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -25,6 +25,99 @@ import Data.Char class FormatTime t where formatCharacter :: Char -> Maybe (TimeLocale -> t -> String) +-- | Substitute various time-related information for each %-code in the string, as per 'formatCharacter'. +-- +-- For all types (note these three are done here, not by 'formatCharacter'): +-- +-- [@%%@] @%@ +-- +-- [@%t@] tab +-- +-- [@%n@] newline +-- +-- For TimeZone (and ZonedTime and UTCTime): +-- +-- [@%z@] timezone offset +-- +-- [@%Z@] timezone name +-- +-- For LocalTime (and ZonedTime and UTCTime): +-- +-- [@%c@] as 'dateTimeFmt' @locale@ (e.g. @%a %b %e %H:%M:%S %Z %Y@) +-- +-- For TimeOfDay (and LocalTime and ZonedTime and UTCTime): +-- +-- [@%R@] same as @%H:%M@ +-- +-- [@%T@] same as @%H:%M:%S@ +-- +-- [@%X@] as 'timeFmt' @locale@ (e.g. @%H:%M:%S@) +-- +-- [@%r@] as 'time12Fmt' @locale@ (e.g. @%I:%M:%S %p@) +-- +-- [@%P@] day half from ('amPm' @locale@), converted to lowercase, @am@, @pm@ +-- +-- [@%p@] day half from ('amPm' @locale@), @AM@, @PM@ +-- +-- [@%H@] hour, 24-hour, leading 0 as needed, @00@ - @23@ +-- +-- [@%I@] hour, 12-hour, leading 0 as needed, @01@ - @12@ +-- +-- [@%k@] hour, 24-hour, leading space as needed, @ 0@ - @23@ +-- +-- [@%l@] hour, 12-hour, leading space as needed, @ 1@ - @12@ +-- +-- [@%M@] minute, @00@ - @59@ +-- +-- [@%S@] second with decimal part if not an integer, @00@ - @60.999999999999@ +-- +-- For UTCTime and ZonedTime: +-- +-- [@%s@] number of seconds since the Unix epoch +-- +-- For Day (and LocalTime and ZonedTime and UTCTime): +-- +-- [@%D@] same as @%m\/%d\/%y@ +-- +-- [@%F@] same as @%Y-%m-%d@ +-- +-- [@%x@] as 'dateFmt' @locale@ (e.g. @%m\/%d\/%y@) +-- +-- [@%Y@] year +-- +-- [@%y@] last two digits of year, @00@ - @99@ +-- +-- [@%C@] century (being the first two digits of the year), @00@ - @99@ +-- +-- [@%B@] month name, long form ('fst' from 'months' @locale@), @January@ - @December@ +-- +-- [@%b@, @%h@] month name, short form ('snd' from 'months' @locale@), @Jan@ - @Dec@ +-- +-- [@%m@] month of year, leading 0 as needed, @01@ - @12@ +-- +-- [@%d@] day of month, leading 0 as needed, @01@ - @31@ +-- +-- [@%e@] day of month, leading space as needed, @ 1@ - @31@ +-- +-- [@%j@] day of year for Ordinal Date format, @001@ - @366@ +-- +-- [@%G@] year for Week Date format +-- +-- [@%g@] last two digits of year for Week Date format, @00@ - @99@ +-- +-- [@%V@] week for Week Date format, @01@ - @53@ +-- +-- [@%u@] day for Week Date format, @1@ - @7@ +-- +-- [@%a@] day of week, short form ('snd' from 'wDays' @locale@), @Sun@ - @Sat@ +-- +-- [@%A@] day of week, long form ('fst' from 'wDays' @locale@), @Sunday@ - @Saturday@ +-- +-- [@%U@] week number of year, where weeks start on Sunday (as 'sundayStartWeek'), @01@ - @53@ +-- +-- [@%w@] day of week number, @0@ (= Sunday) - @6@ (= Saturday) +-- +-- [@%W@] week number of year, where weeks start on Monday (as 'mondayStartWeek'), @01@ - @53@ formatTime :: (FormatTime t) => TimeLocale -> String -> t -> String formatTime _ [] _ = "" formatTime locale ('%':c:cs) t = (formatChar c) ++ (formatTime locale cs t) where @@ -100,7 +193,7 @@ instance FormatTime Day where -- Day of Year formatCharacter 'j' = Just (\_ -> show3 . snd . toOrdinalDate) - -- ISOWeekDay + -- ISO 8601 Week Date formatCharacter 'G' = Just (\_ -> show . (\(y,_,_) -> y) . toWeekDate) formatCharacter 'g' = Just (\_ -> show2 . mod100 . (\(y,_,_) -> y) . toWeekDate) formatCharacter 'V' = Just (\_ -> show2 . (\(_,w,_) -> w) . toWeekDate) From git at git.haskell.org Fri Jan 23 22:55:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:55:58 +0000 (UTC) Subject: [commit: packages/time] master: move Data.Time.TAI to Data.Time.Clock.TAI (f99b7a1) Message-ID: <20150123225558.8B7073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f99b7a1d1f143053a1443b43663f2f34c9fc83a1 >--------------------------------------------------------------- commit f99b7a1d1f143053a1443b43663f2f34c9fc83a1 Author: Ashley Yakeley Date: Sat Dec 17 14:19:51 2005 -0800 move Data.Time.TAI to Data.Time.Clock.TAI darcs-hash:20051217221951-ac6dd-98191cd696896f70ab9883e60043ab442885518d >--------------------------------------------------------------- f99b7a1d1f143053a1443b43663f2f34c9fc83a1 Data/Time/{ => Clock}/TAI.hs | 2 +- Makefile | 12 ++++++------ TimeLib.cabal | 2 +- TimeLib.xcodeproj/project.pbxproj | 2 +- test/TestParseDAT.hs | 2 +- 5 files changed, 10 insertions(+), 10 deletions(-) diff --git a/Data/Time/TAI.hs b/Data/Time/Clock/TAI.hs similarity index 99% rename from Data/Time/TAI.hs rename to Data/Time/Clock/TAI.hs index 23d3c08..00cebd5 100644 --- a/Data/Time/TAI.hs +++ b/Data/Time/Clock/TAI.hs @@ -1,7 +1,7 @@ {-# OPTIONS -Wall -Werror #-} -- | TAI and leap-second tables for converting to UTC: most people won't need this module. -module Data.Time.TAI +module Data.Time.Clock.TAI ( -- TAI arithmetic AbsoluteTime,taiEpoch,addAbsoluteTime,diffAbsoluteTime, diff --git a/Makefile b/Makefile index 15f4aae..f4960f2 100644 --- a/Makefile +++ b/Makefile @@ -23,8 +23,8 @@ SRCS = Data/Fixed.hs \ Data/Time/Clock/UTC.hs \ Data/Time/Clock/POSIX.hs \ Data/Time/Clock/Current.hs \ + Data/Time/Clock/TAI.hs \ Data/Time/Clock.hs \ - Data/Time/TAI.hs \ Data/Time/LocalTime/TimeZone.hs \ Data/Time/LocalTime/TimeOfDay.hs \ Data/Time/LocalTime/LocalTime.hs \ @@ -158,11 +158,11 @@ Data/Time/LocalTime.o : Data/Time/LocalTime/Format.hi Data/Time/LocalTime.o : Data/Time/LocalTime/LocalTime.hi Data/Time/LocalTime.o : Data/Time/LocalTime/TimeOfDay.hi Data/Time/LocalTime.o : Data/Time/LocalTime/TimeZone.hi -Data/Time/TAI.o : Data/Time/TAI.hs -Data/Time/TAI.o : Data/Fixed.hi -Data/Time/TAI.o : Data/Time/Clock.hi -Data/Time/TAI.o : Data/Time/Calendar/Days.hi -Data/Time/TAI.o : Data/Time/LocalTime.hi +Data/Time/Clock/TAI.o : Data/Time/Clock/TAI.hs +Data/Time/Clock/TAI.o : Data/Fixed.hi +Data/Time/Clock/TAI.o : Data/Time/Clock.hi +Data/Time/Clock/TAI.o : Data/Time/Calendar/Days.hi +Data/Time/Clock/TAI.o : Data/Time/LocalTime.hi Data/Time.o : Data/Time.hs Data/Time.o : Data/Time/LocalTime.hi Data/Time.o : Data/Time/Clock.hi diff --git a/TimeLib.cabal b/TimeLib.cabal index 2bdac30..04c1d97 100644 --- a/TimeLib.cabal +++ b/TimeLib.cabal @@ -18,7 +18,7 @@ Exposed-modules: Data.Time.Calendar.Julian, Data.Time.Calendar.Easter, Data.Time.Clock, - Data.Time.TAI, + Data.Time.Clock.TAI, Data.Time.LocalTime, Data.Time Extensions: ForeignFunctionInterface diff --git a/TimeLib.xcodeproj/project.pbxproj b/TimeLib.xcodeproj/project.pbxproj index a3e6a24..e382c8e 100644 --- a/TimeLib.xcodeproj/project.pbxproj +++ b/TimeLib.xcodeproj/project.pbxproj @@ -166,7 +166,6 @@ AB01DCFD08374838003C9EF7 /* Clock.hs */, AB2666A808A56FE30059DEC0 /* LocalTime */, AB2666E808A571460059DEC0 /* LocalTime.hs */, - AB01DCFE08374838003C9EF7 /* TAI.hs */, ); path = Time; sourceTree = ""; @@ -214,6 +213,7 @@ ABD67841084168B700CF37C0 /* UTC.hs */, ABD6783F084167B900CF37C0 /* POSIX.hs */, ABD67840084167D100CF37C0 /* Current.hs */, + AB01DCFE08374838003C9EF7 /* TAI.hs */, ); path = Clock; sourceTree = ""; diff --git a/test/TestParseDAT.hs b/test/TestParseDAT.hs index 2f53fab..ee56d49 100644 --- a/test/TestParseDAT.hs +++ b/test/TestParseDAT.hs @@ -3,7 +3,7 @@ module Main where import Data.Time -import Data.Time.TAI +import Data.Time.Clock.TAI import System.IO hSafeGetContents :: Handle -> IO String From git at git.haskell.org Fri Jan 23 22:56:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:00 +0000 (UTC) Subject: [commit: packages/time] master: sort out POSIX module mess (4bfc389) Message-ID: <20150123225600.95AA23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/4bfc389bd98e0a25f2033dd53b3f77733c932e45 >--------------------------------------------------------------- commit 4bfc389bd98e0a25f2033dd53b3f77733c932e45 Author: Ashley Yakeley Date: Sat Dec 17 15:20:41 2005 -0800 sort out POSIX module mess darcs-hash:20051217232041-ac6dd-3796054df5e794cec4e432cc2a9b192ac0f0df5e >--------------------------------------------------------------- 4bfc389bd98e0a25f2033dd53b3f77733c932e45 Data/Time/Clock.hs | 13 +++++++--- Data/Time/Clock/{Current.hs => CTimeval.hs} | 21 ++++------------ Data/Time/Clock/POSIX.hs | 38 ++++++++++++++++++++++++++--- Data/Time/Clock/UTC.hs | 32 +----------------------- Data/Time/LocalTime/TimeOfDay.hs | 8 +++--- Makefile | 15 +++++++++--- TimeLib.cabal | 5 ++-- TimeLib.xcodeproj/project.pbxproj | 6 +++-- test/TestFormat.hs | 2 +- 9 files changed, 73 insertions(+), 67 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4bfc389bd98e0a25f2033dd53b3f77733c932e45 From git at git.haskell.org Fri Jan 23 22:56:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:02 +0000 (UTC) Subject: [commit: packages/time] master: Big Split into separate fixed and time packages (f82aac1) Message-ID: <20150123225602.A2DB23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f82aac1e2d97ce199dba3c5b7875ed3717cf3d79 >--------------------------------------------------------------- commit f82aac1e2d97ce199dba3c5b7875ed3717cf3d79 Author: Ashley Yakeley Date: Sun Feb 5 21:42:30 2006 -0800 Big Split into separate fixed and time packages darcs-hash:20060206054230-ac6dd-a970e95db4cf6337537aaf779596636f8b92f5fe >--------------------------------------------------------------- f82aac1e2d97ce199dba3c5b7875ed3717cf3d79 Makefile | 189 ++------------------- TimeLib.xcodeproj/project.pbxproj | 68 ++++++-- {Data => fixed/Data}/Fixed.hs | 0 LICENSE => fixed/LICENSE | 2 +- fixed/Makefile | 61 +++++++ Setup.hs => fixed/Setup.hs | 0 fixed/fixed.cabal | 13 ++ fixed/test/Makefile | 39 +++++ {test => fixed/test}/TestFixed.hs | 0 {test => fixed/test}/TestFixed.ref | 0 test/Makefile | 97 ----------- {Data => time/Data}/Time.hs | 0 {Data => time/Data}/Time/Calendar.hs | 0 {Data => time/Data}/Time/Calendar/Days.hs | 0 {Data => time/Data}/Time/Calendar/Easter.hs | 0 {Data => time/Data}/Time/Calendar/Gregorian.hs | 0 {Data => time/Data}/Time/Calendar/Julian.hs | 0 {Data => time/Data}/Time/Calendar/JulianYearDay.hs | 0 {Data => time/Data}/Time/Calendar/MonthDay.hs | 0 {Data => time/Data}/Time/Calendar/OrdinalDate.hs | 0 {Data => time/Data}/Time/Calendar/Private.hs | 0 {Data => time/Data}/Time/Calendar/WeekDate.hs | 0 {Data => time/Data}/Time/Clock.hs | 0 {Data => time/Data}/Time/Clock/CTimeval.hs | 0 {Data => time/Data}/Time/Clock/POSIX.hs | 0 {Data => time/Data}/Time/Clock/Scale.hs | 0 {Data => time/Data}/Time/Clock/TAI.hs | 0 {Data => time/Data}/Time/Clock/UTC.hs | 0 {Data => time/Data}/Time/LocalTime.hs | 0 {Data => time/Data}/Time/LocalTime/Format.hs | 0 {Data => time/Data}/Time/LocalTime/LocalTime.hs | 0 {Data => time/Data}/Time/LocalTime/TimeOfDay.hs | 0 {Data => time/Data}/Time/LocalTime/TimeZone.hs | 0 LICENSE => time/LICENSE | 0 Makefile => time/Makefile | 54 +++--- Setup.hs => time/Setup.hs | 0 {test => time/test}/AddDays.hs | 0 {test => time/test}/AddDays.ref | 0 {test => time/test}/ClipDates.hs | 0 {test => time/test}/ClipDates.ref | 0 {test => time/test}/ConvertBack.hs | 0 {test => time/test}/CurrentTime.hs | 0 {test => time/test}/LongWeekYears.hs | 0 {test => time/test}/LongWeekYears.ref | 0 time/test/Makefile | 93 ++++++++++ {test => time/test}/ShowDST.hs | 0 {test => time/test}/TestCalendars.hs | 0 {test => time/test}/TestCalendars.ref | 0 {test => time/test}/TestEaster.hs | 0 {test => time/test}/TestEaster.ref | 0 {test => time/test}/TestFormat.hs | 0 {test => time/test}/TestFormatStuff.c | 0 {test => time/test}/TestFormatStuff.h | 0 {test => time/test}/TestMonthDay.hs | 0 {test => time/test}/TestMonthDay.ref | 0 {test => time/test}/TestParseDAT.hs | 0 {test => time/test}/TestParseDAT.ref | 0 {test => time/test}/TestTime.hs | 0 {test => time/test}/TestTime.ref | 0 {test => time/test}/TimeZone.hs | 0 {test => time/test}/UseCases.lhs | 0 {test => time/test}/tai-utc.dat | 0 TimeLib.cabal => time/time.cabal | 3 +- timestuff.c => time/timestuff.c | 0 timestuff.h => time/timestuff.h | 0 65 files changed, 312 insertions(+), 307 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f82aac1e2d97ce199dba3c5b7875ed3717cf3d79 From git at git.haskell.org Fri Jan 23 22:56:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:04 +0000 (UTC) Subject: [commit: packages/time] master: add missing file; README file; root Makefile clean fix (76b8ca2) Message-ID: <20150123225604.ABE8C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/76b8ca2b62a41a3bddf727de841d35aac11df6d5 >--------------------------------------------------------------- commit 76b8ca2b62a41a3bddf727de841d35aac11df6d5 Author: Ashley Yakeley Date: Sun Feb 5 22:36:47 2006 -0800 add missing file; README file; root Makefile clean fix darcs-hash:20060206063647-ac6dd-e953bb4a546bdbadc1547fcc27f8f30f537eb435 >--------------------------------------------------------------- 76b8ca2b62a41a3bddf727de841d35aac11df6d5 Makefile | 2 +- README | 24 ++++++++++++++++++++++++ time/Data/Time/Clock/UTCDiff.hs | 15 +++++++++++++++ 3 files changed, 40 insertions(+), 1 deletion(-) diff --git a/Makefile b/Makefile index 571d69a..46d68a2 100644 --- a/Makefile +++ b/Makefile @@ -19,6 +19,6 @@ doc: sources haddock -h -o haddock `cat sources` clean: - rm -f sources + rm -f sources haddock cd time && make clean cd fixed && make clean diff --git a/README b/README new file mode 100644 index 0000000..7661654 --- /dev/null +++ b/README @@ -0,0 +1,24 @@ +This contains two packages, "fixed" and "time". They can each be built with Cabal. "time" depends on "fixed". + + cd fixed + runghc Setup.hs configure + runghc Setup.hs build + sudo runghc Setup.hs install + cd .. + + cd time + runghc Setup.hs configure + runghc Setup.hs build + sudo runghc Setup.hs install + cd .. + +You can use it with ghci: + + $ ghci + Prelude> :m +Data.Time + Prelude Data.Time> t <- getCurrentTime + Prelude Data.Time> t + 2006-02-06 06:31:43.859082 UTC + Prelude Data.Time> zt <- getZonedTime + Prelude Data.Time> zt + 2006-02-05 22:32:32.948607 PST diff --git a/time/Data/Time/Clock/UTCDiff.hs b/time/Data/Time/Clock/UTCDiff.hs new file mode 100644 index 0000000..66a2a48 --- /dev/null +++ b/time/Data/Time/Clock/UTCDiff.hs @@ -0,0 +1,15 @@ +{-# OPTIONS -Wall -Werror #-} + +-- #hide +module Data.Time.Clock.UTCDiff where + +import Data.Time.Clock.POSIX +import Data.Time.Clock.UTC + +-- | addUTCTime a b = a + b +addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime +addUTCTime x t = posixSecondsToUTCTime (x + (utcTimeToPOSIXSeconds t)) + +-- | diffUTCTime a b = a - b +diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime +diffUTCTime a b = (utcTimeToPOSIXSeconds a) - (utcTimeToPOSIXSeconds b) From git at git.haskell.org Fri Jan 23 22:56:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:06 +0000 (UTC) Subject: [commit: packages/time] master: export isLeapYear in Calendar; new version (eb6d142) Message-ID: <20150123225606.B403C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/eb6d142d93f770efa3424ac923fe43c3ffabf0ca >--------------------------------------------------------------- commit eb6d142d93f770efa3424ac923fe43c3ffabf0ca Author: Ashley Yakeley Date: Sat Mar 18 19:47:59 2006 -0800 export isLeapYear in Calendar; new version darcs-hash:20060319034759-ac6dd-c81de3b9819edf8f99dd95e5e34af1871d29fab8 >--------------------------------------------------------------- eb6d142d93f770efa3424ac923fe43c3ffabf0ca time/Data/Time/Calendar/Gregorian.hs | 5 ++++- time/time.cabal | 2 +- 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/time/Data/Time/Calendar/Gregorian.hs b/time/Data/Time/Calendar/Gregorian.hs index 9fe381d..2d3546c 100644 --- a/time/Data/Time/Calendar/Gregorian.hs +++ b/time/Data/Time/Calendar/Gregorian.hs @@ -9,7 +9,10 @@ module Data.Time.Calendar.Gregorian -- calendrical arithmetic -- e.g. "one month after March 31st" addGregorianMonthsClip,addGregorianMonthsRollOver, - addGregorianYearsClip,addGregorianYearsRollOver + addGregorianYearsClip,addGregorianYearsRollOver, + + -- re-exported from OrdinalDate + isLeapYear ) where import Data.Time.Calendar.MonthDay diff --git a/time/time.cabal b/time/time.cabal index c682d8c..c0f0fe5 100644 --- a/time/time.cabal +++ b/time/time.cabal @@ -1,5 +1,5 @@ Name: time -Version: 0.3 +Version: 0.3.1 Stability: Beta License: BSD3 License-File: LICENSE From git at git.haskell.org Fri Jan 23 22:56:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:08 +0000 (UTC) Subject: [commit: packages/time] master: remove everything not part of time package (df1c341) Message-ID: <20150123225608.BB2853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/df1c341543873de7d250d9ef92a726647d3ef665 >--------------------------------------------------------------- commit df1c341543873de7d250d9ef92a726647d3ef665 Author: Ashley Yakeley Date: Mon May 1 00:20:30 2006 -0700 remove everything not part of time package darcs-hash:20060501072030-ac6dd-fd9cd75b438585429686c16d0d5b1cd27dd17f31 >--------------------------------------------------------------- df1c341543873de7d250d9ef92a726647d3ef665 LICENSE | 10 ---- Makefile | 24 --------- README | 24 --------- fixed/Data/Fixed.hs | 124 ----------------------------------------------- fixed/LICENSE | 10 ---- fixed/Makefile | 61 ----------------------- fixed/Setup.hs | 2 - fixed/fixed.cabal | 13 ----- fixed/test/Makefile | 39 --------------- fixed/test/TestFixed.hs | 25 ---------- fixed/test/TestFixed.ref | 72 --------------------------- 11 files changed, 404 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc df1c341543873de7d250d9ef92a726647d3ef665 From git at git.haskell.org Fri Jan 23 22:56:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:10 +0000 (UTC) Subject: [commit: packages/time] master: move time files to proper place (e29bc42) Message-ID: <20150123225610.C3FE13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e29bc429afa968dad1a372108a8efd62be28cf03 >--------------------------------------------------------------- commit e29bc429afa968dad1a372108a8efd62be28cf03 Author: Ashley Yakeley Date: Mon May 1 01:07:37 2006 -0700 move time files to proper place darcs-hash:20060501080737-ac6dd-1516981211d8e07fa5bbb97c1e4c24b0cb4661b2 >--------------------------------------------------------------- e29bc429afa968dad1a372108a8efd62be28cf03 {time/Data => Data}/Time.hs | 0 {time/Data => Data}/Time/Calendar.hs | 0 {time/Data => Data}/Time/Calendar/Days.hs | 0 {time/Data => Data}/Time/Calendar/Easter.hs | 0 {time/Data => Data}/Time/Calendar/Gregorian.hs | 0 {time/Data => Data}/Time/Calendar/Julian.hs | 0 {time/Data => Data}/Time/Calendar/JulianYearDay.hs | 0 {time/Data => Data}/Time/Calendar/MonthDay.hs | 0 {time/Data => Data}/Time/Calendar/OrdinalDate.hs | 0 {time/Data => Data}/Time/Calendar/Private.hs | 0 {time/Data => Data}/Time/Calendar/WeekDate.hs | 0 {time/Data => Data}/Time/Clock.hs | 0 {time/Data => Data}/Time/Clock/CTimeval.hs | 0 {time/Data => Data}/Time/Clock/POSIX.hs | 0 {time/Data => Data}/Time/Clock/Scale.hs | 0 {time/Data => Data}/Time/Clock/TAI.hs | 0 {time/Data => Data}/Time/Clock/UTC.hs | 0 {time/Data => Data}/Time/Clock/UTCDiff.hs | 0 {time/Data => Data}/Time/LocalTime.hs | 0 {time/Data => Data}/Time/LocalTime/Format.hs | 0 {time/Data => Data}/Time/LocalTime/LocalTime.hs | 0 {time/Data => Data}/Time/LocalTime/TimeOfDay.hs | 0 {time/Data => Data}/Time/LocalTime/TimeZone.hs | 0 time/LICENSE => LICENSE | 0 time/Setup.hs => Setup.hs | 0 time/time.cabal => time.cabal | 4 ++-- time/timestuff.c => timestuff.c | 0 time/timestuff.h => timestuff.h | 0 28 files changed, 2 insertions(+), 2 deletions(-) diff --git a/time/Data/Time.hs b/Data/Time.hs similarity index 100% rename from time/Data/Time.hs rename to Data/Time.hs diff --git a/time/Data/Time/Calendar.hs b/Data/Time/Calendar.hs similarity index 100% rename from time/Data/Time/Calendar.hs rename to Data/Time/Calendar.hs diff --git a/time/Data/Time/Calendar/Days.hs b/Data/Time/Calendar/Days.hs similarity index 100% rename from time/Data/Time/Calendar/Days.hs rename to Data/Time/Calendar/Days.hs diff --git a/time/Data/Time/Calendar/Easter.hs b/Data/Time/Calendar/Easter.hs similarity index 100% rename from time/Data/Time/Calendar/Easter.hs rename to Data/Time/Calendar/Easter.hs diff --git a/time/Data/Time/Calendar/Gregorian.hs b/Data/Time/Calendar/Gregorian.hs similarity index 100% rename from time/Data/Time/Calendar/Gregorian.hs rename to Data/Time/Calendar/Gregorian.hs diff --git a/time/Data/Time/Calendar/Julian.hs b/Data/Time/Calendar/Julian.hs similarity index 100% rename from time/Data/Time/Calendar/Julian.hs rename to Data/Time/Calendar/Julian.hs diff --git a/time/Data/Time/Calendar/JulianYearDay.hs b/Data/Time/Calendar/JulianYearDay.hs similarity index 100% rename from time/Data/Time/Calendar/JulianYearDay.hs rename to Data/Time/Calendar/JulianYearDay.hs diff --git a/time/Data/Time/Calendar/MonthDay.hs b/Data/Time/Calendar/MonthDay.hs similarity index 100% rename from time/Data/Time/Calendar/MonthDay.hs rename to Data/Time/Calendar/MonthDay.hs diff --git a/time/Data/Time/Calendar/OrdinalDate.hs b/Data/Time/Calendar/OrdinalDate.hs similarity index 100% rename from time/Data/Time/Calendar/OrdinalDate.hs rename to Data/Time/Calendar/OrdinalDate.hs diff --git a/time/Data/Time/Calendar/Private.hs b/Data/Time/Calendar/Private.hs similarity index 100% rename from time/Data/Time/Calendar/Private.hs rename to Data/Time/Calendar/Private.hs diff --git a/time/Data/Time/Calendar/WeekDate.hs b/Data/Time/Calendar/WeekDate.hs similarity index 100% rename from time/Data/Time/Calendar/WeekDate.hs rename to Data/Time/Calendar/WeekDate.hs diff --git a/time/Data/Time/Clock.hs b/Data/Time/Clock.hs similarity index 100% rename from time/Data/Time/Clock.hs rename to Data/Time/Clock.hs diff --git a/time/Data/Time/Clock/CTimeval.hs b/Data/Time/Clock/CTimeval.hs similarity index 100% rename from time/Data/Time/Clock/CTimeval.hs rename to Data/Time/Clock/CTimeval.hs diff --git a/time/Data/Time/Clock/POSIX.hs b/Data/Time/Clock/POSIX.hs similarity index 100% rename from time/Data/Time/Clock/POSIX.hs rename to Data/Time/Clock/POSIX.hs diff --git a/time/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs similarity index 100% rename from time/Data/Time/Clock/Scale.hs rename to Data/Time/Clock/Scale.hs diff --git a/time/Data/Time/Clock/TAI.hs b/Data/Time/Clock/TAI.hs similarity index 100% rename from time/Data/Time/Clock/TAI.hs rename to Data/Time/Clock/TAI.hs diff --git a/time/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs similarity index 100% rename from time/Data/Time/Clock/UTC.hs rename to Data/Time/Clock/UTC.hs diff --git a/time/Data/Time/Clock/UTCDiff.hs b/Data/Time/Clock/UTCDiff.hs similarity index 100% rename from time/Data/Time/Clock/UTCDiff.hs rename to Data/Time/Clock/UTCDiff.hs diff --git a/time/Data/Time/LocalTime.hs b/Data/Time/LocalTime.hs similarity index 100% rename from time/Data/Time/LocalTime.hs rename to Data/Time/LocalTime.hs diff --git a/time/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs similarity index 100% rename from time/Data/Time/LocalTime/Format.hs rename to Data/Time/LocalTime/Format.hs diff --git a/time/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs similarity index 100% rename from time/Data/Time/LocalTime/LocalTime.hs rename to Data/Time/LocalTime/LocalTime.hs diff --git a/time/Data/Time/LocalTime/TimeOfDay.hs b/Data/Time/LocalTime/TimeOfDay.hs similarity index 100% rename from time/Data/Time/LocalTime/TimeOfDay.hs rename to Data/Time/LocalTime/TimeOfDay.hs diff --git a/time/Data/Time/LocalTime/TimeZone.hs b/Data/Time/LocalTime/TimeZone.hs similarity index 100% rename from time/Data/Time/LocalTime/TimeZone.hs rename to Data/Time/LocalTime/TimeZone.hs diff --git a/time/LICENSE b/LICENSE similarity index 100% rename from time/LICENSE rename to LICENSE diff --git a/time/Setup.hs b/Setup.hs similarity index 100% rename from time/Setup.hs rename to Setup.hs diff --git a/time/time.cabal b/time.cabal similarity index 94% rename from time/time.cabal rename to time.cabal index c0f0fe5..4d8ebf5 100644 --- a/time/time.cabal +++ b/time.cabal @@ -7,8 +7,8 @@ Author: Ashley Yakeley Maintainer: Homepage: http://semantic.org/TimeLib/ Category: -Build-Depends: base, fixed -Synopsis: a new time library +Build-Depends: base +Synopsis: time library Exposed-modules: Data.Time.Calendar, Data.Time.Calendar.MonthDay, diff --git a/time/timestuff.c b/timestuff.c similarity index 100% rename from time/timestuff.c rename to timestuff.c diff --git a/time/timestuff.h b/timestuff.h similarity index 100% rename from time/timestuff.h rename to timestuff.h From git at git.haskell.org Fri Jan 23 22:56:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:12 +0000 (UTC) Subject: [commit: packages/time] master: make suitable for build process (7d86eaa) Message-ID: <20150123225612.CD45D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/7d86eaa6b7ef59d9fb09c9b1cbe74c76621404b3 >--------------------------------------------------------------- commit 7d86eaa6b7ef59d9fb09c9b1cbe74c76621404b3 Author: Ashley Yakeley Date: Mon May 1 02:21:11 2006 -0700 make suitable for build process darcs-hash:20060501092111-ac6dd-5bffa4956f92b470779215f8b501d2cb7e7fcafc >--------------------------------------------------------------- 7d86eaa6b7ef59d9fb09c9b1cbe74c76621404b3 Makefile | 23 +++++++++++++++++++++++ Setup.hs | 2 -- timestuff.h => include/timestuff.h | 0 time.cabal => package.conf.in | 7 +++++-- 4 files changed, 28 insertions(+), 4 deletions(-) diff --git a/Makefile b/Makefile new file mode 100644 index 0000000..33c2a3f --- /dev/null +++ b/Makefile @@ -0,0 +1,23 @@ +TOP=.. +include $(TOP)/mk/boilerplate.mk + +SUBDIRS = + +ALL_DIRS = \ + Data \ + Data/Time \ + Data/Time/Calendar \ + Data/Time/Clock \ + Data/Time/LocalTime + +PACKAGE = time +VERSION = 0.3.1 +PACKAGE_DEPS = base + +SRC_HC_OPTS += -Wall -Werror -fffi -Iinclude + +SRC_CC_OPTS += -Wall -Werror -Iinclude + +SRC_HADDOCK_OPTS += -t "Haskell Hierarchical Libraries ($(PACKAGE) package)" + +include $(TOP)/mk/target.mk diff --git a/Setup.hs b/Setup.hs deleted file mode 100644 index 9a994af..0000000 --- a/Setup.hs +++ /dev/null @@ -1,2 +0,0 @@ -import Distribution.Simple -main = defaultMain diff --git a/timestuff.h b/include/timestuff.h similarity index 100% rename from timestuff.h rename to include/timestuff.h diff --git a/time.cabal b/package.conf.in similarity index 90% copy from time.cabal copy to package.conf.in index 4d8ebf5..eec6b3a 100644 --- a/time.cabal +++ b/package.conf.in @@ -1,11 +1,12 @@ -Name: time -Version: 0.3.1 +Name: PACKAGE +Version: VERSION Stability: Beta License: BSD3 License-File: LICENSE Author: Ashley Yakeley Maintainer: Homepage: http://semantic.org/TimeLib/ +exposed: True Category: Build-Depends: base Synopsis: time library @@ -36,3 +37,5 @@ Other-modules: Data.Time.LocalTime.TimeOfDay, Data.Time.LocalTime.LocalTime, Data.Time.LocalTime.Format +include-dirs: INCLUDE_DIR +includes: "timestuff.h" From git at git.haskell.org Fri Jan 23 22:56:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:14 +0000 (UTC) Subject: [commit: packages/time] master: haddock working with time package (021cdd7) Message-ID: <20150123225614.D472E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/021cdd7549ae6472c25adaa7b3a49dac7af082b0 >--------------------------------------------------------------- commit 021cdd7549ae6472c25adaa7b3a49dac7af082b0 Author: Ashley Yakeley Date: Tue May 2 22:41:16 2006 -0700 haddock working with time package darcs-hash:20060503054116-ac6dd-5604e00093fa50793b3a97849988ca2530a82cc3 >--------------------------------------------------------------- 021cdd7549ae6472c25adaa7b3a49dac7af082b0 package.conf.in | 2 ++ prologue.txt | 2 ++ 2 files changed, 4 insertions(+) diff --git a/package.conf.in b/package.conf.in index eec6b3a..dd2a3cb 100644 --- a/package.conf.in +++ b/package.conf.in @@ -39,3 +39,5 @@ Other-modules: Data.Time.LocalTime.Format include-dirs: INCLUDE_DIR includes: "timestuff.h" +haddock-interfaces: HADDOCK_IFACE +haddock-html: HTML_DIR diff --git a/prologue.txt b/prologue.txt new file mode 100644 index 0000000..6fa7b04 --- /dev/null +++ b/prologue.txt @@ -0,0 +1,2 @@ +Clock and calendar time. + From git at git.haskell.org Fri Jan 23 22:56:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:16 +0000 (UTC) Subject: [commit: packages/time] master: set up boringfile (706483e) Message-ID: <20150123225616.DB53B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/706483e5b72570be046ca6c352540bca01507217 >--------------------------------------------------------------- commit 706483e5b72570be046ca6c352540bca01507217 Author: Ashley Yakeley Date: Wed May 3 23:20:30 2006 -0700 set up boringfile darcs-hash:20060504062030-ac6dd-233eb703d26a826c1c664cf52f3d8a23dd5a8203 >--------------------------------------------------------------- 706483e5b72570be046ca6c352540bca01507217 .darcs-boring | 43 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 43 insertions(+) diff --git a/.darcs-boring b/.darcs-boring new file mode 100644 index 0000000..61e18b4 --- /dev/null +++ b/.darcs-boring @@ -0,0 +1,43 @@ +# Boring file regexps: +\.hi$ +\.o$ +\.p_hi$ +\.p_o$ +\.raw-hs$ +_split$ +\.a$ +(^|/)dist$ +(^|/)package.conf.inplace$ +(^|/)package.conf.installed$ +(^|/)\.depend$ +(^|/)\.setup-config$ +\.haddock$ +\.o\.cmd$ +\.ko$ +\.ko\.cmd$ +\.mod\.c$ +(^|/)\.tmp_versions($|/) +(^|/)CVS($|/) +(^|/)RCS($|/) +~$ +#(^|/)\.[^/] +(^|/)_darcs($|/) +\.bak$ +\.BAK$ +\.orig$ +(^|/)vssver\.scc$ +\.swp$ +(^|/)MT($|/) +(^|/)\{arch\}($|/) +(^|/).arch-ids($|/) +(^|/), +\.class$ +\.prof$ +(^|/)\.DS_Store$ +(^|/)BitKeeper($|/) +(^|/)ChangeSet($|/) +(^|/)\.svn($|/) +\.py[co]$ +\# +\.cvsignore$ +(^|/)Thumbs\.db$ From git at git.haskell.org Fri Jan 23 22:56:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:18 +0000 (UTC) Subject: [commit: packages/time] master: XCode build and temp files are boring (e5ea873) Message-ID: <20150123225618.E1F8D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e5ea873e700621b7221433617392fa79d2be732e >--------------------------------------------------------------- commit e5ea873e700621b7221433617392fa79d2be732e Author: Ashley Yakeley Date: Wed May 3 23:27:58 2006 -0700 XCode build and temp files are boring darcs-hash:20060504062758-ac6dd-3987f29736c7fb7e2286a95f7a2113addbc513e9 >--------------------------------------------------------------- e5ea873e700621b7221433617392fa79d2be732e .darcs-boring | 3 +++ 1 file changed, 3 insertions(+) diff --git a/.darcs-boring b/.darcs-boring index 61e18b4..6c379a9 100644 --- a/.darcs-boring +++ b/.darcs-boring @@ -12,6 +12,9 @@ _split$ (^|/)\.depend$ (^|/)\.setup-config$ \.haddock$ +^build$ +\.xcodeproj/.*\.pbxuser$ +\.xcodeproj/.*\.mode1$ \.o\.cmd$ \.ko$ \.ko\.cmd$ From git at git.haskell.org Fri Jan 23 22:56:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:20 +0000 (UTC) Subject: [commit: packages/time] master: Various fixes to make this build & work on Windows (4b425ec) Message-ID: <20150123225620.EBF083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/4b425ec9819e4a3c0ae52a3f84c2094d46a1ceac >--------------------------------------------------------------- commit 4b425ec9819e4a3c0ae52a3f84c2094d46a1ceac Author: Simon Marlow Date: Mon May 29 05:25:23 2006 -0700 Various fixes to make this build & work on Windows A number of things didn't work on Windows: we were using gettimeofday() which doesn't exist, localtime_r() doesn't exist, the tm_zone field in struct tm doesn't exist, etc. * timestuff.{c,h} is now cbits/HsTime.c and includes/HsTime.h, for consistency with other packages * There's a configure script. Hence, a default Setup.hs will be required for using Cabal (I haven't added this yet, I think we were going to make some more changes in Cabal to make it optional). * fixed various problems in package.conf.in. I haven't tested time.cabal, I expect it doesn't work on Windows, but it might still work on Unix. * We get the current time from the native Win32 API. This requires the Win32 library, hence a conditional dependency on Win32. * some cursory testing on Win32, we can get the local time and the timezone looks ok. darcs-hash:20060529122523-760e2-1707aeb6dcf612f6c7c134b1eab52c1187a8305f >--------------------------------------------------------------- 4b425ec9819e4a3c0ae52a3f84c2094d46a1ceac Data/Time/Clock/CTimeval.hs | 7 +++++- Data/Time/Clock/POSIX.hs | 34 ++++++++++++++++++++++---- Data/Time/LocalTime/TimeZone.hs | 2 +- Makefile | 3 +++ aclocal.m4 | 19 +++++++++++++++ cbits/HsTime.c | 54 +++++++++++++++++++++++++++++++++++++++++ configure.ac | 15 ++++++++++++ include/HsTime.h | 13 ++++++++++ include/timestuff.h | 3 --- package.conf.in | 19 ++++++++++++--- time.cabal | 4 ++- timestuff.c | 14 ----------- 12 files changed, 158 insertions(+), 29 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4b425ec9819e4a3c0ae52a3f84c2094d46a1ceac From git at git.haskell.org Fri Jan 23 22:56:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:22 +0000 (UTC) Subject: [commit: packages/time] master: fix build breakage on Linux (a499f3f) Message-ID: <20150123225622.F2D4F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/a499f3f06163bbf84bf104334db88b28de599d63 >--------------------------------------------------------------- commit a499f3f06163bbf84bf104334db88b28de599d63 Author: Simon Marlow Date: Mon May 29 05:42:50 2006 -0700 fix build breakage on Linux darcs-hash:20060529124250-760e2-12bae2db16624f19ae6462abe185ae79d3a04ad2 >--------------------------------------------------------------- a499f3f06163bbf84bf104334db88b28de599d63 cbits/HsTime.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cbits/HsTime.c b/cbits/HsTime.c index a63836f..6fd8342 100644 --- a/cbits/HsTime.c +++ b/cbits/HsTime.c @@ -6,7 +6,7 @@ long int get_current_timezone_seconds (time_t t,int* pdst,char const* * pname) struct tm* ptm; long gmtoff; int dst; - char *name; + const char *name; #if HAVE_LOCALTIME_R struct tm tmd; From git at git.haskell.org Fri Jan 23 22:56:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:25 +0000 (UTC) Subject: [commit: packages/time] master: CFILES directive for the benefit of Hugs (76bf7f8) Message-ID: <20150123225625.073CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/76bf7f82a6d883d933b97f1187aef79cd3cebbfb >--------------------------------------------------------------- commit 76bf7f82a6d883d933b97f1187aef79cd3cebbfb Author: Ross Paterson Date: Tue May 30 16:29:48 2006 -0700 CFILES directive for the benefit of Hugs darcs-hash:20060530232948-b47d3-2ff97506454a770200384abb80b730d91a45c73d >--------------------------------------------------------------- 76bf7f82a6d883d933b97f1187aef79cd3cebbfb Data/Time/LocalTime/TimeZone.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Data/Time/LocalTime/TimeZone.hs b/Data/Time/LocalTime/TimeZone.hs index 07c1c01..d80671e 100644 --- a/Data/Time/LocalTime/TimeZone.hs +++ b/Data/Time/LocalTime/TimeZone.hs @@ -52,6 +52,7 @@ instance Show TimeZone where utc :: TimeZone utc = TimeZone 0 False "UTC" +{-# CFILES cbits/HsTime.c #-} foreign import ccall unsafe "HsTime.h get_current_timezone_seconds" get_current_timezone_seconds :: CTime -> Ptr CInt -> Ptr CString -> IO CLong posixToCTime :: POSIXTime -> CTime From git at git.haskell.org Fri Jan 23 22:56:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:27 +0000 (UTC) Subject: [commit: packages/time] master: remove dependency on ghcconfig.h (f67b546) Message-ID: <20150123225627.0C8F13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f67b5466dd799a0ce8b7847a71b1fa9f2ad6f2c2 >--------------------------------------------------------------- commit f67b5466dd799a0ce8b7847a71b1fa9f2ad6f2c2 Author: Ross Paterson Date: Tue May 30 16:30:29 2006 -0700 remove dependency on ghcconfig.h darcs-hash:20060530233029-b47d3-8879f40442c09036bcb394df9f8bcf4f08a40d12 >--------------------------------------------------------------- f67b5466dd799a0ce8b7847a71b1fa9f2ad6f2c2 configure.ac | 1 + include/HsTime.h | 1 - 2 files changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 51dbd33..f2e4186 100644 --- a/configure.ac +++ b/configure.ac @@ -5,6 +5,7 @@ AC_CONFIG_SRCDIR([include/HsTime.h]) AC_CONFIG_HEADERS([include/HsTimeConfig.h]) +AC_CHECK_HEADERS([time.h]) AC_CHECK_FUNCS([gmtime_r localtime_r]) AC_STRUCT_TM diff --git a/include/HsTime.h b/include/HsTime.h index b447792..b8da946 100644 --- a/include/HsTime.h +++ b/include/HsTime.h @@ -1,7 +1,6 @@ #ifndef __HSTIME_H__ #define __HSTIME_H__ -#include "ghcconfig.h" #include "HsTimeConfig.h" #if HAVE_TIME_H From git at git.haskell.org Fri Jan 23 22:56:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:29 +0000 (UTC) Subject: [commit: packages/time] master: extra Cabal fields for clean and sdist (37fd2cd) Message-ID: <20150123225629.148603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/37fd2cdcfa945dee219ecfa5e69f3b640da9321b >--------------------------------------------------------------- commit 37fd2cdcfa945dee219ecfa5e69f3b640da9321b Author: Ross Paterson Date: Tue May 30 16:51:52 2006 -0700 extra Cabal fields for clean and sdist darcs-hash:20060530235152-b47d3-782de042e361c2c70e3bdf8d7677f4fdf36314d4 >--------------------------------------------------------------- 37fd2cdcfa945dee219ecfa5e69f3b640da9321b time.cabal | 16 +++++++++++----- 1 file changed, 11 insertions(+), 5 deletions(-) diff --git a/time.cabal b/time.cabal index cce942c..89881a0 100644 --- a/time.cabal +++ b/time.cabal @@ -1,6 +1,6 @@ Name: time Version: 0.3.1 -Stability: Beta +Stability: beta License: BSD3 License-File: LICENSE Author: Ashley Yakeley @@ -9,7 +9,7 @@ Homepage: http://semantic.org/TimeLib/ Category: Build-Depends: base Synopsis: time library -Exposed-modules: +Exposed-Modules: Data.Time.Calendar, Data.Time.Calendar.MonthDay, Data.Time.Calendar.OrdinalDate, @@ -23,7 +23,7 @@ Exposed-modules: Data.Time Extensions: ForeignFunctionInterface C-Sources: HsTime.c -Other-modules: +Other-Modules: Data.Time.Calendar.Private, Data.Time.Calendar.Days, Data.Time.Calendar.Gregorian, @@ -36,5 +36,11 @@ Other-modules: Data.Time.LocalTime.TimeOfDay, Data.Time.LocalTime.LocalTime, Data.Time.LocalTime.Format -include-dirs: include -includes: "HsTime.h" +Extra-Source-Files: + configure.ac configure + include/HsTime.h include/HsTimeConfig.h.in +Extra-Tmp-Files: + config.log config.status autom4te.cache + include/HsTimeConfig.h +Include-Dirs: include +Includes: "HsTime.h" From git at git.haskell.org Fri Jan 23 22:56:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:31 +0000 (UTC) Subject: [commit: packages/time] master: fix typo (3721982) Message-ID: <20150123225631.1C6DD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/37219827d0e5796eb716007399dcbf3270b73986 >--------------------------------------------------------------- commit 37219827d0e5796eb716007399dcbf3270b73986 Author: Simon Marlow Date: Tue Jun 6 05:16:20 2006 -0700 fix typo darcs-hash:20060606121620-760e2-1dc4cf4db92cbe47dcbfb7cca4b8f6e34df94c4d >--------------------------------------------------------------- 37219827d0e5796eb716007399dcbf3270b73986 package.conf.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/package.conf.in b/package.conf.in index f308e51..98922d7 100644 --- a/package.conf.in +++ b/package.conf.in @@ -47,7 +47,7 @@ Hidden-modules: Data.Time.LocalTime.Format import-dirs: IMPORT_DIR library-dirs: LIB_DIR -hs-libraries: "HSTime" +hs-libraries: "HStime" include-dirs: INCLUDE_DIR includes: "HsTime.h" haddock-interfaces: HADDOCK_IFACE From git at git.haskell.org Fri Jan 23 22:56:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:33 +0000 (UTC) Subject: [commit: packages/time] master: re-add #include "ghcconfig.h", conditional on __GLASGOW_HASKELL__ (17faab4) Message-ID: <20150123225633.23DB13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/17faab4835a1decbb2c3dd5297b0073e56a8eed7 >--------------------------------------------------------------- commit 17faab4835a1decbb2c3dd5297b0073e56a8eed7 Author: simonmar Date: Tue Jun 6 05:38:41 2006 -0700 re-add #include "ghcconfig.h", conditional on __GLASGOW_HASKELL__ darcs-hash:20060606123841-3ed52-e9ff9e6558dfbbc2ed6b26a3abb430079749e9c4 >--------------------------------------------------------------- 17faab4835a1decbb2c3dd5297b0073e56a8eed7 include/HsTime.h | 3 +++ 1 file changed, 3 insertions(+) diff --git a/include/HsTime.h b/include/HsTime.h index b8da946..baca0d5 100644 --- a/include/HsTime.h +++ b/include/HsTime.h @@ -1,6 +1,9 @@ #ifndef __HSTIME_H__ #define __HSTIME_H__ +#ifdef __GLASGOW_HASKELL__ +#include "ghcconfig.h" +#endif #include "HsTimeConfig.h" #if HAVE_TIME_H From git at git.haskell.org Fri Jan 23 22:56:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:35 +0000 (UTC) Subject: [commit: packages/time] master: remove debugging code (580b6d2) Message-ID: <20150123225635.2A0573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/580b6d2b0e3c6409b1592c508754460c079a3969 >--------------------------------------------------------------- commit 580b6d2b0e3c6409b1592c508754460c079a3969 Author: simonmar Date: Tue Jun 6 06:00:44 2006 -0700 remove debugging code darcs-hash:20060606130044-3ed52-0c26fad63e2d0cde23c686bccd51205105b702a5 >--------------------------------------------------------------- 580b6d2b0e3c6409b1592c508754460c079a3969 cbits/HsTime.c | 1 - 1 file changed, 1 deletion(-) diff --git a/cbits/HsTime.c b/cbits/HsTime.c index 6fd8342..133fd6c 100644 --- a/cbits/HsTime.c +++ b/cbits/HsTime.c @@ -29,7 +29,6 @@ long int get_current_timezone_seconds (time_t t,int* pdst,char const* * pname) # if mingw32_HOST_OS name = dst ? _tzname[1] : _tzname[0]; - printf("dst: %d, tzname0: %s, tzname1: %s\n", dst, _tzname[0], _tzname[1]); # elif HAVE_TZNAME name = *tzname; # else From git at git.haskell.org Fri Jan 23 22:56:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:37 +0000 (UTC) Subject: [commit: packages/time] master: use non-GHC-specific #ifdef test for Windows (d65e1de) Message-ID: <20150123225637.30EB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/d65e1de56921e9646f42f7cfda349100d57f1bba >--------------------------------------------------------------- commit d65e1de56921e9646f42f7cfda349100d57f1bba Author: Simon Marlow Date: Wed Jun 7 01:18:06 2006 -0700 use non-GHC-specific #ifdef test for Windows darcs-hash:20060607081806-760e2-001f4dfd1e83fba078f4d18274e0bda5ce8910c3 >--------------------------------------------------------------- d65e1de56921e9646f42f7cfda349100d57f1bba cbits/HsTime.c | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/cbits/HsTime.c b/cbits/HsTime.c index 133fd6c..7e93fe8 100644 --- a/cbits/HsTime.c +++ b/cbits/HsTime.c @@ -26,8 +26,7 @@ long int get_current_timezone_seconds (time_t t,int* pdst,char const* * pname) name = ptm -> tm_zone; gmtoff = ptm -> tm_gmtoff; #else - -# if mingw32_HOST_OS +# if defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32) name = dst ? _tzname[1] : _tzname[0]; # elif HAVE_TZNAME name = *tzname; From git at git.haskell.org Fri Jan 23 22:56:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:39 +0000 (UTC) Subject: [commit: packages/time] master: no need to include ghcconfig.h any more (cecf1ab) Message-ID: <20150123225639.389993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/cecf1abf74c74307c799d2f7555bcca2fb010f2a >--------------------------------------------------------------- commit cecf1abf74c74307c799d2f7555bcca2fb010f2a Author: Simon Marlow Date: Wed Jun 7 01:18:29 2006 -0700 no need to include ghcconfig.h any more darcs-hash:20060607081829-760e2-39d464373937cba058c1f6b2b6b6bfd5c16d98a5 >--------------------------------------------------------------- cecf1abf74c74307c799d2f7555bcca2fb010f2a include/HsTime.h | 3 --- 1 file changed, 3 deletions(-) diff --git a/include/HsTime.h b/include/HsTime.h index baca0d5..b8da946 100644 --- a/include/HsTime.h +++ b/include/HsTime.h @@ -1,9 +1,6 @@ #ifndef __HSTIME_H__ #define __HSTIME_H__ -#ifdef __GLASGOW_HASKELL__ -#include "ghcconfig.h" -#endif #include "HsTimeConfig.h" #if HAVE_TIME_H From git at git.haskell.org Fri Jan 23 22:56:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:41 +0000 (UTC) Subject: [commit: packages/time] master: eliminate the other mingw32_HOST_OS test (0108ad0) Message-ID: <20150123225641.3EFEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/0108ad00f1ea1b38f448a7a3462a1745b892467c >--------------------------------------------------------------- commit 0108ad00f1ea1b38f448a7a3462a1745b892467c Author: Ross Paterson Date: Wed Jun 7 01:35:28 2006 -0700 eliminate the other mingw32_HOST_OS test darcs-hash:20060607083528-b47d3-c41fa71af0c4ab114f85816306687ee85c2860a1 >--------------------------------------------------------------- 0108ad00f1ea1b38f448a7a3462a1745b892467c cbits/HsTime.c | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/cbits/HsTime.c b/cbits/HsTime.c index 7e93fe8..f9651e9 100644 --- a/cbits/HsTime.c +++ b/cbits/HsTime.c @@ -25,18 +25,18 @@ long int get_current_timezone_seconds (time_t t,int* pdst,char const* * pname) #if HAVE_TM_ZONE name = ptm -> tm_zone; gmtoff = ptm -> tm_gmtoff; -#else -# if defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32) +#elif defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32) name = dst ? _tzname[1] : _tzname[0]; -# elif HAVE_TZNAME + gmtoff = dst ? _timezone - 3600 : _timezone; +#else + +# if HAVE_TZNAME name = *tzname; # else # error "Don't know how to get at timezone name on your OS" # endif -# if mingw32_HOST_OS - gmtoff = dst ? _timezone - 3600 : _timezone; -# elif HAVE_DECL_ALTZONE +# if HAVE_DECL_ALTZONE gmtoff = dst ? altzone : timezone; # else gmtoff = dst ? timezone - 3600 : timezone; From git at git.haskell.org Fri Jan 23 22:56:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:43 +0000 (UTC) Subject: [commit: packages/time] master: Set version to 1.0 stable (0908d41) Message-ID: <20150123225643.453093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/0908d41b2b54d964238138e073a560f73a7b48ae >--------------------------------------------------------------- commit 0908d41b2b54d964238138e073a560f73a7b48ae Author: Ashley Yakeley Date: Sun Jun 11 15:03:22 2006 -0700 Set version to 1.0 stable darcs-hash:20060611220322-ac6dd-ab053b27abeaf26b9342a0ae7c5151d61f1e95f5 >--------------------------------------------------------------- 0908d41b2b54d964238138e073a560f73a7b48ae Makefile | 2 +- time.cabal | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/Makefile b/Makefile index 9ee3b33..9c27f39 100644 --- a/Makefile +++ b/Makefile @@ -12,7 +12,7 @@ ALL_DIRS = \ Data/Time/LocalTime PACKAGE = time -VERSION = 0.3.1 +VERSION = 1.0 PACKAGE_DEPS = base SRC_HC_OPTS += -Wall -Werror -fffi -Iinclude diff --git a/time.cabal b/time.cabal index 89881a0..80096e6 100644 --- a/time.cabal +++ b/time.cabal @@ -1,6 +1,6 @@ Name: time -Version: 0.3.1 -Stability: beta +Version: 1.0 +Stability: stable License: BSD3 License-File: LICENSE Author: Ashley Yakeley From git at git.haskell.org Fri Jan 23 22:56:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:45 +0000 (UTC) Subject: [commit: packages/time] master: add aclocal.m4 to extra sources (4def2c0) Message-ID: <20150123225645.4BD003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/4def2c0923b48c9b3dcfdf996b83163d82649c82 >--------------------------------------------------------------- commit 4def2c0923b48c9b3dcfdf996b83163d82649c82 Author: Ross Paterson Date: Tue Aug 29 05:36:40 2006 -0700 add aclocal.m4 to extra sources darcs-hash:20060829123640-b47d3-3e8a7c23975307c746b443eca30ca4c427468bcf >--------------------------------------------------------------- 4def2c0923b48c9b3dcfdf996b83163d82649c82 time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 80096e6..672bd2a 100644 --- a/time.cabal +++ b/time.cabal @@ -37,7 +37,7 @@ Other-Modules: Data.Time.LocalTime.LocalTime, Data.Time.LocalTime.Format Extra-Source-Files: - configure.ac configure + aclocal.m4 configure.ac configure include/HsTime.h include/HsTimeConfig.h.in Extra-Tmp-Files: config.log config.status autom4te.cache From git at git.haskell.org Fri Jan 23 22:56:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:47 +0000 (UTC) Subject: [commit: packages/time] master: includes -> install-includes (ca25b1b) Message-ID: <20150123225647.536763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ca25b1ba1cedb6f9f94e5ecdc74c43712fe4abc4 >--------------------------------------------------------------- commit ca25b1ba1cedb6f9f94e5ecdc74c43712fe4abc4 Author: Ross Paterson Date: Tue Aug 29 05:37:45 2006 -0700 includes -> install-includes darcs-hash:20060829123745-b47d3-b412b445da8438997899714f0cd0d54c91e54595 >--------------------------------------------------------------- ca25b1ba1cedb6f9f94e5ecdc74c43712fe4abc4 time.cabal | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 672bd2a..1199bfd 100644 --- a/time.cabal +++ b/time.cabal @@ -43,4 +43,5 @@ Extra-Tmp-Files: config.log config.status autom4te.cache include/HsTimeConfig.h Include-Dirs: include -Includes: "HsTime.h" +Install-Includes: + HsTime.h HsTimeConfig.h From git at git.haskell.org Fri Jan 23 22:56:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:49 +0000 (UTC) Subject: [commit: packages/time] master: fix C-Sources (#893) (3b0c7d3) Message-ID: <20150123225649.5B2493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3b0c7d3c2f4953b9fa2d4d8ce14ae4ed2b1ab4b5 >--------------------------------------------------------------- commit 3b0c7d3c2f4953b9fa2d4d8ce14ae4ed2b1ab4b5 Author: Ross Paterson Date: Fri Sep 8 15:53:13 2006 -0700 fix C-Sources (#893) darcs-hash:20060908225313-b47d3-f3e63afec5f2173f6d7e535f6e6ee8a23094e725 >--------------------------------------------------------------- 3b0c7d3c2f4953b9fa2d4d8ce14ae4ed2b1ab4b5 time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 1199bfd..8500d1a 100644 --- a/time.cabal +++ b/time.cabal @@ -22,7 +22,7 @@ Exposed-Modules: Data.Time.LocalTime, Data.Time Extensions: ForeignFunctionInterface -C-Sources: HsTime.c +C-Sources: cbits/HsTime.c Other-Modules: Data.Time.Calendar.Private, Data.Time.Calendar.Days, From git at git.haskell.org Fri Jan 23 22:56:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:51 +0000 (UTC) Subject: [commit: packages/time] master: note CPP extension (0323c8c) Message-ID: <20150123225651.618383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/0323c8c75fc453d5945d177e4b17db8b7d032e73 >--------------------------------------------------------------- commit 0323c8c75fc453d5945d177e4b17db8b7d032e73 Author: Ross Paterson Date: Fri Sep 8 16:37:07 2006 -0700 note CPP extension darcs-hash:20060908233707-b47d3-78501ce27828a9dec451577e46d281e401b84277 >--------------------------------------------------------------- 0323c8c75fc453d5945d177e4b17db8b7d032e73 time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 8500d1a..8720db3 100644 --- a/time.cabal +++ b/time.cabal @@ -21,7 +21,7 @@ Exposed-Modules: Data.Time.Clock.TAI, Data.Time.LocalTime, Data.Time -Extensions: ForeignFunctionInterface +Extensions: ForeignFunctionInterface, CPP C-Sources: cbits/HsTime.c Other-Modules: Data.Time.Calendar.Private, From git at git.haskell.org Fri Jan 23 22:56:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:53 +0000 (UTC) Subject: [commit: packages/time] master: fix up XCode project file for added files (b50f0c7) Message-ID: <20150123225653.69A2A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b50f0c78a16e3380759283b559dfec92e8f3f923 >--------------------------------------------------------------- commit b50f0c78a16e3380759283b559dfec92e8f3f923 Author: Ashley Yakeley Date: Sun Sep 24 15:11:49 2006 -0700 fix up XCode project file for added files darcs-hash:20060924221149-ac6dd-19f372cb63d0e2d981aaec9f0dd4ff79ad98c26a >--------------------------------------------------------------- b50f0c78a16e3380759283b559dfec92e8f3f923 TimeLib.xcodeproj/project.pbxproj | 153 +++++--------------------------------- 1 file changed, 18 insertions(+), 135 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b50f0c78a16e3380759283b559dfec92e8f3f923 From git at git.haskell.org Fri Jan 23 22:56:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:55 +0000 (UTC) Subject: [commit: packages/time] master: add Setup.hs (de08f7e) Message-ID: <20150123225655.712DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/de08f7e6870ea40f58f77719e08ca6562084f141 >--------------------------------------------------------------- commit de08f7e6870ea40f58f77719e08ca6562084f141 Author: Ross Paterson Date: Thu Sep 28 05:43:41 2006 -0700 add Setup.hs darcs-hash:20060928124341-b47d3-60393a942de235747b1fd6da3d2368850b46b3e4 >--------------------------------------------------------------- de08f7e6870ea40f58f77719e08ca6562084f141 Makefile | 2 ++ Setup.hs | 6 ++++++ 2 files changed, 8 insertions(+) diff --git a/Makefile b/Makefile index 9c27f39..e2d286b 100644 --- a/Makefile +++ b/Makefile @@ -19,6 +19,8 @@ SRC_HC_OPTS += -Wall -Werror -fffi -Iinclude SRC_CC_OPTS += -Wall -Werror -Iinclude +EXCLUDED_SRCS += Setup.hs + SRC_HADDOCK_OPTS += -t "Haskell Hierarchical Libraries ($(PACKAGE) package)" UseGhcForCc = YES diff --git a/Setup.hs b/Setup.hs new file mode 100644 index 0000000..60804b2 --- /dev/null +++ b/Setup.hs @@ -0,0 +1,6 @@ +module Main (main) where + +import Distribution.Simple (defaultMainWithHooks, defaultUserHooks) + +main :: IO () +main = defaultMainWithHooks defaultUserHooks From git at git.haskell.org Fri Jan 23 22:56:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:57 +0000 (UTC) Subject: [commit: packages/time] master: Changed docs for %U and %W to include the possibility of week 0 results. (85fd256) Message-ID: <20150123225657.77BA03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/85fd2569144c8fc3d2249817dabf9944e32cba78 >--------------------------------------------------------------- commit 85fd2569144c8fc3d2249817dabf9944e32cba78 Author: bjorn Date: Sat Nov 11 08:52:07 2006 -0800 Changed docs for %U and %W to include the possibility of week 0 results. darcs-hash:20061111165207-6cdb2-9182b09f62f804176b0febb4a2169348d06655f3 >--------------------------------------------------------------- 85fd2569144c8fc3d2249817dabf9944e32cba78 Data/Time/LocalTime/Format.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index 9564868..d817c13 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -113,11 +113,11 @@ class FormatTime t where -- -- [@%A@] day of week, long form ('fst' from 'wDays' @locale@), @Sunday@ - @Saturday@ -- --- [@%U@] week number of year, where weeks start on Sunday (as 'sundayStartWeek'), @01@ - @53@ +-- [@%U@] week number of year, where weeks start on Sunday (as 'sundayStartWeek'), @00@ - @53@ -- -- [@%w@] day of week number, @0@ (= Sunday) - @6@ (= Saturday) -- --- [@%W@] week number of year, where weeks start on Monday (as 'mondayStartWeek'), @01@ - @53@ +-- [@%W@] week number of year, where weeks start on Monday (as 'mondayStartWeek'), @00@ - @53@ formatTime :: (FormatTime t) => TimeLocale -> String -> t -> String formatTime _ [] _ = "" formatTime locale ('%':c:cs) t = (formatChar c) ++ (formatTime locale cs t) where From git at git.haskell.org Fri Jan 23 22:56:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:56:59 +0000 (UTC) Subject: [commit: packages/time] master: Fixed typo: s/propleptic/proleptic/. (927eb34) Message-ID: <20150123225659.7F5C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/927eb3448f5bf93ca44cf636b2f390f9520e9277 >--------------------------------------------------------------- commit 927eb3448f5bf93ca44cf636b2f390f9520e9277 Author: bjorn Date: Sat Nov 11 08:55:49 2006 -0800 Fixed typo: s/propleptic/proleptic/. darcs-hash:20061111165549-6cdb2-2229da79c00c5415630eb6866533c290022c7ba0 >--------------------------------------------------------------- 927eb3448f5bf93ca44cf636b2f390f9520e9277 Data/Time/Calendar/JulianYearDay.hs | 2 +- Data/Time/Calendar/OrdinalDate.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/Data/Time/Calendar/JulianYearDay.hs b/Data/Time/Calendar/JulianYearDay.hs index a6d5baa..ba10c8f 100644 --- a/Data/Time/Calendar/JulianYearDay.hs +++ b/Data/Time/Calendar/JulianYearDay.hs @@ -33,6 +33,6 @@ showJulianYearAndDay :: Day -> String showJulianYearAndDay date = (show4 y) ++ "-" ++ (show3 d) where (y,d) = toJulianYearAndDay date --- | Is this year a leap year according to the propleptic Gregorian calendar? +-- | Is this year a leap year according to the proleptic Gregorian calendar? isJulianLeapYear :: Integer -> Bool isJulianLeapYear year = (mod year 4 == 0) diff --git a/Data/Time/Calendar/OrdinalDate.hs b/Data/Time/Calendar/OrdinalDate.hs index 7c2099a..a293b5e 100644 --- a/Data/Time/Calendar/OrdinalDate.hs +++ b/Data/Time/Calendar/OrdinalDate.hs @@ -33,7 +33,7 @@ showOrdinalDate :: Day -> String showOrdinalDate date = (show4 y) ++ "-" ++ (show3 d) where (y,d) = toOrdinalDate date --- | Is this year a leap year according to the propleptic Gregorian calendar? +-- | Is this year a leap year according to the proleptic Gregorian calendar? isLeapYear :: Integer -> Bool isLeapYear year = (mod year 4 == 0) && ((mod year 400 == 0) || not (mod year 100 == 0)) From git at git.haskell.org Fri Jan 23 22:57:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:01 +0000 (UTC) Subject: [commit: packages/time] master: Added missing example for showWeekDate. (147381b) Message-ID: <20150123225701.86BA03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/147381b33918537d64e9df200ed20ddac993d012 >--------------------------------------------------------------- commit 147381b33918537d64e9df200ed20ddac993d012 Author: bjorn Date: Wed Nov 15 14:07:39 2006 -0800 Added missing example for showWeekDate. The showWeekDate haddock comment was: "show in ISO 8601 Week Date format as yyyy-Www-dd (e.g." darcs-hash:20061115220739-6cdb2-5f577de58f061136b82cffa9c22c73b2e914bbed >--------------------------------------------------------------- 147381b33918537d64e9df200ed20ddac993d012 Data/Time/Calendar/WeekDate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Time/Calendar/WeekDate.hs b/Data/Time/Calendar/WeekDate.hs index a186ca9..0568a32 100644 --- a/Data/Time/Calendar/WeekDate.hs +++ b/Data/Time/Calendar/WeekDate.hs @@ -35,7 +35,7 @@ fromWeekDate y w d = ModifiedJulianDay (k - (mod k 7) + (toInteger (((clip 1 (if (_,53,_) -> True _ -> False --- | show in ISO 8601 Week Date format as yyyy-Www-dd (e.g. +-- | show in ISO 8601 Week Date format as yyyy-Www-dd (e.g. \"2006-W46-3\"). showWeekDate :: Day -> String showWeekDate date = (show4 y) ++ "-W" ++ (show2 w) ++ "-" ++ (show d) where (y,w,d) = toWeekDate date From git at git.haskell.org Fri Jan 23 22:57:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:03 +0000 (UTC) Subject: [commit: packages/time] master: Handle 'c' also in formatTime for ZonedTime, to get %Z filled in for ZonedTime and UTCTime. (573daed) Message-ID: <20150123225703.8D3C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/573daed43a143ea75360c23317ec9efebe01dfe5 >--------------------------------------------------------------- commit 573daed43a143ea75360c23317ec9efebe01dfe5 Author: bjorn Date: Wed Nov 15 14:08:18 2006 -0800 Handle 'c' also in formatTime for ZonedTime, to get %Z filled in for ZonedTime and UTCTime. Before, formatTime "%c" did not include the time zone even when applied to ZonedTime or UTCTime, since "%c" was handled by the FormatTime LocalTime instance: > fmap (formatTime System.Locale.defaultTimeLocale "%c") getZonedTime "Sat Nov 11 19:12:45.395568 2006" > fmap (formatTime System.Locale.defaultTimeLocale "%c") getCurrentTime "Sat Nov 11 18:13:52.010944 2006" Now it is correct: > fmap (formatTime System.Locale.defaultTimeLocale "%c") getZonedTime "Wed Nov 15 23:08:43.987526 CET 2006" > fmap (formatTime System.Locale.defaultTimeLocale "%c") getCurrentTime "Wed Nov 15 22:08:51.530603 UTC 2006" darcs-hash:20061115220818-6cdb2-db20654b473141486d86a09551688043eebafb8b >--------------------------------------------------------------- 573daed43a143ea75360c23317ec9efebe01dfe5 Data/Time/LocalTime/Format.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index d817c13..c13160e 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -160,6 +160,7 @@ instance FormatTime TimeOfDay where formatCharacter _ = Nothing instance FormatTime ZonedTime where + formatCharacter 'c' = Just (\locale -> formatTime locale (dateTimeFmt locale)) formatCharacter 's' = Just (\_ zt -> show (truncate (utcTimeToPOSIXSeconds (zonedTimeToUTC zt)) :: Integer)) formatCharacter c = case (formatCharacter c) of Just f -> Just (\locale dt -> f locale (zonedTimeToLocalTime dt)) From git at git.haskell.org Fri Jan 23 22:57:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:05 +0000 (UTC) Subject: [commit: packages/time] master: Add secondsToDiffTime and picosecondsToDiffTime. (96ec994) Message-ID: <20150123225705.938643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/96ec99479c89cac13ac310b0b85536e6973c2af1 >--------------------------------------------------------------- commit 96ec99479c89cac13ac310b0b85536e6973c2af1 Author: bjorn Date: Wed Nov 15 14:21:45 2006 -0800 Add secondsToDiffTime and picosecondsToDiffTime. Rationale: As has come up on haskell-cafe (http://comments.gmane.org/gmane.comp.lang.haskell.cafe/15653), it takes a while to figure out how to make DiffTime values. secondsToDiffTime is not that important since it is just another name for fromInteger, but I suspect that it would be used a lot. Using fromRational to create a DiffTime from a number of picoseconds is a bit of a hassle, so having a picosecondsToDiffTime would be useful. darcs-hash:20061115222145-6cdb2-4c0badc67fc5a5c1880c111902ee3e28ad793719 >--------------------------------------------------------------- 96ec99479c89cac13ac310b0b85536e6973c2af1 Data/Time/Clock/Scale.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs index b7bcf97..053c515 100644 --- a/Data/Time/Clock/Scale.hs +++ b/Data/Time/Clock/Scale.hs @@ -8,9 +8,11 @@ module Data.Time.Clock.Scale UniversalTime(..), -- * Absolute intervals - DiffTime + DiffTime, + secondsToDiffTime, picosecondsToDiffTime ) where +import Data.Ratio ((%)) import Data.Fixed -- | The Modified Julian Date is the day with the fraction of the day, measured from UT midnight. @@ -55,3 +57,11 @@ instance Fractional DiffTime where (MkDiffTime a) / (MkDiffTime b) = MkDiffTime (a / b) recip (MkDiffTime a) = MkDiffTime (recip a) fromRational r = MkDiffTime (fromRational r) + +-- | Create a 'DiffTime' which represents an integral number of seconds. +secondsToDiffTime :: Integer -> DiffTime +secondsToDiffTime = fromInteger + +-- | Create a 'DiffTime' from a number of picoseconds. +picosecondsToDiffTime :: Integer -> DiffTime +picosecondsToDiffTime x = fromRational (x % 1000000000000) From git at git.haskell.org Fri Jan 23 22:57:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:07 +0000 (UTC) Subject: [commit: packages/time] master: Added fromMondayStartWeek and fromSundayStartWeek to Data.Time.Calendar.OrdinalDate. (04282fe) Message-ID: <20150123225707.99D553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/04282fedbfbc79af60e7b430457f72789917da9d >--------------------------------------------------------------- commit 04282fedbfbc79af60e7b430457f72789917da9d Author: bjorn Date: Thu Nov 16 01:21:14 2006 -0800 Added fromMondayStartWeek and fromSundayStartWeek to Data.Time.Calendar.OrdinalDate. I couldn't find any duals of mondayStartWeek and sundayStartWeek. They are useful when implementing parsing for %W and %U. darcs-hash:20061116092114-6cdb2-794a278759d65b1cdbb8fbb8f890409edbaa3834 >--------------------------------------------------------------- 04282fedbfbc79af60e7b430457f72789917da9d Data/Time/Calendar/OrdinalDate.hs | 33 +++++++++++++++++++++++++++++++++ 1 file changed, 33 insertions(+) diff --git a/Data/Time/Calendar/OrdinalDate.hs b/Data/Time/Calendar/OrdinalDate.hs index a293b5e..a88943f 100644 --- a/Data/Time/Calendar/OrdinalDate.hs +++ b/Data/Time/Calendar/OrdinalDate.hs @@ -54,3 +54,36 @@ sundayStartWeek date =(fromInteger ((div d 7) - (div k 7)),fromInteger (mod d 7) yd = snd (toOrdinalDate date) d = (toModifiedJulianDay date) + 3 k = d - (toInteger yd) + +-- | The inverse of 'mondayStartWeek'. Get a 'Day' given the year, +-- the number of the Monday-starting week, and the day of the week. +-- The first Monday is the first day of week 1, any earlier days in the year +-- are week 0 (as \"%W\" in formatTime). +fromMondayStartWeek :: Integer -- ^ Year. + -> Int -- ^ Monday-starting week number. + -> Int -- ^ Day of week. + -- Monday is 1, Sunday is 7 (as \"%u\" in formatTime). + -> Day +fromMondayStartWeek y w d = ModifiedJulianDay (firstDay + yd) + where yd = firstMonday + 7 * toInteger (w-1) + toInteger d - 1 + -- first day of the year + firstDay = toModifiedJulianDay (fromOrdinalDate y 1) + -- 0-based year day of first monday of the year + firstMonday = (5 - firstDay) `mod` 7 + +-- | The inverse of 'sundayStartWeek'. Get a 'Day' given the year and +-- the number of the day of a Sunday-starting week. +-- The first Sunday is the first day of week 1, any earlier days in the +-- year are week 0 (as \"%U\" in formatTime). +-- Sunday is 0, Saturday is 6 (as \"%w\" in formatTime). +fromSundayStartWeek :: Integer -- ^ Year. + -> Int -- ^ Sunday-starting week number. + -> Int -- ^ Day of week + -- Sunday is 0, Saturday is 6 (as \"%w\" in formatTime). + -> Day +fromSundayStartWeek y w d = ModifiedJulianDay (firstDay + yd) + where yd = firstSunday + 7 * toInteger (w-1) + toInteger d + -- first day of the year + firstDay = toModifiedJulianDay (fromOrdinalDate y 1) + -- 0-based year day of first sunday of the year + firstSunday = (4 - firstDay) `mod` 7 From git at git.haskell.org Fri Jan 23 22:57:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:09 +0000 (UTC) Subject: [commit: packages/time] master: Some haddock formatting for fromMondayStartWeek and fromSundayStartWeek. (c2bc34a) Message-ID: <20150123225709.A0B013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c2bc34a0e99761e5c16f3217d4b1bc67c6303dc2 >--------------------------------------------------------------- commit c2bc34a0e99761e5c16f3217d4b1bc67c6303dc2 Author: bjorn Date: Thu Nov 16 01:56:20 2006 -0800 Some haddock formatting for fromMondayStartWeek and fromSundayStartWeek. darcs-hash:20061116095620-6cdb2-0add550bd79d80a7f1ddd794a050d72c25226e63 >--------------------------------------------------------------- c2bc34a0e99761e5c16f3217d4b1bc67c6303dc2 Data/Time/Calendar/OrdinalDate.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/Data/Time/Calendar/OrdinalDate.hs b/Data/Time/Calendar/OrdinalDate.hs index a88943f..dfd4069 100644 --- a/Data/Time/Calendar/OrdinalDate.hs +++ b/Data/Time/Calendar/OrdinalDate.hs @@ -58,11 +58,11 @@ sundayStartWeek date =(fromInteger ((div d 7) - (div k 7)),fromInteger (mod d 7) -- | The inverse of 'mondayStartWeek'. Get a 'Day' given the year, -- the number of the Monday-starting week, and the day of the week. -- The first Monday is the first day of week 1, any earlier days in the year --- are week 0 (as \"%W\" in formatTime). +-- are week 0 (as \"%W\" in 'formatTime'). fromMondayStartWeek :: Integer -- ^ Year. -> Int -- ^ Monday-starting week number. -> Int -- ^ Day of week. - -- Monday is 1, Sunday is 7 (as \"%u\" in formatTime). + -- Monday is 1, Sunday is 7 (as \"%u\" in 'formatTime'). -> Day fromMondayStartWeek y w d = ModifiedJulianDay (firstDay + yd) where yd = firstMonday + 7 * toInteger (w-1) + toInteger d - 1 @@ -74,12 +74,11 @@ fromMondayStartWeek y w d = ModifiedJulianDay (firstDay + yd) -- | The inverse of 'sundayStartWeek'. Get a 'Day' given the year and -- the number of the day of a Sunday-starting week. -- The first Sunday is the first day of week 1, any earlier days in the --- year are week 0 (as \"%U\" in formatTime). --- Sunday is 0, Saturday is 6 (as \"%w\" in formatTime). +-- year are week 0 (as \"%U\" in 'formatTime'). fromSundayStartWeek :: Integer -- ^ Year. -> Int -- ^ Sunday-starting week number. -> Int -- ^ Day of week - -- Sunday is 0, Saturday is 6 (as \"%w\" in formatTime). + -- Sunday is 0, Saturday is 6 (as \"%w\" in 'formatTime'). -> Day fromSundayStartWeek y w d = ModifiedJulianDay (firstDay + yd) where yd = firstSunday + 7 * toInteger (w-1) + toInteger d From git at git.haskell.org Fri Jan 23 22:57:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:11 +0000 (UTC) Subject: [commit: packages/time] master: Added Data.Time.LocalTime.Parse, UNIX-style time parsing. (06ad028) Message-ID: <20150123225711.A9FEE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/06ad028f0ddff11a63871b119393b9cc0ee30cd3 >--------------------------------------------------------------- commit 06ad028f0ddff11a63871b119393b9cc0ee30cd3 Author: bjorn Date: Thu Nov 16 01:58:49 2006 -0800 Added Data.Time.LocalTime.Parse, UNIX-style time parsing. The old System.Time has had a TODO "* add functions to parse strings to `CalendarTime' (some day...)" for a long time. The question about date parsing comes up once in a while on the mailing lists (e.g. http://comments.gmane.org/gmane.comp.lang.haskell.cafe/16438). darcs-hash:20061116095849-6cdb2-fef2cd50b6017d49ede023864ae4a2f56f9584a8 >--------------------------------------------------------------- 06ad028f0ddff11a63871b119393b9cc0ee30cd3 Data/Time/LocalTime.hs | 4 +- Data/Time/LocalTime/Parse.hs | 310 +++++++++++++++++++++++++++++++++++++++++++ time.cabal | 3 +- 3 files changed, 315 insertions(+), 2 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 06ad028f0ddff11a63871b119393b9cc0ee30cd3 From git at git.haskell.org Fri Jan 23 22:57:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:13 +0000 (UTC) Subject: [commit: packages/time] master: Updated SRC and dependencies in time/Makefile to include Data.Time.LocalTime.Parse. (d6ff855) Message-ID: <20150123225713.B13553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/d6ff855adbb921cd61cdf46ffa2781c4c6466618 >--------------------------------------------------------------- commit d6ff855adbb921cd61cdf46ffa2781c4c6466618 Author: bjorn Date: Thu Nov 16 02:44:38 2006 -0800 Updated SRC and dependencies in time/Makefile to include Data.Time.LocalTime.Parse. darcs-hash:20061116104438-6cdb2-7dad989c3cb1ccaadefe38b7f03a40a0a219ad8d >--------------------------------------------------------------- d6ff855adbb921cd61cdf46ffa2781c4c6466618 time/Makefile | 26 +++++++++++++++++++------- 1 file changed, 19 insertions(+), 7 deletions(-) diff --git a/time/Makefile b/time/Makefile index 9ca9a17..f99d908 100644 --- a/time/Makefile +++ b/time/Makefile @@ -42,6 +42,7 @@ SRCS = \ Data/Time/LocalTime/TimeOfDay.hs \ Data/Time/LocalTime/LocalTime.hs \ Data/Time/LocalTime/Format.hs \ + Data/Time/LocalTime/Parse.hs \ Data/Time/LocalTime.hs \ Data/Time.hs @@ -121,19 +122,13 @@ Data/Time/Calendar/Julian.o : Data/Time/Calendar/Private.hi Data/Time/Calendar/Julian.o : Data/Time/Calendar/Days.hi Data/Time/Calendar/Julian.o : Data/Time/Calendar/JulianYearDay.hi Data/Time/Calendar/Julian.o : Data/Time/Calendar/MonthDay.hi -Data/Time/Calendar.o : Data/Time/Calendar.hs -Data/Time/Calendar.o : Data/Time/Calendar/Gregorian.hi -Data/Time/Calendar.o : Data/Time/Calendar/Days.hi -Data/Time/Calendar/Easter.o : Data/Time/Calendar/Easter.hs -Data/Time/Calendar/Easter.o : Data/Time/Calendar/Julian.hi -Data/Time/Calendar/Easter.o : Data/Time/Calendar.hi Data/Time/Clock/UTC.o : Data/Time/Clock/UTC.hs Data/Time/Clock/UTC.o : Data/Time/Clock/Scale.hi Data/Time/Clock/UTC.o : Data/Time/Calendar/Days.hi Data/Time/Clock/POSIX.o : Data/Time/Clock/POSIX.hs +Data/Time/Clock/POSIX.o : Data/Time/Clock/CTimeval.hi Data/Time/Clock/POSIX.o : Data/Time/Calendar/Days.hi Data/Time/Clock/POSIX.o : Data/Time/Clock/UTC.hi -Data/Time/Clock/POSIX.o : Data/Time/Clock/CTimeval.hi Data/Time/Clock/UTCDiff.o : Data/Time/Clock/UTCDiff.hs Data/Time/Clock/UTCDiff.o : Data/Time/Clock/UTC.hi Data/Time/Clock/UTCDiff.o : Data/Time/Clock/POSIX.hi @@ -150,11 +145,27 @@ Data/Time/LocalTime/TimeOfDay.o : Data/Time/LocalTime/TimeOfDay.hs Data/Time/LocalTime/TimeOfDay.o : Data/Time/Clock.hi Data/Time/LocalTime/TimeOfDay.o : Data/Time/Calendar/Private.hi Data/Time/LocalTime/TimeOfDay.o : Data/Time/LocalTime/TimeZone.hi +Data/Time/Calendar.o : Data/Time/Calendar.hs +Data/Time/Calendar.o : Data/Time/Calendar/Gregorian.hi +Data/Time/Calendar.o : Data/Time/Calendar/Days.hi +Data/Time/Calendar/Easter.o : Data/Time/Calendar/Easter.hs +Data/Time/Calendar/Easter.o : Data/Time/Calendar/Julian.hi +Data/Time/Calendar/Easter.o : Data/Time/Calendar.hi Data/Time/LocalTime/LocalTime.o : Data/Time/LocalTime/LocalTime.hs Data/Time/LocalTime/LocalTime.o : Data/Time/Clock.hi Data/Time/LocalTime/LocalTime.o : Data/Time/Calendar.hi Data/Time/LocalTime/LocalTime.o : Data/Time/LocalTime/TimeZone.hi Data/Time/LocalTime/LocalTime.o : Data/Time/LocalTime/TimeOfDay.hi +Data/Time/LocalTime/Parse.o : Data/Time/LocalTime/Parse.hs +Data/Time/LocalTime/Parse.o : Data/Time/LocalTime/TimeZone.hi +Data/Time/LocalTime/Parse.o : Data/Time/LocalTime/TimeOfDay.hi +Data/Time/LocalTime/Parse.o : Data/Time/LocalTime/LocalTime.hi +Data/Time/LocalTime/Parse.o : Data/Time/Calendar/WeekDate.hi +Data/Time/LocalTime/Parse.o : Data/Time/Calendar/OrdinalDate.hi +Data/Time/LocalTime/Parse.o : Data/Time/Calendar/Gregorian.hi +Data/Time/LocalTime/Parse.o : Data/Time/Calendar/Days.hi +Data/Time/LocalTime/Parse.o : Data/Time/Clock/UTC.hi +Data/Time/LocalTime/Parse.o : Data/Time/Clock/POSIX.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/Format.hs Data/Time/LocalTime/Format.o : Data/Time/Clock/POSIX.hi Data/Time/LocalTime/Format.o : Data/Time/Clock.hi @@ -166,6 +177,7 @@ Data/Time/LocalTime/Format.o : Data/Time/LocalTime/TimeZone.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/TimeOfDay.hi Data/Time/LocalTime/Format.o : Data/Time/LocalTime/LocalTime.hi Data/Time/LocalTime.o : Data/Time/LocalTime.hs +Data/Time/LocalTime.o : Data/Time/LocalTime/Parse.hi Data/Time/LocalTime.o : Data/Time/LocalTime/Format.hi Data/Time/LocalTime.o : Data/Time/LocalTime/LocalTime.hi Data/Time/LocalTime.o : Data/Time/LocalTime/TimeOfDay.hi From git at git.haskell.org Fri Jan 23 22:57:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:15 +0000 (UTC) Subject: [commit: packages/time] master: Changed UTC to +0000 in default time zone in ParseTime, to avoid spurios time zone names. (16a9225) Message-ID: <20150123225715.BA9263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/16a92252a19297d9e1ec75a7b292a880f57b9587 >--------------------------------------------------------------- commit 16a92252a19297d9e1ec75a7b292a880f57b9587 Author: bjorn Date: Thu Nov 16 02:52:54 2006 -0800 Changed UTC to +0000 in default time zone in ParseTime, to avoid spurios time zone names. darcs-hash:20061116105254-6cdb2-3328529fc7d8536b6e9009295768fdc2eae7e25a >--------------------------------------------------------------- 16a92252a19297d9e1ec75a7b292a880f57b9587 Data/Time/LocalTime/Parse.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Data/Time/LocalTime/Parse.hs b/Data/Time/LocalTime/Parse.hs index b3c42c7..a5420d3 100644 --- a/Data/Time/LocalTime/Parse.hs +++ b/Data/Time/LocalTime/Parse.hs @@ -33,7 +33,7 @@ class ParseTime t where -- | Builds a time value from a parsed input string. -- If the input does not include all the information needed to -- construct a complete value, any missing parts should be taken - -- from 1970-01-01 00:00:00 UTC (which was a Thursday). + -- from 1970-01-01 00:00:00 +0000 (which was a Thursday). buildTime :: TimeLocale -- ^ The time locale. -> [(Char,String)] -- ^ Pairs of format characters and the -- corresponding part of the input. @@ -263,7 +263,7 @@ instance ParseTime LocalTime where buildTime l xs = LocalTime (buildTime l xs) (buildTime l xs) instance ParseTime TimeZone where - buildTime _ = foldl f utc + buildTime _ = foldl f (minutesToTimeZone 0) where f t@(TimeZone offset dst name) (c,x) = case c of From git at git.haskell.org Fri Jan 23 22:57:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:17 +0000 (UTC) Subject: [commit: packages/time] master: Added quickcheck properties for time parsing. (ad26aa5) Message-ID: <20150123225717.C45723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ad26aa5cf47d8c573dd0b6333da5e065843f37af >--------------------------------------------------------------- commit ad26aa5cf47d8c573dd0b6333da5e065843f37af Author: bjorn Date: Thu Nov 16 02:56:16 2006 -0800 Added quickcheck properties for time parsing. darcs-hash:20061116105616-6cdb2-eed6a7e86410241c74b0b43e4e2d8c4a45096ba7 >--------------------------------------------------------------- ad26aa5cf47d8c573dd0b6333da5e065843f37af time/test/Makefile | 6 +- time/test/TestParseTime.hs | 290 +++++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 295 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ad26aa5cf47d8c573dd0b6333da5e065843f37af From git at git.haskell.org Fri Jan 23 22:57:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:19 +0000 (UTC) Subject: [commit: packages/time] master: Moved %c to failing ZonedTime test since formatTime %Z does not output time zone offset if there is no time zone name. (bef9a3c) Message-ID: <20150123225719.CAE823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/bef9a3cf6f39980706483a8e14013890a9c54d80 >--------------------------------------------------------------- commit bef9a3cf6f39980706483a8e14013890a9c54d80 Author: bjorn Date: Thu Nov 16 03:12:47 2006 -0800 Moved %c to failing ZonedTime test since formatTime %Z does not output time zone offset if there is no time zone name. darcs-hash:20061116111247-6cdb2-509d4a19b5225b95dc0343a983099569d2f90fad >--------------------------------------------------------------- bef9a3cf6f39980706483a8e14013890a9c54d80 time/test/TestParseTime.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/time/test/TestParseTime.hs b/time/test/TestParseTime.hs index 356f2fb..91d76b0 100644 --- a/time/test/TestParseTime.hs +++ b/time/test/TestParseTime.hs @@ -237,7 +237,7 @@ timeZoneFormats = map FormatString ["%z","%z%Z","%Z%z"] zonedTimeFormats :: [FormatString ZonedTime] zonedTimeFormats = map FormatString - ["%a, %d %b %Y %H:%M:%S %z","%c"] + ["%a, %d %b %Y %H:%M:%S %z"] utcTimeFormats :: [FormatString UTCTime] utcTimeFormats = map FormatString @@ -275,7 +275,8 @@ failingTimeZoneFormats = map FormatString failingZonedTimeFormats :: [FormatString ZonedTime] failingZonedTimeFormats = map FormatString [ - -- %Z is not implemented properly + -- can't figure out offset from %Z, also, formatTime produces "" for %Z + "%c", "%a, %d %b %Y %H:%M:%S %Z", -- %s does not include second decimals "%s %z" From git at git.haskell.org Fri Jan 23 22:57:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:21 +0000 (UTC) Subject: [commit: packages/time] master: Changed test case Makefile to work with GHC 6.6 (there is no -package fixed). (eba81c2) Message-ID: <20150123225721.D25883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/eba81c2d010185d361181c3132f6de9165037b43 >--------------------------------------------------------------- commit eba81c2d010185d361181c3132f6de9165037b43 Author: bjorn Date: Thu Nov 16 03:13:46 2006 -0800 Changed test case Makefile to work with GHC 6.6 (there is no -package fixed). darcs-hash:20061116111346-6cdb2-7ced2b2124315f6bf4545d0617ec10bd50bd6896 >--------------------------------------------------------------- eba81c2d010185d361181c3132f6de9165037b43 time/test/LongWeekYears.hs | 1 - time/test/Makefile | 32 ++++++++++++++++++-------------- 2 files changed, 18 insertions(+), 15 deletions(-) diff --git a/time/test/LongWeekYears.hs b/time/test/LongWeekYears.hs index b5c3913..db453be 100644 --- a/time/test/LongWeekYears.hs +++ b/time/test/LongWeekYears.hs @@ -2,7 +2,6 @@ module Main where -import Data.Time.Calendar.OrdinalDate import Data.Time.Calendar.WeekDate import Data.Time.Calendar diff --git a/time/test/Makefile b/time/test/Makefile index cb4c2ea..9df2b39 100644 --- a/time/test/Makefile +++ b/time/test/Makefile @@ -1,52 +1,55 @@ +GHC = ghc +GHCFLAGS = + default: CurrentTime.run ShowDST.run test TestMonthDay: TestMonthDay.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ ConvertBack: ConvertBack.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ TestCalendars: TestCalendars.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ TestTime: TestTime.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ LongWeekYears: LongWeekYears.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ ClipDates: ClipDates.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ AddDays: AddDays.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ TestFormat: TestFormat.o TestFormatStuff.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ TestFormatStuff.o: TestFormatStuff.c TestFormatStuff.h gcc -o $@ -c $< TestParseDAT: TestParseDAT.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ TestEaster: TestEaster.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ CurrentTime: CurrentTime.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ ShowDST: ShowDST.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ TimeZone: TimeZone.o ../libHStime.a - ghc -package fixed $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ TimeZone.ref: FORCE date +%z > $@ TestParseTime: TestParseTime.o ../libHStime.a - ghc -package fixed -package QuickCheck $^ -o $@ + $(GHC) $(GHCFLAGS) -package QuickCheck $^ -o $@ test: \ TestMonthDay.diff \ @@ -60,6 +63,7 @@ test: \ TestFormat.diff0 \ TestParseDAT.diff \ TestEaster.diff \ + TestParseTime.run \ UseCases.o clean: From git at git.haskell.org Fri Jan 23 22:57:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:23 +0000 (UTC) Subject: [commit: packages/time] master: Compile test programs using ../../dist/build/libHStime-1.0.a as produced by the Cabal build step. (43d95b2) Message-ID: <20150123225723.D91573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/43d95b2e3a860661e66bed2e606b7675178eb22f >--------------------------------------------------------------- commit 43d95b2e3a860661e66bed2e606b7675178eb22f Author: bjorn Date: Thu Nov 16 03:20:48 2006 -0800 Compile test programs using ../../dist/build/libHStime-1.0.a as produced by the Cabal build step. darcs-hash:20061116112048-6cdb2-c592217ab26ead8026d074c6d410f0d10265e0c0 >--------------------------------------------------------------- 43d95b2e3a860661e66bed2e606b7675178eb22f time/test/Makefile | 29 +++++++++++++++-------------- 1 file changed, 15 insertions(+), 14 deletions(-) diff --git a/time/test/Makefile b/time/test/Makefile index 9df2b39..c3f2992 100644 --- a/time/test/Makefile +++ b/time/test/Makefile @@ -1,54 +1,55 @@ GHC = ghc GHCFLAGS = +LIBS = ../../dist/build/libHStime-1.0.a default: CurrentTime.run ShowDST.run test -TestMonthDay: TestMonthDay.o ../libHStime.a +TestMonthDay: TestMonthDay.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -ConvertBack: ConvertBack.o ../libHStime.a +ConvertBack: ConvertBack.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -TestCalendars: TestCalendars.o ../libHStime.a +TestCalendars: TestCalendars.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -TestTime: TestTime.o ../libHStime.a +TestTime: TestTime.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -LongWeekYears: LongWeekYears.o ../libHStime.a +LongWeekYears: LongWeekYears.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -ClipDates: ClipDates.o ../libHStime.a +ClipDates: ClipDates.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -AddDays: AddDays.o ../libHStime.a +AddDays: AddDays.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -TestFormat: TestFormat.o TestFormatStuff.o ../libHStime.a +TestFormat: TestFormat.o TestFormatStuff.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ TestFormatStuff.o: TestFormatStuff.c TestFormatStuff.h gcc -o $@ -c $< -TestParseDAT: TestParseDAT.o ../libHStime.a +TestParseDAT: TestParseDAT.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -TestEaster: TestEaster.o ../libHStime.a +TestEaster: TestEaster.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -CurrentTime: CurrentTime.o ../libHStime.a +CurrentTime: CurrentTime.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -ShowDST: ShowDST.o ../libHStime.a +ShowDST: ShowDST.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ -TimeZone: TimeZone.o ../libHStime.a +TimeZone: TimeZone.o $(LIBS) $(GHC) $(GHCFLAGS) $^ -o $@ TimeZone.ref: FORCE date +%z > $@ -TestParseTime: TestParseTime.o ../libHStime.a +TestParseTime: TestParseTime.o $(LIBS) $(GHC) $(GHCFLAGS) -package QuickCheck $^ -o $@ test: \ From git at git.haskell.org Fri Jan 23 22:57:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:25 +0000 (UTC) Subject: [commit: packages/time] master: Fixed taiEpoch Haddock comment to include the epoch time. (1632436) Message-ID: <20150123225725.DF8113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/16324364771a9c323bed81d8eba20083576c9a4a >--------------------------------------------------------------- commit 16324364771a9c323bed81d8eba20083576c9a4a Author: bjorn Date: Thu Nov 16 04:00:24 2006 -0800 Fixed taiEpoch Haddock comment to include the epoch time. The taiEpoch haddock comment was just "The epoch of TAI, which is". Changed this to "The epoch of TAI, which is 1858-11-17 00:00:00 TAI." darcs-hash:20061116120024-6cdb2-fe77f9d9bd5336bbd91bee5afcb055f3a6796965 >--------------------------------------------------------------- 16324364771a9c323bed81d8eba20083576c9a4a Data/Time/Clock/TAI.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Time/Clock/TAI.hs b/Data/Time/Clock/TAI.hs index 00cebd5..b1c37c1 100644 --- a/Data/Time/Clock/TAI.hs +++ b/Data/Time/Clock/TAI.hs @@ -26,7 +26,7 @@ newtype AbsoluteTime = MkAbsoluteTime {unAbsoluteTime :: DiffTime} deriving (Eq, instance Show AbsoluteTime where show t = show (utcToLocalTime utc (taiToUTCTime (const 0) t)) ++ " TAI" -- ugly, but standard apparently --- | The epoch of TAI, which is +-- | The epoch of TAI, which is 1858-11-17 00:00:00 TAI. taiEpoch :: AbsoluteTime taiEpoch = MkAbsoluteTime 0 From git at git.haskell.org Fri Jan 23 22:57:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:27 +0000 (UTC) Subject: [commit: packages/time] master: move test dir up, remove old junk (9b6744e) Message-ID: <20150123225727.E804A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/9b6744e0fb08826431d844e6f3e0e1f57544f8cf >--------------------------------------------------------------- commit 9b6744e0fb08826431d844e6f3e0e1f57544f8cf Author: Ashley Yakeley Date: Mon Dec 11 00:00:45 2006 -0800 move test dir up, remove old junk darcs-hash:20061211080045-ac6dd-ce8452ab86b8c8efdfb9d6697df9c32aad49d87d >--------------------------------------------------------------- 9b6744e0fb08826431d844e6f3e0e1f57544f8cf {time/test => test}/AddDays.hs | 0 {time/test => test}/AddDays.ref | 0 {time/test => test}/ClipDates.hs | 0 {time/test => test}/ClipDates.ref | 0 {time/test => test}/ConvertBack.hs | 0 {time/test => test}/CurrentTime.hs | 0 {time/test => test}/LongWeekYears.hs | 0 {time/test => test}/LongWeekYears.ref | 0 {time/test => test}/Makefile | 0 {time/test => test}/ShowDST.hs | 0 {time/test => test}/TestCalendars.hs | 0 {time/test => test}/TestCalendars.ref | 0 {time/test => test}/TestEaster.hs | 0 {time/test => test}/TestEaster.ref | 0 {time/test => test}/TestFormat.hs | 0 {time/test => test}/TestFormatStuff.c | 0 {time/test => test}/TestFormatStuff.h | 0 {time/test => test}/TestMonthDay.hs | 0 {time/test => test}/TestMonthDay.ref | 0 {time/test => test}/TestParseDAT.hs | 0 {time/test => test}/TestParseDAT.ref | 0 {time/test => test}/TestParseTime.hs | 0 {time/test => test}/TestTime.hs | 0 {time/test => test}/TestTime.ref | 0 {time/test => test}/TimeZone.hs | 0 {time/test => test}/UseCases.lhs | 0 {time/test => test}/tai-utc.dat | 0 time/Makefile | 193 ---------------------------------- 28 files changed, 193 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9b6744e0fb08826431d844e6f3e0e1f57544f8cf From git at git.haskell.org Fri Jan 23 22:57:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:29 +0000 (UTC) Subject: [commit: packages/time] master: HsTime.h should be installed (acf02ec) Message-ID: <20150123225729.EF72F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/acf02ece782ad06eed2bf8980e2c24e65d6dca3b >--------------------------------------------------------------- commit acf02ece782ad06eed2bf8980e2c24e65d6dca3b Author: mukai Date: Wed Dec 13 07:13:46 2006 -0800 HsTime.h should be installed darcs-hash:20061213151346-f0081-bc57b7801c511854b6e762e4db78a5e68ff109b7 >--------------------------------------------------------------- acf02ece782ad06eed2bf8980e2c24e65d6dca3b Makefile | 2 +- include/Makefile | 11 +++++++++++ 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/Makefile b/Makefile index e2d286b..76ea560 100644 --- a/Makefile +++ b/Makefile @@ -1,7 +1,7 @@ TOP=.. include $(TOP)/mk/boilerplate.mk -SUBDIRS = +SUBDIRS = include ALL_DIRS = \ cbits \ diff --git a/include/Makefile b/include/Makefile new file mode 100644 index 0000000..748523c --- /dev/null +++ b/include/Makefile @@ -0,0 +1,11 @@ +TOP=../.. +include $(TOP)/mk/boilerplate.mk + +H_FILES = $(wildcard *.h) + +includedir = $(libdir)/include +INSTALL_INCLUDES = $(H_FILES) + +DIST_CLEAN_FILES += HsTimeConfig.h + +include $(TOP)/mk/target.mk From git at git.haskell.org Fri Jan 23 22:57:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:32 +0000 (UTC) Subject: [commit: packages/time] master: clean up .xcodeproj to use cabal (5892926) Message-ID: <20150123225732.0633E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/58929269a10f917192c37231dade58935dded69b >--------------------------------------------------------------- commit 58929269a10f917192c37231dade58935dded69b Author: Ashley Yakeley Date: Tue Dec 19 21:05:38 2006 -0800 clean up .xcodeproj to use cabal darcs-hash:20061220050538-ac6dd-e79ba99f9d60002b3298c351f73744dd7fc8eafd >--------------------------------------------------------------- 58929269a10f917192c37231dade58935dded69b time.xcodeproj/cabalbuild | 5 + .../project.pbxproj | 180 +++++---------------- 2 files changed, 42 insertions(+), 143 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 58929269a10f917192c37231dade58935dded69b From git at git.haskell.org Fri Jan 23 22:57:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:34 +0000 (UTC) Subject: [commit: packages/time] master: improve error reporting in XCode (a4b8812) Message-ID: <20150123225734.0D2B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/a4b8812aa30291185aca449117d2bc8141985121 >--------------------------------------------------------------- commit a4b8812aa30291185aca449117d2bc8141985121 Author: Ashley Yakeley Date: Tue Dec 19 22:49:48 2006 -0800 improve error reporting in XCode darcs-hash:20061220064948-ac6dd-e6e4ca06bf1e0a7d15ca9d825a42a6b34775cefc >--------------------------------------------------------------- a4b8812aa30291185aca449117d2bc8141985121 time.xcodeproj/cabalbuild | 5 ++++- time.xcodeproj/fixerrormsgs | 10 ++++++++++ 2 files changed, 14 insertions(+), 1 deletion(-) diff --git a/time.xcodeproj/cabalbuild b/time.xcodeproj/cabalbuild index 6b4a2d1..2462967 100755 --- a/time.xcodeproj/cabalbuild +++ b/time.xcodeproj/cabalbuild @@ -1,5 +1,8 @@ #!/bin/sh +{ case $1 in '' ) runghc Setup.hs configure;runghc Setup.hs build ;; * ) runghc Setup.hs $1 ;; -esac +esac 2>&1; +} | ${0/%cabalbuild/}/fixerrormsgs +exit $PIPESTATUS diff --git a/time.xcodeproj/fixerrormsgs b/time.xcodeproj/fixerrormsgs new file mode 100755 index 0000000..ee6d461 --- /dev/null +++ b/time.xcodeproj/fixerrormsgs @@ -0,0 +1,10 @@ +#!/usr/bin/perl +$| = 1; +my $found = false; +while (<>) + { + s/^[ ]*/ / if $found; + s/^ Warning:/ warning:/ if $found; + $found = s/(^[^ ][^ ]*:[0-9][0-9]*:)\n/$1/; + print; + } From git at git.haskell.org Fri Jan 23 22:57:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:36 +0000 (UTC) Subject: [commit: packages/time] master: XCode tweak (ef08a05) Message-ID: <20150123225736.142BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ef08a05eb43c43181d0af24ba66dd6038f078665 >--------------------------------------------------------------- commit ef08a05eb43c43181d0af24ba66dd6038f078665 Author: Ashley Yakeley Date: Tue Dec 19 22:50:56 2006 -0800 XCode tweak darcs-hash:20061220065056-ac6dd-5e7ba8cb7e336e47f345da73ee1bec98f45ef182 >--------------------------------------------------------------- ef08a05eb43c43181d0af24ba66dd6038f078665 time.xcodeproj/project.pbxproj | 2 ++ 1 file changed, 2 insertions(+) diff --git a/time.xcodeproj/project.pbxproj b/time.xcodeproj/project.pbxproj index 6152858..a4fb8b8 100644 --- a/time.xcodeproj/project.pbxproj +++ b/time.xcodeproj/project.pbxproj @@ -87,6 +87,7 @@ AB6859EE0AC73993004B83FC /* prologue.txt */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = text; path = prologue.txt; sourceTree = ""; }; AB7FC7490954C86800796113 /* UTCDiff.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = UTCDiff.hs; sourceTree = ""; }; AB7FC8360954E17000796113 /* LICENSE */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = text; path = LICENSE; sourceTree = ""; }; + AB9864C60B39084300D66E11 /* Setup.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = Setup.hs; sourceTree = ""; }; ABC0F98D090C7A6000DEF265 /* tai-utc.dat */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = text; path = "tai-utc.dat"; sourceTree = ""; }; ABC0F98E090C7A6000DEF265 /* TestParseDAT.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = TestParseDAT.hs; sourceTree = ""; }; ABC0F9910913518A00DEF265 /* TestParseDAT.ref */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = text; path = TestParseDAT.ref; sourceTree = ""; }; @@ -165,6 +166,7 @@ isa = PBXGroup; children = ( AB01DCF708374808003C9EF7 /* time.cabal */, + AB9864C60B39084300D66E11 /* Setup.hs */, AB7FC8360954E17000796113 /* LICENSE */, AB01DCF908374808003C9EF7 /* HsTime.h */, AB01DCF808374808003C9EF7 /* HsTime.c */, From git at git.haskell.org Fri Jan 23 22:57:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:38 +0000 (UTC) Subject: [commit: packages/time] master: xcodeproj cleanup (49451d6) Message-ID: <20150123225738.1B7EA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/49451d6560edc0cf438c63d06b392a61f224c2ca >--------------------------------------------------------------- commit 49451d6560edc0cf438c63d06b392a61f224c2ca Author: Ashley Yakeley Date: Wed Dec 20 02:10:47 2006 -0800 xcodeproj cleanup darcs-hash:20061220101047-ac6dd-3093f56c4241839008d7f7d41348462ddab923de >--------------------------------------------------------------- 49451d6560edc0cf438c63d06b392a61f224c2ca time.xcodeproj/project.pbxproj | 160 +---------------------------------------- 1 file changed, 2 insertions(+), 158 deletions(-) diff --git a/time.xcodeproj/project.pbxproj b/time.xcodeproj/project.pbxproj index a4fb8b8..ee8c7d6 100644 --- a/time.xcodeproj/project.pbxproj +++ b/time.xcodeproj/project.pbxproj @@ -91,6 +91,7 @@ ABC0F98D090C7A6000DEF265 /* tai-utc.dat */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = text; path = "tai-utc.dat"; sourceTree = ""; }; ABC0F98E090C7A6000DEF265 /* TestParseDAT.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = TestParseDAT.hs; sourceTree = ""; }; ABC0F9910913518A00DEF265 /* TestParseDAT.ref */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = text; path = TestParseDAT.ref; sourceTree = ""; }; + ABD4C3540B3939E7003A5C75 /* TestParseTime.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = TestParseTime.hs; sourceTree = ""; }; ABD6783F084167B900CF37C0 /* POSIX.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = POSIX.hs; sourceTree = ""; }; ABD67840084167D100CF37C0 /* CTimeval.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = CTimeval.hs; sourceTree = ""; }; ABD67841084168B700CF37C0 /* UTC.hs */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.haskell; path = UTC.hs; sourceTree = ""; }; @@ -247,6 +248,7 @@ AB20A9E509275795001A7C3C /* TestEaster.ref */, ABC0F98D090C7A6000DEF265 /* tai-utc.dat */, AB26689F08A6D7290059DEC0 /* UseCases.lhs */, + ABD4C3540B3939E7003A5C75 /* TestParseTime.hs */, ); path = test; sourceTree = ""; @@ -339,40 +341,6 @@ /* End PBXTargetDependency section */ /* Begin XCBuildConfiguration section */ - ABD26A480878B4D200AD8A23 /* Development */ = { - isa = XCBuildConfiguration; - buildSettings = { - COPY_PHASE_STRIP = NO; - OTHER_CFLAGS = ""; - OTHER_LDFLAGS = ""; - OTHER_REZFLAGS = ""; - PRODUCT_NAME = Untitled; - SECTORDER_FLAGS = ""; - WARNING_CFLAGS = ( - "-Wmost", - "-Wno-four-char-constants", - "-Wno-unknown-pragmas", - ); - }; - name = Development; - }; - ABD26A490878B4D200AD8A23 /* Deployment */ = { - isa = XCBuildConfiguration; - buildSettings = { - COPY_PHASE_STRIP = YES; - OTHER_CFLAGS = ""; - OTHER_LDFLAGS = ""; - OTHER_REZFLAGS = ""; - PRODUCT_NAME = Untitled; - SECTORDER_FLAGS = ""; - WARNING_CFLAGS = ( - "-Wmost", - "-Wno-four-char-constants", - "-Wno-unknown-pragmas", - ); - }; - name = Deployment; - }; ABD26A4A0878B4D200AD8A23 /* Default */ = { isa = XCBuildConfiguration; buildSettings = { @@ -380,40 +348,6 @@ }; name = Default; }; - ABD26A4C0878B4D200AD8A23 /* Development */ = { - isa = XCBuildConfiguration; - buildSettings = { - COPY_PHASE_STRIP = NO; - OTHER_CFLAGS = ""; - OTHER_LDFLAGS = ""; - OTHER_REZFLAGS = ""; - PRODUCT_NAME = Test; - SECTORDER_FLAGS = ""; - WARNING_CFLAGS = ( - "-Wmost", - "-Wno-four-char-constants", - "-Wno-unknown-pragmas", - ); - }; - name = Development; - }; - ABD26A4D0878B4D200AD8A23 /* Deployment */ = { - isa = XCBuildConfiguration; - buildSettings = { - COPY_PHASE_STRIP = YES; - OTHER_CFLAGS = ""; - OTHER_LDFLAGS = ""; - OTHER_REZFLAGS = ""; - PRODUCT_NAME = Test; - SECTORDER_FLAGS = ""; - WARNING_CFLAGS = ( - "-Wmost", - "-Wno-four-char-constants", - "-Wno-unknown-pragmas", - ); - }; - name = Deployment; - }; ABD26A4E0878B4D200AD8A23 /* Default */ = { isa = XCBuildConfiguration; buildSettings = { @@ -421,40 +355,6 @@ }; name = Default; }; - ABD26A500878B4D200AD8A23 /* Development */ = { - isa = XCBuildConfiguration; - buildSettings = { - COPY_PHASE_STRIP = NO; - OTHER_CFLAGS = ""; - OTHER_LDFLAGS = ""; - OTHER_REZFLAGS = ""; - PRODUCT_NAME = Untitled; - SECTORDER_FLAGS = ""; - WARNING_CFLAGS = ( - "-Wmost", - "-Wno-four-char-constants", - "-Wno-unknown-pragmas", - ); - }; - name = Development; - }; - ABD26A510878B4D200AD8A23 /* Deployment */ = { - isa = XCBuildConfiguration; - buildSettings = { - COPY_PHASE_STRIP = YES; - OTHER_CFLAGS = ""; - OTHER_LDFLAGS = ""; - OTHER_REZFLAGS = ""; - PRODUCT_NAME = Untitled; - SECTORDER_FLAGS = ""; - WARNING_CFLAGS = ( - "-Wmost", - "-Wno-four-char-constants", - "-Wno-unknown-pragmas", - ); - }; - name = Deployment; - }; ABD26A520878B4D200AD8A23 /* Default */ = { isa = XCBuildConfiguration; buildSettings = { @@ -462,40 +362,6 @@ }; name = Default; }; - ABD26A540878B4D200AD8A23 /* Development */ = { - isa = XCBuildConfiguration; - buildSettings = { - COPY_PHASE_STRIP = NO; - OTHER_CFLAGS = ""; - OTHER_LDFLAGS = ""; - OTHER_REZFLAGS = ""; - PRODUCT_NAME = Everything; - SECTORDER_FLAGS = ""; - WARNING_CFLAGS = ( - "-Wmost", - "-Wno-four-char-constants", - "-Wno-unknown-pragmas", - ); - }; - name = Development; - }; - ABD26A550878B4D200AD8A23 /* Deployment */ = { - isa = XCBuildConfiguration; - buildSettings = { - COPY_PHASE_STRIP = YES; - OTHER_CFLAGS = ""; - OTHER_LDFLAGS = ""; - OTHER_REZFLAGS = ""; - PRODUCT_NAME = Everything; - SECTORDER_FLAGS = ""; - WARNING_CFLAGS = ( - "-Wmost", - "-Wno-four-char-constants", - "-Wno-unknown-pragmas", - ); - }; - name = Deployment; - }; ABD26A560878B4D200AD8A23 /* Default */ = { isa = XCBuildConfiguration; buildSettings = { @@ -512,18 +378,6 @@ }; name = Default; }; - ABD26A580878B4D200AD8A23 /* Development */ = { - isa = XCBuildConfiguration; - buildSettings = { - }; - name = Development; - }; - ABD26A590878B4D200AD8A23 /* Deployment */ = { - isa = XCBuildConfiguration; - buildSettings = { - }; - name = Deployment; - }; ABD26A5A0878B4D200AD8A23 /* Default */ = { isa = XCBuildConfiguration; buildSettings = { @@ -536,8 +390,6 @@ ABD26A470878B4D200AD8A23 /* Build configuration list for PBXLegacyTarget "Build" */ = { isa = XCConfigurationList; buildConfigurations = ( - ABD26A480878B4D200AD8A23 /* Development */, - ABD26A490878B4D200AD8A23 /* Deployment */, ABD26A4A0878B4D200AD8A23 /* Default */, ); defaultConfigurationIsVisible = 0; @@ -546,8 +398,6 @@ ABD26A4B0878B4D200AD8A23 /* Build configuration list for PBXLegacyTarget "Test" */ = { isa = XCConfigurationList; buildConfigurations = ( - ABD26A4C0878B4D200AD8A23 /* Development */, - ABD26A4D0878B4D200AD8A23 /* Deployment */, ABD26A4E0878B4D200AD8A23 /* Default */, ); defaultConfigurationIsVisible = 0; @@ -556,8 +406,6 @@ ABD26A4F0878B4D200AD8A23 /* Build configuration list for PBXLegacyTarget "Documentation" */ = { isa = XCConfigurationList; buildConfigurations = ( - ABD26A500878B4D200AD8A23 /* Development */, - ABD26A510878B4D200AD8A23 /* Deployment */, ABD26A520878B4D200AD8A23 /* Default */, ); defaultConfigurationIsVisible = 0; @@ -566,8 +414,6 @@ ABD26A530878B4D200AD8A23 /* Build configuration list for PBXAggregateTarget "Everything" */ = { isa = XCConfigurationList; buildConfigurations = ( - ABD26A540878B4D200AD8A23 /* Development */, - ABD26A550878B4D200AD8A23 /* Deployment */, ABD26A560878B4D200AD8A23 /* Default */, ); defaultConfigurationIsVisible = 0; @@ -576,8 +422,6 @@ ABD26A570878B4D200AD8A23 /* Build configuration list for PBXProject "time" */ = { isa = XCConfigurationList; buildConfigurations = ( - ABD26A580878B4D200AD8A23 /* Development */, - ABD26A590878B4D200AD8A23 /* Deployment */, ABD26A5A0878B4D200AD8A23 /* Default */, ); defaultConfigurationIsVisible = 0; From git at git.haskell.org Fri Jan 23 22:57:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:40 +0000 (UTC) Subject: [commit: packages/time] master: attempt to get cabal test working (843ed89) Message-ID: <20150123225740.22AC23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/843ed89f8f3d46ddabe04f1ea8ccf33426a13c92 >--------------------------------------------------------------- commit 843ed89f8f3d46ddabe04f1ea8ccf33426a13c92 Author: Ashley Yakeley Date: Wed Dec 20 02:12:54 2006 -0800 attempt to get cabal test working darcs-hash:20061220101254-ac6dd-56f6ff37f578c96f352ca61032eaf269e727bdf9 >--------------------------------------------------------------- 843ed89f8f3d46ddabe04f1ea8ccf33426a13c92 Setup.hs | 19 +++++++++++++++++-- test/Makefile | 8 ++++---- 2 files changed, 21 insertions(+), 6 deletions(-) diff --git a/Setup.hs b/Setup.hs index 60804b2..2859262 100644 --- a/Setup.hs +++ b/Setup.hs @@ -1,6 +1,21 @@ module Main (main) where -import Distribution.Simple (defaultMainWithHooks, defaultUserHooks) +import Distribution.Simple +import Distribution.PackageDescription +import Distribution.Simple.LocalBuildInfo +import System.Exit +import System.Cmd +import System.Directory +import Control.Exception + +withCurrentDirectory :: FilePath -> IO a -> IO a +withCurrentDirectory path f = do + cur <- getCurrentDirectory + setCurrentDirectory path + finally f (setCurrentDirectory cur) + +runTestScript :: Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO ExitCode +runTestScript args flag pd lbi = withCurrentDirectory "test" (system "make") main :: IO () -main = defaultMainWithHooks defaultUserHooks +main = defaultMainWithHooks defaultUserHooks{runTests = runTestScript} diff --git a/test/Makefile b/test/Makefile index c3f2992..ff2454b 100644 --- a/test/Makefile +++ b/test/Makefile @@ -1,6 +1,6 @@ GHC = ghc -GHCFLAGS = -LIBS = ../../dist/build/libHStime-1.0.a +GHCFLAGS = -i../dist/build +LIBS = ../dist/build/libHStime-1.0.a default: CurrentTime.run ShowDST.run test @@ -88,10 +88,10 @@ clean: @: %.o: %.hs - ghc -i.. -c $< -o $@ + $(GHC) $(GHCFLAGS) -c $< -o $@ %.o: %.lhs - ghc -i.. -c $< -o $@ + $(GHC) $(GHCFLAGS) -c $< -o $@ FORCE: From git at git.haskell.org Fri Jan 23 22:57:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:42 +0000 (UTC) Subject: [commit: packages/time] master: get "runhaskell Setup.hs test" to work (ab61764) Message-ID: <20150123225742.298873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ab6176494357c23ad1bd6b4a79bc5cbeae76c4b6 >--------------------------------------------------------------- commit ab6176494357c23ad1bd6b4a79bc5cbeae76c4b6 Author: Ashley Yakeley Date: Fri Dec 22 18:26:02 2006 -0800 get "runhaskell Setup.hs test" to work darcs-hash:20061223022602-ac6dd-8a16b100b94134574f8368cb1a521ea0d55ff64f >--------------------------------------------------------------- ab6176494357c23ad1bd6b4a79bc5cbeae76c4b6 test/Makefile | 36 +++++++++++++++++++----------------- test/TestParseTime.hs | 23 ++++++++++++++++------- 2 files changed, 35 insertions(+), 24 deletions(-) diff --git a/test/Makefile b/test/Makefile index ff2454b..ecfaa96 100644 --- a/test/Makefile +++ b/test/Makefile @@ -1,55 +1,57 @@ GHC = ghc -GHCFLAGS = -i../dist/build -LIBS = ../dist/build/libHStime-1.0.a +GHCFLAGS = -package time -default: CurrentTime.run ShowDST.run test +default: + cd ..; runhaskell Setup.hs register --user --inplace + make CurrentTime.run ShowDST.run test + cd ..; runhaskell Setup.hs unregister --user -TestMonthDay: TestMonthDay.o $(LIBS) +TestMonthDay: TestMonthDay.o $(GHC) $(GHCFLAGS) $^ -o $@ -ConvertBack: ConvertBack.o $(LIBS) +ConvertBack: ConvertBack.o $(GHC) $(GHCFLAGS) $^ -o $@ -TestCalendars: TestCalendars.o $(LIBS) +TestCalendars: TestCalendars.o $(GHC) $(GHCFLAGS) $^ -o $@ -TestTime: TestTime.o $(LIBS) +TestTime: TestTime.o $(GHC) $(GHCFLAGS) $^ -o $@ -LongWeekYears: LongWeekYears.o $(LIBS) +LongWeekYears: LongWeekYears.o $(GHC) $(GHCFLAGS) $^ -o $@ -ClipDates: ClipDates.o $(LIBS) +ClipDates: ClipDates.o $(GHC) $(GHCFLAGS) $^ -o $@ -AddDays: AddDays.o $(LIBS) +AddDays: AddDays.o $(GHC) $(GHCFLAGS) $^ -o $@ -TestFormat: TestFormat.o TestFormatStuff.o $(LIBS) +TestFormat: TestFormat.o TestFormatStuff.o $(GHC) $(GHCFLAGS) $^ -o $@ TestFormatStuff.o: TestFormatStuff.c TestFormatStuff.h gcc -o $@ -c $< -TestParseDAT: TestParseDAT.o $(LIBS) +TestParseDAT: TestParseDAT.o $(GHC) $(GHCFLAGS) $^ -o $@ -TestEaster: TestEaster.o $(LIBS) +TestEaster: TestEaster.o $(GHC) $(GHCFLAGS) $^ -o $@ -CurrentTime: CurrentTime.o $(LIBS) +CurrentTime: CurrentTime.o $(GHC) $(GHCFLAGS) $^ -o $@ -ShowDST: ShowDST.o $(LIBS) +ShowDST: ShowDST.o $(GHC) $(GHCFLAGS) $^ -o $@ -TimeZone: TimeZone.o $(LIBS) +TimeZone: TimeZone.o $(GHC) $(GHCFLAGS) $^ -o $@ TimeZone.ref: FORCE date +%z > $@ -TestParseTime: TestParseTime.o $(LIBS) +TestParseTime: TestParseTime.o $(GHC) $(GHCFLAGS) -package QuickCheck $^ -o $@ test: \ diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index 91d76b0..ad0c1c5 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -1,3 +1,5 @@ +{-# OPTIONS -Wall -Werror -fno-warn-type-defaults -fno-warn-unused-binds #-} + import Control.Monad import Data.Char import Data.Ratio @@ -10,6 +12,7 @@ import System.Locale import Test.QuickCheck +ntest :: Int ntest = 1000 main :: IO () @@ -26,10 +29,13 @@ checkOne :: Config -> NamedProperty -> IO () checkOne config (n,p) = do putStr (rpad 65 ' ' n) check config p - where rpad n c xs = xs ++ replicate (n - length xs) c + where rpad n' c xs = xs ++ replicate (n' - length xs) c + +parse :: ParseTime t => String -> String -> Maybe t parse f t = parseTime defaultTimeLocale f t +format :: (FormatTime t) => String -> t -> String format f t = formatTime defaultTimeLocale f t @@ -39,12 +45,12 @@ instance Arbitrary Day where instance Arbitrary DiffTime where arbitrary = oneof [intSecs, fracSecs] -- up to 1 leap second - where intSecs = liftM secondsToDiffTime $ choose (0, 86400) - fracSecs = liftM picosecondsToDiffTime $ choose (0, 86400 * 10^12) - secondsToDiffTime :: Integer -> DiffTime - secondsToDiffTime = fromInteger - picosecondsToDiffTime :: Integer -> DiffTime - picosecondsToDiffTime x = fromRational (x % 10^12) + where intSecs = liftM secondsToDiffTime' $ choose (0, 86400) + fracSecs = liftM picosecondsToDiffTime' $ choose (0, 86400 * 10^12) + secondsToDiffTime' :: Integer -> DiffTime + secondsToDiffTime' = fromInteger + picosecondsToDiffTime' :: Integer -> DiffTime + picosecondsToDiffTime' x = fromRational (x % 10^12) coarbitrary t = coarbitrary (fromEnum t) instance Arbitrary TimeOfDay where @@ -75,6 +81,7 @@ instance Eq ZonedTime where -- * tests for dbugging failing cases -- +test_parse_format :: (FormatTime t,ParseTime t,Show t) => String -> t -> (String,String,Maybe t) test_parse_format f t = let s = format f t in (show t, s, parse f s `asTypeOf` Just t) -- @@ -101,11 +108,13 @@ prop_parse_showOrdinalDate d = parse "%Y-%j" (showOrdinalDate d) == Just d -- * fromMondayStartWeek and fromSundayStartWeek -- +prop_fromMondayStartWeek :: Day -> Bool prop_fromMondayStartWeek d = let (w,wd) = mondayStartWeek d (y,_,_) = toGregorian d in fromMondayStartWeek y w wd == d +prop_fromSundayStartWeek :: Day -> Bool prop_fromSundayStartWeek d = let (w,wd) = sundayStartWeek d (y,_,_) = toGregorian d From git at git.haskell.org Fri Jan 23 22:57:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:44 +0000 (UTC) Subject: [commit: packages/time] master: Changed %S to return whole seconds, and added %Q and %q. (f73da90) Message-ID: <20150123225744.3079F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f73da902c82a2ce5f0a336ee1fd1774df5bdb6e2 >--------------------------------------------------------------- commit f73da902c82a2ce5f0a336ee1fd1774df5bdb6e2 Author: bjorn Date: Sun Feb 11 07:53:58 2007 -0800 Changed %S to return whole seconds, and added %Q and %q. Implements part of http://hackage.haskell.org/trac/ghc/ticket/1007 formatTime: Change %S to: the number of whole seconds. formatTime: Add %q: the number of picoseconds (including trailing zeroes). formatTime: Add %Q: decimal point and second decimals, without trailing zeros. If the number of picoseconds is zero, nothing is produced (not even the decimal point). Rationale: Currently %S includes decimals if there are any. This is different from strftime, and there is no format specifier for just the integer part of the seconds. It would be nice to have such a specifier to implement many standard date formats (e.g. RFC 822). Also a specifier for second decimals would also help when using %s. Currently there is no reasonable way to get more than integer second precision with since-epoch timestamps. The current %S would be equivalent to %S%Q under this proposal." darcs-hash:20070211155358-6cdb2-de94204665c57a1b86b65bd80f1a98d3d469d0f0 >--------------------------------------------------------------- f73da902c82a2ce5f0a336ee1fd1774df5bdb6e2 Data/Time/LocalTime/Format.hs | 19 +++++++++++++++---- Data/Time/LocalTime/Parse.hs | 34 +++++++++++++++++++--------------- 2 files changed, 34 insertions(+), 19 deletions(-) diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index c13160e..fc26327 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -20,6 +20,7 @@ import Data.Time.Clock.POSIX import System.Locale import Data.Maybe import Data.Char +import Data.Fixed -- class FormatTime t where @@ -69,11 +70,19 @@ class FormatTime t where -- -- [@%M@] minute, @00@ - @59@ -- --- [@%S@] second with decimal part if not an integer, @00@ - @60.999999999999@ +-- [@%S@] second, without decimal part, @00@ - @60@ +-- +-- [@%q@] picosecond, including trailing zeros, @000000000000@ - @999999999999 at . +-- +-- [@%Q@] decimal point and up to 12 second decimals, without trailing zeros. +-- For a whole number of seconds, @%Q@ produces the empty string. -- -- For UTCTime and ZonedTime: -- --- [@%s@] number of seconds since the Unix epoch +-- [@%s@] number of whole seconds since the Unix epoch. For times before +-- the Unix epoch, this is a negative number. Note that in @%s.%q@ and @%s%Q@ +-- the decimals are positive, not negative. For example, 0.9 seconds +-- before the Unix epoch is formatted as @-1.1@ with @%s%Q at . -- -- For Day (and LocalTime and ZonedTime and UTCTime): -- @@ -154,14 +163,16 @@ instance FormatTime TimeOfDay where -- Minute formatCharacter 'M' = Just (\_ -> show2 . todMin) -- Second - formatCharacter 'S' = Just (\_ -> show2Fixed . todSec) + formatCharacter 'S' = Just (\_ -> (show2 :: Int -> String) . truncate . todSec) + formatCharacter 'q' = Just (\_ -> drop 1 . dropWhile (/='.') . showFixed False . todSec) + formatCharacter 'Q' = Just (\_ -> dropWhile (/='.') . showFixed True . todSec) -- Default formatCharacter _ = Nothing instance FormatTime ZonedTime where formatCharacter 'c' = Just (\locale -> formatTime locale (dateTimeFmt locale)) - formatCharacter 's' = Just (\_ zt -> show (truncate (utcTimeToPOSIXSeconds (zonedTimeToUTC zt)) :: Integer)) + formatCharacter 's' = Just (\_ zt -> show (floor (utcTimeToPOSIXSeconds (zonedTimeToUTC zt)) :: Integer)) formatCharacter c = case (formatCharacter c) of Just f -> Just (\locale dt -> f locale (zonedTimeToLocalTime dt)) Nothing -> case (formatCharacter c) of diff --git a/Data/Time/LocalTime/Parse.hs b/Data/Time/LocalTime/Parse.hs index a5420d3..b6ae350 100644 --- a/Data/Time/LocalTime/Parse.hs +++ b/Data/Time/LocalTime/Parse.hs @@ -123,10 +123,9 @@ parseValue l c = 'k' -> spdigits 2 'l' -> spdigits 2 'M' -> digits 2 - 'S' -> do s <- digits 2 - ds <- liftM2 (:) (char '.') (munch isDigit) - <++ return "" - return $ s ++ ds + 'S' -> digits 2 + 'q' -> digits 12 + 'Q' -> liftM2 (:) (char '.') (munch isDigit) <++ return "" 's' -> (char '-' >> liftM ('-':) (munch1 isDigit)) <++ munch1 isDigit 'Y' -> digits 4 @@ -246,18 +245,20 @@ instance ParseTime TimeOfDay where 'k' -> TimeOfDay (read x) m s 'l' -> TimeOfDay (read x) m s 'M' -> TimeOfDay h (read x) s - 'S' -> TimeOfDay h m (readFixed x) + 'S' -> TimeOfDay h m (fromInteger (read x)) + 'q' -> TimeOfDay h m (mkPico (truncate s) (read x)) + 'Q' -> if null x then t + else let ps = read $ take 12 $ rpad 12 '0' $ drop 1 x + in TimeOfDay h m (mkPico (truncate s) ps) _ -> t where am = TimeOfDay (h `mod` 12) m s pm = TimeOfDay (if h < 12 then h + 12 else h) m s +rpad :: Int -> a -> [a] -> [a] +rpad n c xs = xs ++ replicate (n - length xs) c -readFixed :: HasResolution a => String -> Fixed a -readFixed s = case break (=='.') s of - (x,"") -> fromInteger (read x) - (x,_:y) -> mkFixed12 (read x) (read (rpad 12 '0' y)) - where rpad n c xs = xs ++ replicate (n - length xs) c - mkFixed12 i f = fromInteger i + fromRational (f % 1000000000000) +mkPico :: Integer -> Integer -> Pico +mkPico i f = fromInteger i + fromRational (f % 1000000000000) instance ParseTime LocalTime where buildTime l xs = LocalTime (buildTime l xs) (buildTime l xs) @@ -278,9 +279,12 @@ instance ParseTime TimeZone where instance ParseTime ZonedTime where buildTime l xs = foldl f (ZonedTime (buildTime l xs) (buildTime l xs)) xs where - f t (c,x) = + f t@(ZonedTime (LocalTime _ tod) z) (c,x) = case c of - 's' -> utcToZonedTime (zonedTimeZone t) (posixSecondsToUTCTime (fromInteger (read x))) + 's' -> let s = fromInteger (read x) + (_,ps) = properFraction (todSec tod) :: (Integer,Pico) + s' = s + fromRational (toRational ps) + in utcToZonedTime z (posixSecondsToUTCTime s') _ -> t instance ParseTime UTCTime where @@ -292,10 +296,10 @@ instance Read Day where readsPrec _ = readParen False $ readsTime defaultTimeLocale "%Y-%m-%d" instance Read TimeOfDay where - readsPrec _ = readParen False $ readsTime defaultTimeLocale "%H:%M:%S" + readsPrec _ = readParen False $ readsTime defaultTimeLocale "%H:%M:%S%Q" instance Read LocalTime where - readsPrec _ = readParen False $ readsTime defaultTimeLocale "%Y-%m-%d %H:%M:%S" + readsPrec _ = readParen False $ readsTime defaultTimeLocale "%Y-%m-%d %H:%M:%S%Q" instance Read TimeZone where readsPrec _ = readParen False $ \s -> From git at git.haskell.org Fri Jan 23 22:57:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:46 +0000 (UTC) Subject: [commit: packages/time] master: QuickCheck properties for the new %S, %q and %Q. (fcf3460) Message-ID: <20150123225746.3612B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/fcf34604835eb3f4b512052b49a1f51d3bc65fed >--------------------------------------------------------------- commit fcf34604835eb3f4b512052b49a1f51d3bc65fed Author: bjorn Date: Sun Feb 11 08:15:46 2007 -0800 QuickCheck properties for the new %S, %q and %Q. darcs-hash:20070211161546-6cdb2-207fccfeafd267fd7216458018b523bd134137e4 >--------------------------------------------------------------- fcf34604835eb3f4b512052b49a1f51d3bc65fed test/TestParseTime.hs | 102 ++++++++++++++++++++++++++++++++++++++++---------- 1 file changed, 83 insertions(+), 19 deletions(-) diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index ad0c1c5..8b8b334 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -133,6 +133,16 @@ prop_parse_format_named typeName f = ("prop_parse_format " ++ typeName ++ " " ++ show f, property (prop_parse_format f)) +prop_format_parse_format :: (FormatTime t, ParseTime t) => FormatString t -> t -> Bool +prop_format_parse_format (FormatString f) t = + fmap (format f) (parse f (format f t) `asTypeOf` Just t) == Just (format f t) + +prop_format_parse_format_named :: (Arbitrary t, Show t, FormatTime t, ParseTime t) + => String -> FormatString t -> NamedProperty +prop_format_parse_format_named typeName f = + ("prop_format_parse_format " ++ typeName ++ " " ++ show f, + property (prop_format_parse_format f)) + -- -- * crashes in parse -- @@ -190,6 +200,7 @@ properties = ++ [("prop_parse_showWeekDate", property prop_parse_showWeekDate), ("prop_parse_showGregorian", property prop_parse_showGregorian), ("prop_parse_showOrdinalDate", property prop_parse_showOrdinalDate)] + ++ map (prop_parse_format_named "Day") dayFormats ++ map (prop_parse_format_named "TimeOfDay") timeOfDayFormats ++ map (prop_parse_format_named "LocalTime") localTimeFormats @@ -197,13 +208,19 @@ properties = ++ map (prop_parse_format_named "ZonedTime") zonedTimeFormats ++ map (prop_parse_format_named "UTCTime") utcTimeFormats - ++ map (prop_no_crash_bad_input_named "Day") dayFormats - ++ map (prop_no_crash_bad_input_named "TimeOfDay") timeOfDayFormats - ++ map (prop_no_crash_bad_input_named "LocalTime") localTimeFormats - ++ map (prop_no_crash_bad_input_named "TimeZone") timeZoneFormats - ++ map (prop_no_crash_bad_input_named "ZonedTime") zonedTimeFormats - ++ map (prop_no_crash_bad_input_named "UTCTime") utcTimeFormats + ++ map (prop_format_parse_format_named "Day") partialDayFormats + ++ map (prop_format_parse_format_named "TimeOfDay") partialTimeOfDayFormats + ++ map (prop_format_parse_format_named "LocalTime") partialLocalTimeFormats + ++ map (prop_format_parse_format_named "TimeZone") partialTimeZoneFormats + ++ map (prop_format_parse_format_named "ZonedTime") partialZonedTimeFormats + ++ map (prop_format_parse_format_named "UTCTime") partialUTCTimeFormats + ++ map (prop_no_crash_bad_input_named "Day") (dayFormats ++ partialDayFormats ++ failingDayFormats) + ++ map (prop_no_crash_bad_input_named "TimeOfDay") (timeOfDayFormats ++ partialTimeOfDayFormats ++ failingTimeOfDayFormats) + ++ map (prop_no_crash_bad_input_named "LocalTime") (localTimeFormats ++ partialLocalTimeFormats ++ failingLocalTimeFormats) + ++ map (prop_no_crash_bad_input_named "TimeZone") (timeZoneFormats ++ partialTimeZoneFormats ++ failingTimeZoneFormats) + ++ map (prop_no_crash_bad_input_named "ZonedTime") (zonedTimeFormats ++ partialZonedTimeFormats ++ failingZonedTimeFormats) + ++ map (prop_no_crash_bad_input_named "UTCTime") (utcTimeFormats ++ partialUTCTimeFormats ++ failingUTCTimeFormats) @@ -227,14 +244,16 @@ timeOfDayFormats :: [FormatString TimeOfDay] timeOfDayFormats = map FormatString [ -- 24 h formats - "%H:%M:%S","%k:%M:%S","%H%M%S","%T","%X","%R:%S", + "%H:%M:%S.%q","%k:%M:%S.%q","%H%M%S.%q","%T.%q","%X.%q","%R:%S.%q", + "%H:%M:%S%Q","%k:%M:%S%Q","%H%M%S%Q","%T%Q","%X%Q","%R:%S%Q", -- 12 h formats - "%I:%M:%S %p","%I:%M:%S %P","%l:%M:%S %p","%r" + "%I:%M:%S.%q %p","%I:%M:%S.%q %P","%l:%M:%S.%q %p","%r %q", + "%I:%M:%S%Q %p","%I:%M:%S%Q %P","%l:%M:%S%Q %p","%r %Q" ] localTimeFormats :: [FormatString LocalTime] localTimeFormats = map FormatString $ - ["%c"] + [] {- -- there's soo many of them... concat [ [df ++ " " ++ tf, tf ++ " " ++ df] | FormatString df <- dayFormats, @@ -246,11 +265,52 @@ timeZoneFormats = map FormatString ["%z","%z%Z","%Z%z"] zonedTimeFormats :: [FormatString ZonedTime] zonedTimeFormats = map FormatString - ["%a, %d %b %Y %H:%M:%S %z"] + ["%a, %d %b %Y %H:%M:%S.%q %z", "%a, %d %b %Y %H:%M:%S%Q %z", "%s.%q %z", "%s%Q %z"] utcTimeFormats :: [FormatString UTCTime] utcTimeFormats = map FormatString - ["%c"] + ["%s.%q","%s%Q"] + +-- +-- * Formats that do not include all the information +-- + +partialDayFormats :: [FormatString Day] +partialDayFormats = map FormatString + [ ] + +partialTimeOfDayFormats :: [FormatString TimeOfDay] +partialTimeOfDayFormats = map FormatString + [ ] + +partialLocalTimeFormats :: [FormatString LocalTime] +partialLocalTimeFormats = map FormatString + [ + -- %c does not include second decimals + "%c" + ] + +partialTimeZoneFormats :: [FormatString TimeZone] +partialTimeZoneFormats = map FormatString + [ + ] + +partialZonedTimeFormats :: [FormatString ZonedTime] +partialZonedTimeFormats = map FormatString + [ + -- %s does not include second decimals + "%s %z" + ] + +partialUTCTimeFormats :: [FormatString UTCTime] +partialUTCTimeFormats = map FormatString + [ + -- %s does not include second decimals + "%s", + -- %c does not include second decimals + "%c" + ] + -- -- * Known failures @@ -266,13 +326,22 @@ knownFailures = + failingDayFormats :: [FormatString Day] failingDayFormats = map FormatString + [ -- ISO week dates with two digit year + "%g-%V-%u","%g-%V-%a","%g-%V-%A","%g-%V-%w", "%A week %V, %g", "day %V, week %A, %g", + "%g-W%V-%u" + ] + +failingTimeOfDayFormats :: [FormatString TimeOfDay] +failingTimeOfDayFormats = map FormatString [ ] failingLocalTimeFormats :: [FormatString LocalTime] failingLocalTimeFormats = map FormatString - [ ] + [ + ] failingTimeZoneFormats :: [FormatString TimeZone] failingTimeZoneFormats = map FormatString @@ -286,15 +355,10 @@ failingZonedTimeFormats = map FormatString [ -- can't figure out offset from %Z, also, formatTime produces "" for %Z "%c", - "%a, %d %b %Y %H:%M:%S %Z", - -- %s does not include second decimals - "%s %z" + "%a, %d %b %Y %H:%M:%S %Z" ] failingUTCTimeFormats :: [FormatString UTCTime] failingUTCTimeFormats = map FormatString - [ - -- %s does not include second decimals - "%s" - ] + [] From git at git.haskell.org Fri Jan 23 22:57:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:48 +0000 (UTC) Subject: [commit: packages/time] master: Added %f: The century part of the week date year. (5ac1884) Message-ID: <20150123225748.3D4FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/5ac1884daa4866c151c1955cca0b0a308e95412d >--------------------------------------------------------------- commit 5ac1884daa4866c151c1955cca0b0a308e95412d Author: bjorn Date: Sun Feb 11 08:26:07 2007 -0800 Added %f: The century part of the week date year. Fixes part of http://hackage.haskell.org/trac/ghc/ticket/1007 Rationale: There is a %g specifier for the last two digits of the week date year, but no specifier for the century. %C cannot be used, since the normal century and the week date century can differ: > formatTime defaultTimeLocale "%Y %G" (fromGregorian 2000 1 1) "2000 1999" darcs-hash:20070211162607-6cdb2-605a7f26b21c0a063f2308683845e727688a35bd >--------------------------------------------------------------- 5ac1884daa4866c151c1955cca0b0a308e95412d Data/Time/LocalTime/Format.hs | 4 ++++ Data/Time/LocalTime/Parse.hs | 3 +++ test/TestParseTime.hs | 2 ++ 3 files changed, 9 insertions(+) diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index fc26327..ff9ca67 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -114,6 +114,8 @@ class FormatTime t where -- -- [@%g@] last two digits of year for Week Date format, @00@ - @99@ -- +-- [@%f@] century (first two digits of year) for Week Date format, @00@ - @99@ +-- -- [@%V@] week for Week Date format, @01@ - @53@ -- -- [@%u@] day for Week Date format, @1@ - @7@ @@ -208,6 +210,8 @@ instance FormatTime Day where -- ISO 8601 Week Date formatCharacter 'G' = Just (\_ -> show . (\(y,_,_) -> y) . toWeekDate) formatCharacter 'g' = Just (\_ -> show2 . mod100 . (\(y,_,_) -> y) . toWeekDate) + formatCharacter 'f' = Just (\_ -> show2 . div100 . (\(y,_,_) -> y) . toWeekDate) + formatCharacter 'V' = Just (\_ -> show2 . (\(_,w,_) -> w) . toWeekDate) formatCharacter 'u' = Just (\_ -> show . (\(_,_,d) -> d) . toWeekDate) diff --git a/Data/Time/LocalTime/Parse.hs b/Data/Time/LocalTime/Parse.hs index b6ae350..fa71a8a 100644 --- a/Data/Time/LocalTime/Parse.hs +++ b/Data/Time/LocalTime/Parse.hs @@ -139,6 +139,7 @@ parseValue l c = 'j' -> digits 3 'G' -> digits 4 'g' -> digits 2 + 'f' -> digits 2 'V' -> digits 2 'u' -> oneOf $ map (:[]) ['1'..'7'] 'a' -> oneOf (map snd (wDays l)) @@ -198,6 +199,8 @@ instance ParseTime Day where 'G' -> let y = read x in [Century (y `div` 100), Year (y `mod` 100)] -- %g: last two digits of year for Week Date format, 00 - 99 'g' -> [Year (read x)] + -- %f century (first two digits of year) for Week Date format, 00 - 99 + 'f' -> [Century (read x)] -- %V: week for Week Date format, 01 - 53 'V' -> [Week ISOWeek (read x)] -- %u: day for Week Date format, 1 - 7 diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index 8b8b334..876c227 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -236,6 +236,8 @@ dayFormats = map FormatString -- ISO week dates "%G-%V-%u","%G-%V-%a","%G-%V-%A","%G-%V-%w", "%A week %V, %G", "day %V, week %A, %G", "%G-W%V-%u", + "%f%g-%V-%u","%f%g-%V-%a","%f%g-%V-%A","%f%g-%V-%w", "%A week %V, %f%g", "day %V, week %A, %f%g", + "%f%g-W%V-%u", -- monday and sunday week dates "%Y-w%U-%A", "%Y-w%W-%A", "%Y-%A-w%U", "%Y-%A-w%W", "%A week %U, %Y", "%A week %W, %Y" ] From git at git.haskell.org Fri Jan 23 22:57:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:50 +0000 (UTC) Subject: [commit: packages/time] master: Changed %Z to produce the time zone offset if the time zone name is "". (4d14562) Message-ID: <20150123225750.43F633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/4d14562fbd5ba0118216365198b3298eb6265648 >--------------------------------------------------------------- commit 4d14562fbd5ba0118216365198b3298eb6265648 Author: bjorn Date: Sun Feb 11 10:11:09 2007 -0800 Changed %Z to produce the time zone offset if the time zone name is "". Rationale: Without this, if you format a ZonedTime which contains an unnamed timezone, %Z produces the empty string. This is invalid in many formats. It is better to output the offset when there is no timezone name. darcs-hash:20070211181109-6cdb2-bde288cdfb6400ef08b24b26aa2f59d7f25807e4 >--------------------------------------------------------------- 4d14562fbd5ba0118216365198b3298eb6265648 Data/Time/LocalTime/Format.hs | 4 +++- Data/Time/LocalTime/Parse.hs | 17 ++++++++++------- 2 files changed, 13 insertions(+), 8 deletions(-) diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs index ff9ca67..61a4e90 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/LocalTime/Format.hs @@ -183,7 +183,9 @@ instance FormatTime ZonedTime where instance FormatTime TimeZone where formatCharacter 'z' = Just (\_ -> timeZoneOffsetString) - formatCharacter 'Z' = Just (\_ -> timeZoneName) + formatCharacter 'Z' = + Just (\_ z -> let n = timeZoneName z + in if null n then timeZoneOffsetString z else n) formatCharacter _ = Nothing instance FormatTime Day where diff --git a/Data/Time/LocalTime/Parse.hs b/Data/Time/LocalTime/Parse.hs index fa71a8a..605eee9 100644 --- a/Data/Time/LocalTime/Parse.hs +++ b/Data/Time/LocalTime/Parse.hs @@ -114,7 +114,9 @@ parseValue :: TimeLocale -> Char -> ReadP String parseValue l c = case c of 'z' -> liftM2 (:) (choice [char '+', char '-']) (digits 4) - 'Z' -> munch isUpper + 'Z' -> munch1 isUpper <++ + liftM2 (:) (choice [char '+', char '-']) (digits 4) <++ + return "" -- produced by %Z for LocalTime 'P' -> oneOf (let (am,pm) = amPm l in [map toLower am, map toLower pm]) 'p' -> oneOf (let (am,pm) = amPm l in [am, pm]) @@ -271,13 +273,16 @@ instance ParseTime TimeZone where where f t@(TimeZone offset dst name) (c,x) = case c of - 'z' -> TimeZone (sign * (60 * h + m)) dst name + 'z' -> zone + 'Z' | null x -> t + | isUpper (head x) -> TimeZone offset dst x -- FIXME: figure out timezone offset? + | otherwise -> zone + _ -> t + where zone = TimeZone (sign * (60 * h + m)) dst name where (s:h1:h2:m1:m2:[]) = x sign = if s == '-' then -1 else 1 h = read [h1,h2] m = read [m1,m2] - 'Z' -> TimeZone offset dst x -- FIXME: figure out timezone offset? - _ -> t instance ParseTime ZonedTime where buildTime l xs = foldl f (ZonedTime (buildTime l xs) (buildTime l xs)) xs @@ -305,9 +310,7 @@ instance Read LocalTime where readsPrec _ = readParen False $ readsTime defaultTimeLocale "%Y-%m-%d %H:%M:%S%Q" instance Read TimeZone where - readsPrec _ = readParen False $ \s -> - readsTime defaultTimeLocale "%z" s - ++ readsTime defaultTimeLocale "%Z" s + readsPrec _ = readParen False $ readsTime defaultTimeLocale "%Z" instance Read ZonedTime where readsPrec n = readParen False $ \s -> From git at git.haskell.org Fri Jan 23 22:57:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:52 +0000 (UTC) Subject: [commit: packages/time] master: Cleaned up date parsing QuickCheck properties. (3750abf) Message-ID: <20150123225752.4ADD83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3750abfb4e0384d8cdcc84720cdc88bcd576ba08 >--------------------------------------------------------------- commit 3750abfb4e0384d8cdcc84720cdc88bcd576ba08 Author: bjorn Date: Sun Feb 11 10:15:02 2007 -0800 Cleaned up date parsing QuickCheck properties. darcs-hash:20070211181502-6cdb2-225795f312c8381c33bd79811535c0d34e2e461b >--------------------------------------------------------------- 3750abfb4e0384d8cdcc84720cdc88bcd576ba08 test/TestParseTime.hs | 75 +++++++++++++-------------------------------------- 1 file changed, 19 insertions(+), 56 deletions(-) diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index 876c227..50049bc 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -211,16 +211,15 @@ properties = ++ map (prop_format_parse_format_named "Day") partialDayFormats ++ map (prop_format_parse_format_named "TimeOfDay") partialTimeOfDayFormats ++ map (prop_format_parse_format_named "LocalTime") partialLocalTimeFormats - ++ map (prop_format_parse_format_named "TimeZone") partialTimeZoneFormats ++ map (prop_format_parse_format_named "ZonedTime") partialZonedTimeFormats ++ map (prop_format_parse_format_named "UTCTime") partialUTCTimeFormats - ++ map (prop_no_crash_bad_input_named "Day") (dayFormats ++ partialDayFormats ++ failingDayFormats) - ++ map (prop_no_crash_bad_input_named "TimeOfDay") (timeOfDayFormats ++ partialTimeOfDayFormats ++ failingTimeOfDayFormats) - ++ map (prop_no_crash_bad_input_named "LocalTime") (localTimeFormats ++ partialLocalTimeFormats ++ failingLocalTimeFormats) - ++ map (prop_no_crash_bad_input_named "TimeZone") (timeZoneFormats ++ partialTimeZoneFormats ++ failingTimeZoneFormats) - ++ map (prop_no_crash_bad_input_named "ZonedTime") (zonedTimeFormats ++ partialZonedTimeFormats ++ failingZonedTimeFormats) - ++ map (prop_no_crash_bad_input_named "UTCTime") (utcTimeFormats ++ partialUTCTimeFormats ++ failingUTCTimeFormats) + ++ map (prop_no_crash_bad_input_named "Day") (dayFormats ++ partialDayFormats ++ failingPartialDayFormats) + ++ map (prop_no_crash_bad_input_named "TimeOfDay") (timeOfDayFormats ++ partialTimeOfDayFormats) + ++ map (prop_no_crash_bad_input_named "LocalTime") (localTimeFormats ++ partialLocalTimeFormats) + ++ map (prop_no_crash_bad_input_named "TimeZone") (timeZoneFormats) + ++ map (prop_no_crash_bad_input_named "ZonedTime") (zonedTimeFormats ++ partialZonedTimeFormats) + ++ map (prop_no_crash_bad_input_named "UTCTime") (utcTimeFormats ++ partialUTCTimeFormats) @@ -263,11 +262,12 @@ localTimeFormats = map FormatString $ -} timeZoneFormats :: [FormatString TimeZone] -timeZoneFormats = map FormatString ["%z","%z%Z","%Z%z"] +timeZoneFormats = map FormatString ["%z","%z%Z","%Z%z","%Z"] zonedTimeFormats :: [FormatString ZonedTime] zonedTimeFormats = map FormatString - ["%a, %d %b %Y %H:%M:%S.%q %z", "%a, %d %b %Y %H:%M:%S%Q %z", "%s.%q %z", "%s%Q %z"] + ["%a, %d %b %Y %H:%M:%S.%q %z", "%a, %d %b %Y %H:%M:%S%Q %z", "%s.%q %z", "%s%Q %z", + "%a, %d %b %Y %H:%M:%S.%q %Z", "%a, %d %b %Y %H:%M:%S%Q %Z", "%s.%q %Z", "%s%Q %Z"] utcTimeFormats :: [FormatString UTCTime] utcTimeFormats = map FormatString @@ -279,7 +279,7 @@ utcTimeFormats = map FormatString partialDayFormats :: [FormatString Day] partialDayFormats = map FormatString - [ ] + [ ] partialTimeOfDayFormats :: [FormatString TimeOfDay] partialTimeOfDayFormats = map FormatString @@ -292,16 +292,13 @@ partialLocalTimeFormats = map FormatString "%c" ] -partialTimeZoneFormats :: [FormatString TimeZone] -partialTimeZoneFormats = map FormatString - [ - ] - partialZonedTimeFormats :: [FormatString ZonedTime] partialZonedTimeFormats = map FormatString [ -- %s does not include second decimals - "%s %z" + "%s %z", + -- %S does not include second decimals + "%c", "%a, %d %b %Y %H:%M:%S %Z" ] partialUTCTimeFormats :: [FormatString UTCTime] @@ -320,47 +317,13 @@ partialUTCTimeFormats = map FormatString knownFailures :: [NamedProperty] knownFailures = - map (prop_parse_format_named "Day") failingDayFormats - ++ map (prop_parse_format_named "LocalTime") failingLocalTimeFormats - ++ map (prop_parse_format_named "TimeZone") failingTimeZoneFormats - ++ map (prop_parse_format_named "ZonedTime") failingZonedTimeFormats - ++ map (prop_parse_format_named "UTCTime") failingUTCTimeFormats - + map (prop_format_parse_format_named "Day") failingPartialDayFormats - - -failingDayFormats :: [FormatString Day] -failingDayFormats = map FormatString - [ -- ISO week dates with two digit year +failingPartialDayFormats :: [FormatString Day] +failingPartialDayFormats = map FormatString + [ -- ISO week dates with two digit year. + -- This can fail in the beginning or the end of a year where + -- the ISO week date year does not match the gregorian year. "%g-%V-%u","%g-%V-%a","%g-%V-%A","%g-%V-%w", "%A week %V, %g", "day %V, week %A, %g", "%g-W%V-%u" ] - -failingTimeOfDayFormats :: [FormatString TimeOfDay] -failingTimeOfDayFormats = map FormatString - [ ] - -failingLocalTimeFormats :: [FormatString LocalTime] -failingLocalTimeFormats = map FormatString - [ - ] - -failingTimeZoneFormats :: [FormatString TimeZone] -failingTimeZoneFormats = map FormatString - [ - -- %Z does not figure out the offset - "%Z" - ] - -failingZonedTimeFormats :: [FormatString ZonedTime] -failingZonedTimeFormats = map FormatString - [ - -- can't figure out offset from %Z, also, formatTime produces "" for %Z - "%c", - "%a, %d %b %Y %H:%M:%S %Z" - ] - -failingUTCTimeFormats :: [FormatString UTCTime] -failingUTCTimeFormats = map FormatString - [] - From git at git.haskell.org Fri Jan 23 22:57:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:54 +0000 (UTC) Subject: [commit: packages/time] master: move parsing and formatting into new module (48535e6) Message-ID: <20150123225754.546573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/48535e6a2a85ec5545a1ff30d9f27087108bbc57 >--------------------------------------------------------------- commit 48535e6a2a85ec5545a1ff30d9f27087108bbc57 Author: Ashley Yakeley Date: Tue Feb 13 19:59:07 2007 -0800 move parsing and formatting into new module darcs-hash:20070214035907-ac6dd-25a86dd8e9d5313cc998c300f9c524d4652749bf >--------------------------------------------------------------- 48535e6a2a85ec5545a1ff30d9f27087108bbc57 Data/Time.hs | 4 +++- Data/Time/{LocalTime => }/Format.hs | 11 +++++------ Data/Time/{LocalTime => Format}/Parse.hs | 11 ++++------- Data/Time/LocalTime.hs | 6 +----- test/TestEaster.hs | 2 +- time.cabal | 4 ++-- time.xcodeproj/project.pbxproj | 12 ++++++++++-- 7 files changed, 26 insertions(+), 24 deletions(-) diff --git a/Data/Time.hs b/Data/Time.hs index 65926cd..4167ec6 100644 --- a/Data/Time.hs +++ b/Data/Time.hs @@ -4,9 +4,11 @@ module Data.Time ( module Data.Time.Calendar, module Data.Time.Clock, - module Data.Time.LocalTime + module Data.Time.LocalTime, + module Data.Time.Format ) where import Data.Time.Calendar import Data.Time.Clock import Data.Time.LocalTime +import Data.Time.Format diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/Format.hs similarity index 97% rename from Data/Time/LocalTime/Format.hs rename to Data/Time/Format.hs index 61a4e90..64f73ef 100644 --- a/Data/Time/LocalTime/Format.hs +++ b/Data/Time/Format.hs @@ -1,15 +1,14 @@ {-# OPTIONS -Wall -Werror #-} --- #hide -module Data.Time.LocalTime.Format +module Data.Time.Format ( -- * UNIX-style formatting - module Data.Time.LocalTime.Format + module Data.Time.Format, + module Data.Time.Format.Parse ) where -import Data.Time.LocalTime.LocalTime -import Data.Time.LocalTime.TimeOfDay -import Data.Time.LocalTime.TimeZone +import Data.Time.Format.Parse +import Data.Time.LocalTime import Data.Time.Calendar.WeekDate import Data.Time.Calendar.OrdinalDate import Data.Time.Calendar diff --git a/Data/Time/LocalTime/Parse.hs b/Data/Time/Format/Parse.hs similarity index 98% rename from Data/Time/LocalTime/Parse.hs rename to Data/Time/Format/Parse.hs index 605eee9..bee16e8 100644 --- a/Data/Time/LocalTime/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -1,7 +1,7 @@ {-# OPTIONS -Wall -Werror #-} -- #hide -module Data.Time.LocalTime.Parse +module Data.Time.Format.Parse ( -- * UNIX-style parsing parseTime, readTime, readsTime, @@ -9,14 +9,11 @@ module Data.Time.LocalTime.Parse ) where import Data.Time.Clock.POSIX -import Data.Time.Clock.UTC -import Data.Time.Calendar.Days -import Data.Time.Calendar.Gregorian +import Data.Time.Clock +import Data.Time.Calendar import Data.Time.Calendar.OrdinalDate import Data.Time.Calendar.WeekDate -import Data.Time.LocalTime.LocalTime -import Data.Time.LocalTime.TimeOfDay -import Data.Time.LocalTime.TimeZone +import Data.Time.LocalTime import Control.Monad import Data.Char diff --git a/Data/Time/LocalTime.hs b/Data/Time/LocalTime.hs index a5e2943..5676b58 100644 --- a/Data/Time/LocalTime.hs +++ b/Data/Time/LocalTime.hs @@ -4,13 +4,9 @@ module Data.Time.LocalTime ( module Data.Time.LocalTime.TimeZone, module Data.Time.LocalTime.TimeOfDay, - module Data.Time.LocalTime.LocalTime, - module Data.Time.LocalTime.Format, - module Data.Time.LocalTime.Parse + module Data.Time.LocalTime.LocalTime ) where import Data.Time.LocalTime.TimeZone import Data.Time.LocalTime.TimeOfDay import Data.Time.LocalTime.LocalTime -import Data.Time.LocalTime.Format -import Data.Time.LocalTime.Parse diff --git a/test/TestEaster.hs b/test/TestEaster.hs index 86a3318..290c066 100644 --- a/test/TestEaster.hs +++ b/test/TestEaster.hs @@ -4,7 +4,7 @@ module Main where import Data.Time.Calendar.Easter import Data.Time.Calendar -import Data.Time.LocalTime +import Data.Time.Format import System.Locale diff --git a/time.cabal b/time.cabal index a4fae43..c45da8c 100644 --- a/time.cabal +++ b/time.cabal @@ -20,6 +20,7 @@ Exposed-Modules: Data.Time.Clock.POSIX, Data.Time.Clock.TAI, Data.Time.LocalTime, + Data.Time.Format, Data.Time Extensions: ForeignFunctionInterface, CPP C-Sources: cbits/HsTime.c @@ -35,8 +36,7 @@ Other-Modules: Data.Time.LocalTime.TimeZone, Data.Time.LocalTime.TimeOfDay, Data.Time.LocalTime.LocalTime, - Data.Time.LocalTime.Format, - Data.Time.LocalTime.Parse + Data.Time.Format.Parse Extra-Source-Files: aclocal.m4 configure.ac configure include/HsTime.h include/HsTimeConfig.h.in diff --git a/time.xcodeproj/project.pbxproj b/time.xcodeproj/project.pbxproj index ee8c7d6..e7fab3a 100644 --- a/time.xcodeproj/project.pbxproj +++ b/time.xcodeproj/project.pbxproj @@ -130,6 +130,8 @@ ABD6783C0841677900CF37C0 /* Clock */, AB01DCFD08374838003C9EF7 /* Clock.hs */, AB2666A808A56FE30059DEC0 /* LocalTime */, + ABD4B1320B82BCA100CEB254 /* Format */, + AB01DD13083748EC003C9EF7 /* Format.hs */, AB2666E808A571460059DEC0 /* LocalTime.hs */, ); path = Time; @@ -157,8 +159,6 @@ AB01DD18083748EC003C9EF7 /* TimeZone.hs */, AB01DD17083748EC003C9EF7 /* TimeOfDay.hs */, AB01DD12083748EC003C9EF7 /* LocalTime.hs */, - AB01DD13083748EC003C9EF7 /* Format.hs */, - ABD6AC650B2D52D400843342 /* Parse.hs */, ); path = LocalTime; sourceTree = ""; @@ -197,6 +197,14 @@ name = "GHC stuff"; sourceTree = ""; }; + ABD4B1320B82BCA100CEB254 /* Format */ = { + isa = PBXGroup; + children = ( + ABD6AC650B2D52D400843342 /* Parse.hs */, + ); + path = Format; + sourceTree = ""; + }; ABD6783C0841677900CF37C0 /* Clock */ = { isa = PBXGroup; children = ( From git at git.haskell.org Fri Jan 23 22:57:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:56 +0000 (UTC) Subject: [commit: packages/time] master: README about building from darcs (09c85ef) Message-ID: <20150123225756.5B63F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/09c85ef703705f311b49ea7e7291a80c3a452d49 >--------------------------------------------------------------- commit 09c85ef703705f311b49ea7e7291a80c3a452d49 Author: Ross Paterson Date: Sun Feb 18 03:01:59 2007 -0800 README about building from darcs darcs-hash:20070218110159-b47d3-02982554bbac9710b4ad35c5d4de873c6c0f693f >--------------------------------------------------------------- 09c85ef703705f311b49ea7e7291a80c3a452d49 README | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README b/README new file mode 100644 index 0000000..f5aa1cf --- /dev/null +++ b/README @@ -0,0 +1,4 @@ +To build this package using Cabal directly from darcs, you must run +"autoreconf" before the usual Cabal build steps (configure/build/install). +autoreconf is included in the GNU autoconf tools. There is no need to run +the "configure" script: the "setup configure" step will do this for you. From git at git.haskell.org Fri Jan 23 22:57:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:57:58 +0000 (UTC) Subject: [commit: packages/time] master: version 1.1 (28d5ef3) Message-ID: <20150123225758.62EA33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/28d5ef3d018b1650652d25d6be07e5b3749dc6b3 >--------------------------------------------------------------- commit 28d5ef3d018b1650652d25d6be07e5b3749dc6b3 Author: Ashley Yakeley Date: Mon Feb 19 17:52:51 2007 -0800 version 1.1 darcs-hash:20070220015251-ac6dd-223729392751ba0ef63dda315df9cd5263dbadc4 >--------------------------------------------------------------- 28d5ef3d018b1650652d25d6be07e5b3749dc6b3 Makefile | 2 +- configure.ac | 2 +- time.cabal | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/Makefile b/Makefile index 76ea560..9fca5cd 100644 --- a/Makefile +++ b/Makefile @@ -12,7 +12,7 @@ ALL_DIRS = \ Data/Time/LocalTime PACKAGE = time -VERSION = 1.0 +VERSION = 1.1 PACKAGE_DEPS = base SRC_HC_OPTS += -Wall -Werror -fffi -Iinclude diff --git a/configure.ac b/configure.ac index f2e4186..5778502 100644 --- a/configure.ac +++ b/configure.ac @@ -1,4 +1,4 @@ -AC_INIT([Haskell time package], [0.3.1], [ashley at semantic.org], [time]) +AC_INIT([Haskell time package], [1.1], [ashley at semantic.org], [time]) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([include/HsTime.h]) diff --git a/time.cabal b/time.cabal index c45da8c..d877a1b 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ Name: time -Version: 1.0 +Version: 1.1 Stability: stable License: BSD3 License-File: LICENSE From git at git.haskell.org Fri Jan 23 22:58:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:00 +0000 (UTC) Subject: [commit: packages/time] master: clean up HsTime (696f384) Message-ID: <20150123225800.6ADBE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/696f384f00c6a33e0114fe30cd3a80e2e93dc3dc >--------------------------------------------------------------- commit 696f384f00c6a33e0114fe30cd3a80e2e93dc3dc Author: Ashley Yakeley Date: Mon Feb 19 18:01:29 2007 -0800 clean up HsTime darcs-hash:20070220020129-ac6dd-8b7a4cfbded155623c93ee1b26bafe5f801fd1c6 >--------------------------------------------------------------- 696f384f00c6a33e0114fe30cd3a80e2e93dc3dc cbits/HsTime.c | 44 ++++++++++++++++---------------------------- include/HsTime.h | 2 +- 2 files changed, 17 insertions(+), 29 deletions(-) diff --git a/cbits/HsTime.c b/cbits/HsTime.c index f9651e9..58b7d06 100644 --- a/cbits/HsTime.c +++ b/cbits/HsTime.c @@ -3,50 +3,38 @@ long int get_current_timezone_seconds (time_t t,int* pdst,char const* * pname) { - struct tm* ptm; - long gmtoff; - int dst; - const char *name; - #if HAVE_LOCALTIME_R struct tm tmd; - ptm = localtime_r(&t,&tmd); + struct tm* ptm = localtime_r(&t,&tmd); #else - ptm = localtime(&t); + struct tm* ptm = localtime(&t); #endif - // We don't have a better API to use on Windows, the logic to - // decide whether a given data/time falls within DST is - // implemented as part of localtime() in the CRT. This is_dst - // flag is all we need here. - if (ptm) { - dst = ptm -> tm_isdst; + int dst = ptm -> tm_isdst; + *pdst = dst; #if HAVE_TM_ZONE - name = ptm -> tm_zone; - gmtoff = ptm -> tm_gmtoff; + *pname = ptm -> tm_zone; + return ptm -> tm_gmtoff; #elif defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32) - name = dst ? _tzname[1] : _tzname[0]; - gmtoff = dst ? _timezone - 3600 : _timezone; + // We don't have a better API to use on Windows, the logic to + // decide whether a given date/time falls within DST is + // implemented as part of localtime() in the CRT. This is_dst + // flag is all we need here. + *pname = dst ? _tzname[1] : _tzname[0]; + return dst ? _timezone - 3600 : _timezone; #else - # if HAVE_TZNAME - name = *tzname; + *pname = *tzname; # else -# error "Don't know how to get at timezone name on your OS" +# error "Don't know how to get timezone name on your OS" # endif - # if HAVE_DECL_ALTZONE - gmtoff = dst ? altzone : timezone; + return dst ? altzone : timezone; # else - gmtoff = dst ? timezone - 3600 : timezone; + return dst ? timezone - 3600 : timezone; # endif - #endif // HAVE_TM_ZONE - *pdst = dst; - *pname = name; - return gmtoff; - } else return 0x80000000; } diff --git a/include/HsTime.h b/include/HsTime.h index b8da946..059cbc0 100644 --- a/include/HsTime.h +++ b/include/HsTime.h @@ -7,6 +7,6 @@ #include #endif -long int get_current_timezone_seconds (time_t,int* dst,char const* * name); +long int get_current_timezone_seconds (time_t,int* pdst,char const* * pname); #endif From git at git.haskell.org Fri Jan 23 22:58:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:02 +0000 (UTC) Subject: [commit: packages/time] master: build/license/boring cleanup (cc9a460) Message-ID: <20150123225802.71A5D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/cc9a460009cf283c0e533ac051967a363842b1db >--------------------------------------------------------------- commit cc9a460009cf283c0e533ac051967a363842b1db Author: Ashley Yakeley Date: Thu Feb 22 16:33:26 2007 -0800 build/license/boring cleanup darcs-hash:20070223003326-ac6dd-68918006d98d55eea314ccedb36a5b24de0d509b >--------------------------------------------------------------- cc9a460009cf283c0e533ac051967a363842b1db .darcs-boring | 23 +++++++++++++++++++++++ LICENSE | 2 +- package.conf.in | 14 ++++++++------ 3 files changed, 32 insertions(+), 7 deletions(-) diff --git a/.darcs-boring b/.darcs-boring index 6c379a9..0b4f6cb 100644 --- a/.darcs-boring +++ b/.darcs-boring @@ -11,6 +11,7 @@ _split$ (^|/)package.conf.installed$ (^|/)\.depend$ (^|/)\.setup-config$ +(^|/)\.installed-pkg-config$ \.haddock$ ^build$ \.xcodeproj/.*\.pbxuser$ @@ -43,4 +44,26 @@ _split$ \.py[co]$ \# \.cvsignore$ +^Private($|/) (^|/)Thumbs\.db$ +^configure$ +^config\..*$ +^autom4te.cache($|/) +^include/HsTimeConfig\.h$ +^include/HsTimeConfig\.h.in$ +^test/.*\.out$ +^test/AddDays$ +^test/ClipDates$ +^test/ConvertBack$ +^test/CurrentTime$ +^test/LongWeekYears$ +^test/ShowDST$ +^test/TestCalendars$ +^test/TestEaster$ +^test/TestFormat$ +^test/TestMonthDay$ +^test/TestParseDAT$ +^test/TestParseTime$ +^test/TestTime$ +^test/TimeZone$ +^test/TimeZone.ref$ diff --git a/LICENSE b/LICENSE index 17f1f27..af649fe 100644 --- a/LICENSE +++ b/LICENSE @@ -1,4 +1,4 @@ -TimeLib is Copyright (c) Ashley Yakeley, 2004-2005. +TimeLib is Copyright (c) Ashley Yakeley, 2004-2007. All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: diff --git a/package.conf.in b/package.conf.in index 98922d7..fc3bf80 100644 --- a/package.conf.in +++ b/package.conf.in @@ -2,7 +2,7 @@ Name: PACKAGE Version: VERSION -Stability: Beta +Stability: stable License: BSD3 License-File: LICENSE Author: Ashley Yakeley @@ -29,10 +29,11 @@ Exposed-modules: Data.Time.Clock.POSIX, Data.Time.Clock.TAI, Data.Time.LocalTime, + Data.Time.Format, Data.Time -Extensions: ForeignFunctionInterface -C-Sources: HsTime.c -Hidden-modules: +Extensions: ForeignFunctionInterface, CPP +C-Sources: cbits/HsTime.c +Other-Modules: Data.Time.Calendar.Private, Data.Time.Calendar.Days, Data.Time.Calendar.Gregorian, @@ -44,11 +45,12 @@ Hidden-modules: Data.Time.LocalTime.TimeZone, Data.Time.LocalTime.TimeOfDay, Data.Time.LocalTime.LocalTime, - Data.Time.LocalTime.Format + Data.Time.Format.Parse import-dirs: IMPORT_DIR library-dirs: LIB_DIR hs-libraries: "HStime" include-dirs: INCLUDE_DIR -includes: "HsTime.h" +Install-Includes: + HsTime.h HsTimeConfig.h haddock-interfaces: HADDOCK_IFACE haddock-html: HTML_DIR From git at git.haskell.org Fri Jan 23 22:58:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:04 +0000 (UTC) Subject: [commit: packages/time] master: Fixed hyperlinks to formatTime (7053937) Message-ID: <20150123225804.7AA233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/7053937ced02dbed6684556445211d094bb61c4b >--------------------------------------------------------------- commit 7053937ced02dbed6684556445211d094bb61c4b Author: sven.panne Date: Thu Mar 22 10:02:58 2007 -0700 Fixed hyperlinks to formatTime darcs-hash:20070322170258-96103-bd25d42aa6fa7432c891d28a9032b103f3cc53f3 >--------------------------------------------------------------- 7053937ced02dbed6684556445211d094bb61c4b Data/Time/Calendar/OrdinalDate.hs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/Data/Time/Calendar/OrdinalDate.hs b/Data/Time/Calendar/OrdinalDate.hs index dfd4069..9dbdd96 100644 --- a/Data/Time/Calendar/OrdinalDate.hs +++ b/Data/Time/Calendar/OrdinalDate.hs @@ -38,8 +38,8 @@ isLeapYear :: Integer -> Bool isLeapYear year = (mod year 4 == 0) && ((mod year 400 == 0) || not (mod year 100 == 0)) -- | Get the number of the Monday-starting week in the year and the day of the week. --- The first Monday is the first day of week 1, any earlier days in the year are week 0 (as \"%W\" in formatTime). --- Monday is 1, Sunday is 7 (as \"%u\" in formatTime). +-- The first Monday is the first day of week 1, any earlier days in the year are week 0 (as \"%W\" in 'Data.Time.Format.formatTime'). +-- Monday is 1, Sunday is 7 (as \"%u\" in 'Data.Time.Format.formatTime'). mondayStartWeek :: Day -> (Int,Int) mondayStartWeek date = (fromInteger ((div d 7) - (div k 7)),fromInteger (mod d 7) + 1) where yd = snd (toOrdinalDate date) @@ -47,8 +47,8 @@ mondayStartWeek date = (fromInteger ((div d 7) - (div k 7)),fromInteger (mod d 7 k = d - (toInteger yd) -- | Get the number of the Sunday-starting week in the year and the day of the week. --- The first Sunday is the first day of week 1, any earlier days in the year are week 0 (as \"%U\" in formatTime). --- Sunday is 0, Saturday is 6 (as \"%w\" in formatTime). +-- The first Sunday is the first day of week 1, any earlier days in the year are week 0 (as \"%U\" in 'Data.Time.Format.formatTime'). +-- Sunday is 0, Saturday is 6 (as \"%w\" in 'Data.Time.Format.formatTime'). sundayStartWeek :: Day -> (Int,Int) sundayStartWeek date =(fromInteger ((div d 7) - (div k 7)),fromInteger (mod d 7)) where yd = snd (toOrdinalDate date) @@ -58,11 +58,11 @@ sundayStartWeek date =(fromInteger ((div d 7) - (div k 7)),fromInteger (mod d 7) -- | The inverse of 'mondayStartWeek'. Get a 'Day' given the year, -- the number of the Monday-starting week, and the day of the week. -- The first Monday is the first day of week 1, any earlier days in the year --- are week 0 (as \"%W\" in 'formatTime'). +-- are week 0 (as \"%W\" in 'Data.Time.Format.formatTime'). fromMondayStartWeek :: Integer -- ^ Year. -> Int -- ^ Monday-starting week number. -> Int -- ^ Day of week. - -- Monday is 1, Sunday is 7 (as \"%u\" in 'formatTime'). + -- Monday is 1, Sunday is 7 (as \"%u\" in 'Data.Time.Format.formatTime'). -> Day fromMondayStartWeek y w d = ModifiedJulianDay (firstDay + yd) where yd = firstMonday + 7 * toInteger (w-1) + toInteger d - 1 @@ -74,11 +74,11 @@ fromMondayStartWeek y w d = ModifiedJulianDay (firstDay + yd) -- | The inverse of 'sundayStartWeek'. Get a 'Day' given the year and -- the number of the day of a Sunday-starting week. -- The first Sunday is the first day of week 1, any earlier days in the --- year are week 0 (as \"%U\" in 'formatTime'). +-- year are week 0 (as \"%U\" in 'Data.Time.Format.formatTime'). fromSundayStartWeek :: Integer -- ^ Year. -> Int -- ^ Sunday-starting week number. -> Int -- ^ Day of week - -- Sunday is 0, Saturday is 6 (as \"%w\" in 'formatTime'). + -- Sunday is 0, Saturday is 6 (as \"%w\" in 'Data.Time.Format.formatTime'). -> Day fromSundayStartWeek y w d = ModifiedJulianDay (firstDay + yd) where yd = firstSunday + 7 * toInteger (w-1) + toInteger d From git at git.haskell.org Fri Jan 23 22:58:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:06 +0000 (UTC) Subject: [commit: packages/time] master: Added missing directory (a293612) Message-ID: <20150123225806.817193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/a29361230de31e0d0fc6acb6b3e4c185f683463c >--------------------------------------------------------------- commit a29361230de31e0d0fc6acb6b3e4c185f683463c Author: sven.panne Date: Thu Mar 22 10:26:49 2007 -0700 Added missing directory darcs-hash:20070322172649-96103-35df5e909f8a7d8bb1158a45cc50110b24aa7c4f >--------------------------------------------------------------- a29361230de31e0d0fc6acb6b3e4c185f683463c Makefile | 1 + 1 file changed, 1 insertion(+) diff --git a/Makefile b/Makefile index 9fca5cd..8c4e8f5 100644 --- a/Makefile +++ b/Makefile @@ -9,6 +9,7 @@ ALL_DIRS = \ Data/Time \ Data/Time/Calendar \ Data/Time/Clock \ + Data/Time/Format \ Data/Time/LocalTime PACKAGE = time From git at git.haskell.org Fri Jan 23 22:58:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:08 +0000 (UTC) Subject: [commit: packages/time] master: Make Setup.hs suitable for building in a GHC tree (2f507d7) Message-ID: <20150123225808.878853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2f507d73fbd98f417b70fd4ce01c1108c211847e >--------------------------------------------------------------- commit 2f507d73fbd98f417b70fd4ce01c1108c211847e Author: Ian Lynagh Date: Sat Apr 7 10:41:49 2007 -0700 Make Setup.hs suitable for building in a GHC tree darcs-hash:20070407174149-3fd76-51c9fae37e93e4f367400b38078fc490266864f0 >--------------------------------------------------------------- 2f507d73fbd98f417b70fd4ce01c1108c211847e Setup.hs | 68 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++-------- 1 file changed, 60 insertions(+), 8 deletions(-) diff --git a/Setup.hs b/Setup.hs index 2859262..9ef61d3 100644 --- a/Setup.hs +++ b/Setup.hs @@ -1,21 +1,73 @@ module Main (main) where +import Control.Exception +import Data.List import Distribution.Simple import Distribution.PackageDescription +import Distribution.PreProcess +import Distribution.Setup import Distribution.Simple.LocalBuildInfo -import System.Exit import System.Cmd import System.Directory -import Control.Exception +import System.Environment +import System.Exit + +main :: IO () +main = do args <- getArgs + let (ghcArgs, args') = extractGhcArgs args + (_, args'') = extractConfigureArgs args' + hooks = defaultUserHooks { + buildHook = add_ghc_options ghcArgs + $ buildHook defaultUserHooks, + runTests = runTestScript } + withArgs args'' $ defaultMainWithHooks hooks withCurrentDirectory :: FilePath -> IO a -> IO a withCurrentDirectory path f = do - cur <- getCurrentDirectory - setCurrentDirectory path - finally f (setCurrentDirectory cur) + cur <- getCurrentDirectory + setCurrentDirectory path + finally f (setCurrentDirectory cur) -runTestScript :: Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO ExitCode +runTestScript :: Args -> Bool -> PackageDescription -> LocalBuildInfo + -> IO ExitCode runTestScript args flag pd lbi = withCurrentDirectory "test" (system "make") -main :: IO () -main = defaultMainWithHooks defaultUserHooks{runTests = runTestScript} +extractGhcArgs :: [String] -> ([String], [String]) +extractGhcArgs = extractPrefixArgs "--ghc-option=" + +extractConfigureArgs :: [String] -> ([String], [String]) +extractConfigureArgs = extractPrefixArgs "--configure-option=" + +extractPrefixArgs :: String -> [String] -> ([String], [String]) +extractPrefixArgs prefix args + = let f [] = ([], []) + f (x:xs) = case f xs of + (wantedArgs, otherArgs) -> + case removePrefix prefix x of + Just wantedArg -> + (wantedArg:wantedArgs, otherArgs) + Nothing -> + (wantedArgs, x:otherArgs) + in f args + +removePrefix :: String -> String -> Maybe String +removePrefix "" ys = Just ys +removePrefix (x:xs) (y:ys) + | x == y = removePrefix xs ys + | otherwise = Nothing + +type Hook a = PackageDescription -> LocalBuildInfo -> Maybe UserHooks -> a + -> IO () + +add_ghc_options :: [String] -> Hook a -> Hook a +add_ghc_options args f pd lbi muhs x + = do let lib' = case library pd of + Just lib -> + let bi = libBuildInfo lib + opts = options bi ++ [(GHC, args)] + bi' = bi { options = opts } + in lib { libBuildInfo = bi' } + Nothing -> error "Expected a library" + pd' = pd { library = Just lib' } + f pd' lbi muhs x + From git at git.haskell.org Fri Jan 23 22:58:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:10 +0000 (UTC) Subject: [commit: packages/time] master: Fix -Wall warnings (ae16651) Message-ID: <20150123225810.8E40F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ae16651f2429c01af64184318d06bed2023cd380 >--------------------------------------------------------------- commit ae16651f2429c01af64184318d06bed2023cd380 Author: Ian Lynagh Date: Tue Apr 10 18:22:40 2007 -0700 Fix -Wall warnings darcs-hash:20070411012240-3fd76-b092e0f174e882a180df231c955a3456d2ddeb65 >--------------------------------------------------------------- ae16651f2429c01af64184318d06bed2023cd380 Setup.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/Setup.hs b/Setup.hs index 9ef61d3..3c31867 100644 --- a/Setup.hs +++ b/Setup.hs @@ -4,7 +4,6 @@ import Control.Exception import Data.List import Distribution.Simple import Distribution.PackageDescription -import Distribution.PreProcess import Distribution.Setup import Distribution.Simple.LocalBuildInfo import System.Cmd @@ -30,7 +29,8 @@ withCurrentDirectory path f = do runTestScript :: Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO ExitCode -runTestScript args flag pd lbi = withCurrentDirectory "test" (system "make") +runTestScript _args _flag _pd _lbi + = withCurrentDirectory "test" (system "make") extractGhcArgs :: [String] -> ([String], [String]) extractGhcArgs = extractPrefixArgs "--ghc-option=" @@ -39,11 +39,11 @@ extractConfigureArgs :: [String] -> ([String], [String]) extractConfigureArgs = extractPrefixArgs "--configure-option=" extractPrefixArgs :: String -> [String] -> ([String], [String]) -extractPrefixArgs prefix args +extractPrefixArgs the_prefix args = let f [] = ([], []) f (x:xs) = case f xs of (wantedArgs, otherArgs) -> - case removePrefix prefix x of + case removePrefix the_prefix x of Just wantedArg -> (wantedArg:wantedArgs, otherArgs) Nothing -> @@ -52,6 +52,7 @@ extractPrefixArgs prefix args removePrefix :: String -> String -> Maybe String removePrefix "" ys = Just ys +removePrefix _ "" = Nothing removePrefix (x:xs) (y:ys) | x == y = removePrefix xs ys | otherwise = Nothing From git at git.haskell.org Fri Jan 23 22:58:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:12 +0000 (UTC) Subject: [commit: packages/time] master: Hack due to time needing Win32 on Windows (dbd2265) Message-ID: <20150123225812.950D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/dbd22650b674227dff9c45c53e921367441fdc99 >--------------------------------------------------------------- commit dbd22650b674227dff9c45c53e921367441fdc99 Author: Ian Lynagh Date: Sun Apr 15 14:52:27 2007 -0700 Hack due to time needing Win32 on Windows darcs-hash:20070415215227-3fd76-ee66b60c836f81fa879ba9e80220fac57f47e261 >--------------------------------------------------------------- dbd22650b674227dff9c45c53e921367441fdc99 Setup.hs | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/Setup.hs b/Setup.hs index 3c31867..f078742 100644 --- a/Setup.hs +++ b/Setup.hs @@ -10,12 +10,15 @@ import System.Cmd import System.Directory import System.Environment import System.Exit +import System.Info main :: IO () main = do args <- getArgs let (ghcArgs, args') = extractGhcArgs args (_, args'') = extractConfigureArgs args' hooks = defaultUserHooks { + confHook = add_Win32_dep + $ confHook defaultUserHooks, buildHook = add_ghc_options ghcArgs $ buildHook defaultUserHooks, runTests = runTestScript } @@ -72,3 +75,14 @@ add_ghc_options args f pd lbi muhs x pd' = pd { library = Just lib' } f pd' lbi muhs x +type ConfHook = PackageDescription -> ConfigFlags -> IO LocalBuildInfo + +-- XXX Hideous hack +add_Win32_dep :: ConfHook -> ConfHook +add_Win32_dep f pd cf + = do let pd' = if os == "mingw32" + then pd { buildDepends = Dependency "Win32" AnyVersion + : buildDepends pd } + else pd + f pd' cf + From git at git.haskell.org Fri Jan 23 22:58:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:14 +0000 (UTC) Subject: [commit: packages/time] master: Follow Cabal changes in Setup.*hs (fae8a55) Message-ID: <20150123225814.9D3833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/fae8a5587481b1ae3da17c49d04cc0ab89ed8ca6 >--------------------------------------------------------------- commit fae8a5587481b1ae3da17c49d04cc0ab89ed8ca6 Author: Ian Lynagh Date: Wed Apr 18 05:14:32 2007 -0700 Follow Cabal changes in Setup.*hs darcs-hash:20070418121432-3fd76-50d82afe568d115252a1a061ee8e8cb581e2bebc >--------------------------------------------------------------- fae8a5587481b1ae3da17c49d04cc0ab89ed8ca6 Setup.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/Setup.hs b/Setup.hs index f078742..caecfdd 100644 --- a/Setup.hs +++ b/Setup.hs @@ -9,7 +9,6 @@ import Distribution.Simple.LocalBuildInfo import System.Cmd import System.Directory import System.Environment -import System.Exit import System.Info main :: IO () @@ -31,7 +30,7 @@ withCurrentDirectory path f = do finally f (setCurrentDirectory cur) runTestScript :: Args -> Bool -> PackageDescription -> LocalBuildInfo - -> IO ExitCode + -> IO () runTestScript _args _flag _pd _lbi = withCurrentDirectory "test" (system "make") @@ -60,11 +59,10 @@ removePrefix (x:xs) (y:ys) | x == y = removePrefix xs ys | otherwise = Nothing -type Hook a = PackageDescription -> LocalBuildInfo -> Maybe UserHooks -> a - -> IO () +type Hook a = PackageDescription -> LocalBuildInfo -> UserHooks -> a -> IO () add_ghc_options :: [String] -> Hook a -> Hook a -add_ghc_options args f pd lbi muhs x +add_ghc_options args f pd lbi uhs x = do let lib' = case library pd of Just lib -> let bi = libBuildInfo lib @@ -73,7 +71,7 @@ add_ghc_options args f pd lbi muhs x in lib { libBuildInfo = bi' } Nothing -> error "Expected a library" pd' = pd { library = Just lib' } - f pd' lbi muhs x + f pd' lbi uhs x type ConfHook = PackageDescription -> ConfigFlags -> IO LocalBuildInfo From git at git.haskell.org Fri Jan 23 22:58:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:16 +0000 (UTC) Subject: [commit: packages/time] master: We now need to check the exitcode of the tests (ccb1264) Message-ID: <20150123225816.A95143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ccb1264e93dfa379d26368677aa05ec3b7ec34c2 >--------------------------------------------------------------- commit ccb1264e93dfa379d26368677aa05ec3b7ec34c2 Author: Ian Lynagh Date: Sat Apr 21 09:23:30 2007 -0700 We now need to check the exitcode of the tests darcs-hash:20070421162330-3fd76-36ce113c06f673ae509deac9eb047e5f539a69c5 >--------------------------------------------------------------- ccb1264e93dfa379d26368677aa05ec3b7ec34c2 Setup.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/Setup.hs b/Setup.hs index caecfdd..d2fff29 100644 --- a/Setup.hs +++ b/Setup.hs @@ -2,10 +2,11 @@ module Main (main) where import Control.Exception import Data.List -import Distribution.Simple import Distribution.PackageDescription import Distribution.Setup +import Distribution.Simple import Distribution.Simple.LocalBuildInfo +import Distribution.Simple.Utils import System.Cmd import System.Directory import System.Environment @@ -29,10 +30,9 @@ withCurrentDirectory path f = do setCurrentDirectory path finally f (setCurrentDirectory cur) -runTestScript :: Args -> Bool -> PackageDescription -> LocalBuildInfo - -> IO () +runTestScript :: Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO () runTestScript _args _flag _pd _lbi - = withCurrentDirectory "test" (system "make") + = maybeExit $ withCurrentDirectory "test" $ system "make" extractGhcArgs :: [String] -> ([String], [String]) extractGhcArgs = extractPrefixArgs "--ghc-option=" From git at git.haskell.org Fri Jan 23 22:58:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:20 +0000 (UTC) Subject: [commit: packages/time] master: Remove Makefile and package.conf.in (used in the old GHC build system) (ef82b6f) Message-ID: <20150123225820.B27A13A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ef82b6ff52f984bb55c26ef10624adc218a18f98 >--------------------------------------------------------------- commit ef82b6ff52f984bb55c26ef10624adc218a18f98 Author: Ian Lynagh Date: Thu May 24 07:58:37 2007 -0700 Remove Makefile and package.conf.in (used in the old GHC build system) darcs-hash:20070524145837-3fd76-402cae7ffe2155bdb3ef4b1a3081935c74e66f32 >--------------------------------------------------------------- ef82b6ff52f984bb55c26ef10624adc218a18f98 Makefile | 29 ----------------------------- package.conf.in | 56 -------------------------------------------------------- 2 files changed, 85 deletions(-) diff --git a/Makefile b/Makefile deleted file mode 100644 index 9f61dd2..0000000 --- a/Makefile +++ /dev/null @@ -1,29 +0,0 @@ -TOP=.. -include $(TOP)/mk/boilerplate.mk - -SUBDIRS = include - -ALL_DIRS = \ - cbits \ - Data \ - Data/Time \ - Data/Time/Calendar \ - Data/Time/Clock \ - Data/Time/Format \ - Data/Time/LocalTime - -PACKAGE = time -VERSION = 1.1.1 -PACKAGE_DEPS = base - -SRC_HC_OPTS += -Wall -Werror -fffi -Iinclude - -SRC_CC_OPTS += -Wall -Werror -Iinclude - -EXCLUDED_SRCS += Setup.hs - -SRC_HADDOCK_OPTS += -t "Haskell Hierarchical Libraries ($(PACKAGE) package)" - -UseGhcForCc = YES - -include $(TOP)/mk/target.mk diff --git a/package.conf.in b/package.conf.in deleted file mode 100644 index fc3bf80..0000000 --- a/package.conf.in +++ /dev/null @@ -1,56 +0,0 @@ -#include "ghcconfig.h" - -Name: PACKAGE -Version: VERSION -Stability: stable -License: BSD3 -License-File: LICENSE -Author: Ashley Yakeley -Maintainer: -Homepage: http://semantic.org/TimeLib/ -exposed: True -Category: - -#if mingw32_HOST_OS -depends: Win32, base -#else -depends: base -#endif - -Synopsis: time library -Exposed-modules: - Data.Time.Calendar, - Data.Time.Calendar.MonthDay, - Data.Time.Calendar.OrdinalDate, - Data.Time.Calendar.WeekDate, - Data.Time.Calendar.Julian, - Data.Time.Calendar.Easter, - Data.Time.Clock, - Data.Time.Clock.POSIX, - Data.Time.Clock.TAI, - Data.Time.LocalTime, - Data.Time.Format, - Data.Time -Extensions: ForeignFunctionInterface, CPP -C-Sources: cbits/HsTime.c -Other-Modules: - Data.Time.Calendar.Private, - Data.Time.Calendar.Days, - Data.Time.Calendar.Gregorian, - Data.Time.Calendar.JulianYearDay, - Data.Time.Clock.Scale, - Data.Time.Clock.UTC, - Data.Time.Clock.CTimeval, - Data.Time.Clock.UTCDiff, - Data.Time.LocalTime.TimeZone, - Data.Time.LocalTime.TimeOfDay, - Data.Time.LocalTime.LocalTime, - Data.Time.Format.Parse -import-dirs: IMPORT_DIR -library-dirs: LIB_DIR -hs-libraries: "HStime" -include-dirs: INCLUDE_DIR -Install-Includes: - HsTime.h HsTimeConfig.h -haddock-interfaces: HADDOCK_IFACE -haddock-html: HTML_DIR From git at git.haskell.org Fri Jan 23 22:58:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:22 +0000 (UTC) Subject: [commit: packages/time] master: Follow base split (now dep on old-locale) (c0d8daf) Message-ID: <20150123225822.BB1B83A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c0d8daf1b9f892bf94cf16e41f928c45c0437542 >--------------------------------------------------------------- commit c0d8daf1b9f892bf94cf16e41f928c45c0437542 Author: Ian Lynagh Date: Thu May 24 10:37:51 2007 -0700 Follow base split (now dep on old-locale) darcs-hash:20070524173751-3fd76-d9ce4ca8fba7e38a62deaea0920d0011cf82678e >--------------------------------------------------------------- c0d8daf1b9f892bf94cf16e41f928c45c0437542 time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 3c44a66..cb9b6ca 100644 --- a/time.cabal +++ b/time.cabal @@ -7,7 +7,7 @@ Author: Ashley Yakeley Maintainer: Homepage: http://semantic.org/TimeLib/ Category: -Build-Depends: base +Build-Depends: base, old-locale Synopsis: time library Exposed-Modules: Data.Time.Calendar, From git at git.haskell.org Fri Jan 23 22:58:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:18 +0000 (UTC) Subject: [commit: packages/time] master: Bump version to 1.1.1 (9eb62d6) Message-ID: <20150123225818.AD51A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/9eb62d6b83f0401cf7d11afdbaaed725f44a57f5 >--------------------------------------------------------------- commit 9eb62d6b83f0401cf7d11afdbaaed725f44a57f5 Author: Ian Lynagh Date: Sun Apr 22 12:52:28 2007 -0700 Bump version to 1.1.1 darcs-hash:20070422195228-3fd76-279361d39d538b6e458e46526389712ccc8b45fe >--------------------------------------------------------------- 9eb62d6b83f0401cf7d11afdbaaed725f44a57f5 Makefile | 2 +- configure.ac | 2 +- time.cabal | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/Makefile b/Makefile index 8c4e8f5..9f61dd2 100644 --- a/Makefile +++ b/Makefile @@ -13,7 +13,7 @@ ALL_DIRS = \ Data/Time/LocalTime PACKAGE = time -VERSION = 1.1 +VERSION = 1.1.1 PACKAGE_DEPS = base SRC_HC_OPTS += -Wall -Werror -fffi -Iinclude diff --git a/configure.ac b/configure.ac index 5778502..0da7fc4 100644 --- a/configure.ac +++ b/configure.ac @@ -1,4 +1,4 @@ -AC_INIT([Haskell time package], [1.1], [ashley at semantic.org], [time]) +AC_INIT([Haskell time package], [1.1.1], [ashley at semantic.org], [time]) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([include/HsTime.h]) diff --git a/time.cabal b/time.cabal index d877a1b..3c44a66 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ Name: time -Version: 1.1 +Version: 1.1.1 Stability: stable License: BSD3 License-File: LICENSE From git at git.haskell.org Fri Jan 23 22:58:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:24 +0000 (UTC) Subject: [commit: packages/time] master: --configure-option and --ghc-option are now provided by Cabal (a9edca5) Message-ID: <20150123225824.C5CFD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/a9edca50d629162c592b7ef78d6cb55b23822b2c >--------------------------------------------------------------- commit a9edca50d629162c592b7ef78d6cb55b23822b2c Author: Ross Paterson Date: Mon Jun 4 04:55:55 2007 -0700 --configure-option and --ghc-option are now provided by Cabal darcs-hash:20070604115555-b47d3-494f023ee54f001497ff09fe4e165b655a776147 >--------------------------------------------------------------- a9edca50d629162c592b7ef78d6cb55b23822b2c Setup.hs | 51 ++------------------------------------------------- 1 file changed, 2 insertions(+), 49 deletions(-) diff --git a/Setup.hs b/Setup.hs index d2fff29..e8a005c 100644 --- a/Setup.hs +++ b/Setup.hs @@ -1,7 +1,6 @@ module Main (main) where import Control.Exception -import Data.List import Distribution.PackageDescription import Distribution.Setup import Distribution.Simple @@ -9,20 +8,14 @@ import Distribution.Simple.LocalBuildInfo import Distribution.Simple.Utils import System.Cmd import System.Directory -import System.Environment import System.Info main :: IO () -main = do args <- getArgs - let (ghcArgs, args') = extractGhcArgs args - (_, args'') = extractConfigureArgs args' - hooks = defaultUserHooks { +main = do let hooks = defaultUserHooks { confHook = add_Win32_dep $ confHook defaultUserHooks, - buildHook = add_ghc_options ghcArgs - $ buildHook defaultUserHooks, runTests = runTestScript } - withArgs args'' $ defaultMainWithHooks hooks + defaultMainWithHooks hooks withCurrentDirectory :: FilePath -> IO a -> IO a withCurrentDirectory path f = do @@ -34,45 +27,6 @@ runTestScript :: Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO () runTestScript _args _flag _pd _lbi = maybeExit $ withCurrentDirectory "test" $ system "make" -extractGhcArgs :: [String] -> ([String], [String]) -extractGhcArgs = extractPrefixArgs "--ghc-option=" - -extractConfigureArgs :: [String] -> ([String], [String]) -extractConfigureArgs = extractPrefixArgs "--configure-option=" - -extractPrefixArgs :: String -> [String] -> ([String], [String]) -extractPrefixArgs the_prefix args - = let f [] = ([], []) - f (x:xs) = case f xs of - (wantedArgs, otherArgs) -> - case removePrefix the_prefix x of - Just wantedArg -> - (wantedArg:wantedArgs, otherArgs) - Nothing -> - (wantedArgs, x:otherArgs) - in f args - -removePrefix :: String -> String -> Maybe String -removePrefix "" ys = Just ys -removePrefix _ "" = Nothing -removePrefix (x:xs) (y:ys) - | x == y = removePrefix xs ys - | otherwise = Nothing - -type Hook a = PackageDescription -> LocalBuildInfo -> UserHooks -> a -> IO () - -add_ghc_options :: [String] -> Hook a -> Hook a -add_ghc_options args f pd lbi uhs x - = do let lib' = case library pd of - Just lib -> - let bi = libBuildInfo lib - opts = options bi ++ [(GHC, args)] - bi' = bi { options = opts } - in lib { libBuildInfo = bi' } - Nothing -> error "Expected a library" - pd' = pd { library = Just lib' } - f pd' lbi uhs x - type ConfHook = PackageDescription -> ConfigFlags -> IO LocalBuildInfo -- XXX Hideous hack @@ -83,4 +37,3 @@ add_Win32_dep f pd cf : buildDepends pd } else pd f pd' cf - From git at git.haskell.org Fri Jan 23 22:58:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:26 +0000 (UTC) Subject: [commit: packages/time] master: #undef PACKAGE_NAME and friends to avoid clashes (2f36990) Message-ID: <20150123225826.CBE703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2f369900a7bb45aa52dede558fa5364a1a7a7e13 >--------------------------------------------------------------- commit 2f369900a7bb45aa52dede558fa5364a1a7a7e13 Author: Simon Marlow Date: Wed Jun 6 07:20:42 2007 -0700 #undef PACKAGE_NAME and friends to avoid clashes darcs-hash:20070606142042-760e2-20bc4e080e1edf8b0e12fd8c5b68da9d21e89c79 >--------------------------------------------------------------- 2f369900a7bb45aa52dede558fa5364a1a7a7e13 include/HsTime.h | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/include/HsTime.h b/include/HsTime.h index 059cbc0..c02cc53 100644 --- a/include/HsTime.h +++ b/include/HsTime.h @@ -2,6 +2,12 @@ #define __HSTIME_H__ #include "HsTimeConfig.h" +// Otherwise these clash with similar definitions from other packages: +#undef PACKAGE_BUGREPORT +#undef PACKAGE_NAME +#undef PACKAGE_STRING +#undef PACKAGE_TARNAME +#undef PACKAGE_VERSION #if HAVE_TIME_H #include From git at git.haskell.org Fri Jan 23 22:58:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:28 +0000 (UTC) Subject: [commit: packages/time] master: Provide a configure flag to set which C compiler is used (96f1b36) Message-ID: <20150123225828.D6E2C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/96f1b36a54af14d10654ff15235ab652fa187ef4 >--------------------------------------------------------------- commit 96f1b36a54af14d10654ff15235ab652fa187ef4 Author: Ian Lynagh Date: Sat Jul 7 04:24:51 2007 -0700 Provide a configure flag to set which C compiler is used darcs-hash:20070707112451-3fd76-20588169237238c46714c9edaa964ca373949bfa >--------------------------------------------------------------- 96f1b36a54af14d10654ff15235ab652fa187ef4 configure.ac | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/configure.ac b/configure.ac index 0da7fc4..1b45b5b 100644 --- a/configure.ac +++ b/configure.ac @@ -3,6 +3,11 @@ AC_INIT([Haskell time package], [1.1.1], [ashley at semantic.org], [time]) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([include/HsTime.h]) +AC_ARG_WITH([cc], + [C compiler], + [CC=$withval]) +AC_PROG_CC() + AC_CONFIG_HEADERS([include/HsTimeConfig.h]) AC_CHECK_HEADERS([time.h]) From git at git.haskell.org Fri Jan 23 22:58:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:30 +0000 (UTC) Subject: [commit: packages/time] master: FIX #1486: timezone offset has the wrong sign on Windows (8e487ba) Message-ID: <20150123225830.DE0E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/8e487bae5f6507e15d8b142683b0ba1c4eefa223 >--------------------------------------------------------------- commit 8e487bae5f6507e15d8b142683b0ba1c4eefa223 Author: Simon Marlow Date: Tue Jul 10 01:12:36 2007 -0700 FIX #1486: timezone offset has the wrong sign on Windows Fix submitted by Olivier Boudry, thanks! darcs-hash:20070710081236-760e2-6581eff1e91b2207190b15ec6143f0eb26442178 >--------------------------------------------------------------- 8e487bae5f6507e15d8b142683b0ba1c4eefa223 cbits/HsTime.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cbits/HsTime.c b/cbits/HsTime.c index 58b7d06..dacb1d4 100644 --- a/cbits/HsTime.c +++ b/cbits/HsTime.c @@ -22,7 +22,7 @@ long int get_current_timezone_seconds (time_t t,int* pdst,char const* * pname) // implemented as part of localtime() in the CRT. This is_dst // flag is all we need here. *pname = dst ? _tzname[1] : _tzname[0]; - return dst ? _timezone - 3600 : _timezone; + return - (dst ? _timezone - 3600 : _timezone); #else # if HAVE_TZNAME *pname = *tzname; From git at git.haskell.org Fri Jan 23 22:58:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:32 +0000 (UTC) Subject: [commit: packages/time] master: Use configurations rather than Setup.hs hacks (5b0af2b) Message-ID: <20150123225832.E41A33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/5b0af2be4901a466c6daf2895b242eaf46e70870 >--------------------------------------------------------------- commit 5b0af2be4901a466c6daf2895b242eaf46e70870 Author: Ian Lynagh Date: Sun Jul 29 14:38:33 2007 -0700 Use configurations rather than Setup.hs hacks darcs-hash:20070729213833-3fd76-865c6cb804d9768e5712cfe6bb5cd1f77340eda9 >--------------------------------------------------------------- 5b0af2be4901a466c6daf2895b242eaf46e70870 Setup.hs | 13 +--------- time.cabal | 85 ++++++++++++++++++++++++++++++++++---------------------------- 2 files changed, 47 insertions(+), 51 deletions(-) diff --git a/Setup.hs b/Setup.hs index e8a005c..d57f1c9 100644 --- a/Setup.hs +++ b/Setup.hs @@ -11,10 +11,7 @@ import System.Directory import System.Info main :: IO () -main = do let hooks = defaultUserHooks { - confHook = add_Win32_dep - $ confHook defaultUserHooks, - runTests = runTestScript } +main = do let hooks = defaultUserHooks { runTests = runTestScript } defaultMainWithHooks hooks withCurrentDirectory :: FilePath -> IO a -> IO a @@ -29,11 +26,3 @@ runTestScript _args _flag _pd _lbi type ConfHook = PackageDescription -> ConfigFlags -> IO LocalBuildInfo --- XXX Hideous hack -add_Win32_dep :: ConfHook -> ConfHook -add_Win32_dep f pd cf - = do let pd' = if os == "mingw32" - then pd { buildDepends = Dependency "Win32" AnyVersion - : buildDepends pd } - else pd - f pd' cf diff --git a/time.cabal b/time.cabal index cb9b6ca..e32a126 100644 --- a/time.cabal +++ b/time.cabal @@ -7,42 +7,49 @@ Author: Ashley Yakeley Maintainer: Homepage: http://semantic.org/TimeLib/ Category: -Build-Depends: base, old-locale -Synopsis: time library -Exposed-Modules: - Data.Time.Calendar, - Data.Time.Calendar.MonthDay, - Data.Time.Calendar.OrdinalDate, - Data.Time.Calendar.WeekDate, - Data.Time.Calendar.Julian, - Data.Time.Calendar.Easter, - Data.Time.Clock, - Data.Time.Clock.POSIX, - Data.Time.Clock.TAI, - Data.Time.LocalTime, - Data.Time.Format, - Data.Time -Extensions: ForeignFunctionInterface, CPP -C-Sources: cbits/HsTime.c -Other-Modules: - Data.Time.Calendar.Private, - Data.Time.Calendar.Days, - Data.Time.Calendar.Gregorian, - Data.Time.Calendar.JulianYearDay, - Data.Time.Clock.Scale, - Data.Time.Clock.UTC, - Data.Time.Clock.CTimeval, - Data.Time.Clock.UTCDiff, - Data.Time.LocalTime.TimeZone, - Data.Time.LocalTime.TimeOfDay, - Data.Time.LocalTime.LocalTime, - Data.Time.Format.Parse -Extra-Source-Files: - aclocal.m4 configure.ac configure - include/HsTime.h include/HsTimeConfig.h.in -Extra-Tmp-Files: - config.log config.status autom4te.cache - include/HsTimeConfig.h -Include-Dirs: include -Install-Includes: - HsTime.h HsTimeConfig.h + +Library { + Build-Depends: base, old-locale + if os(mingw32) { + Build-Depends: Win32 + } + Synopsis: time library + Exposed-Modules: + Data.Time.Calendar, + Data.Time.Calendar.MonthDay, + Data.Time.Calendar.OrdinalDate, + Data.Time.Calendar.WeekDate, + Data.Time.Calendar.Julian, + Data.Time.Calendar.Easter, + Data.Time.Clock, + Data.Time.Clock.POSIX, + Data.Time.Clock.TAI, + Data.Time.LocalTime, + Data.Time.Format, + Data.Time + Extensions: ForeignFunctionInterface, CPP + C-Sources: cbits/HsTime.c + Other-Modules: + Data.Time.Calendar.Private, + Data.Time.Calendar.Days, + Data.Time.Calendar.Gregorian, + Data.Time.Calendar.JulianYearDay, + Data.Time.Clock.Scale, + Data.Time.Clock.UTC, + Data.Time.Clock.CTimeval, + Data.Time.Clock.UTCDiff, + Data.Time.LocalTime.TimeZone, + Data.Time.LocalTime.TimeOfDay, + Data.Time.LocalTime.LocalTime, + Data.Time.Format.Parse + Extra-Source-Files: + aclocal.m4 configure.ac configure + include/HsTime.h include/HsTimeConfig.h.in + Extra-Tmp-Files: + config.log config.status autom4te.cache + include/HsTimeConfig.h + Include-Dirs: include + Install-Includes: + HsTime.h HsTimeConfig.h +} + From git at git.haskell.org Fri Jan 23 22:58:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:34 +0000 (UTC) Subject: [commit: packages/time] master: Track .cabal syntax changes once again (8b0d7b8) Message-ID: <20150123225834.EC49A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/8b0d7b84e60e824da7a410431dfafcee52d64029 >--------------------------------------------------------------- commit 8b0d7b84e60e824da7a410431dfafcee52d64029 Author: sven.panne Date: Sat Sep 1 08:47:28 2007 -0700 Track .cabal syntax changes once again darcs-hash:20070901154728-96103-656ff80bfc077ca44cbfe2afc3ca3a1a032b2fa9 >--------------------------------------------------------------- 8b0d7b84e60e824da7a410431dfafcee52d64029 time.cabal | 65 +++++++++++++++++++++++++++++++------------------------------- 1 file changed, 33 insertions(+), 32 deletions(-) diff --git a/time.cabal b/time.cabal index e32a126..f9c0c17 100644 --- a/time.cabal +++ b/time.cabal @@ -6,50 +6,51 @@ License-File: LICENSE Author: Ashley Yakeley Maintainer: Homepage: http://semantic.org/TimeLib/ +Synopsis: time library Category: +Extra-Source-Files: + aclocal.m4 configure.ac configure + include/HsTime.h include/HsTimeConfig.h.in +Extra-Tmp-Files: + config.log config.status autom4te.cache + include/HsTimeConfig.h + Library { Build-Depends: base, old-locale if os(mingw32) { Build-Depends: Win32 } - Synopsis: time library Exposed-Modules: - Data.Time.Calendar, - Data.Time.Calendar.MonthDay, - Data.Time.Calendar.OrdinalDate, - Data.Time.Calendar.WeekDate, - Data.Time.Calendar.Julian, - Data.Time.Calendar.Easter, - Data.Time.Clock, - Data.Time.Clock.POSIX, - Data.Time.Clock.TAI, - Data.Time.LocalTime, - Data.Time.Format, - Data.Time + Data.Time.Calendar, + Data.Time.Calendar.MonthDay, + Data.Time.Calendar.OrdinalDate, + Data.Time.Calendar.WeekDate, + Data.Time.Calendar.Julian, + Data.Time.Calendar.Easter, + Data.Time.Clock, + Data.Time.Clock.POSIX, + Data.Time.Clock.TAI, + Data.Time.LocalTime, + Data.Time.Format, + Data.Time Extensions: ForeignFunctionInterface, CPP C-Sources: cbits/HsTime.c Other-Modules: - Data.Time.Calendar.Private, - Data.Time.Calendar.Days, - Data.Time.Calendar.Gregorian, - Data.Time.Calendar.JulianYearDay, - Data.Time.Clock.Scale, - Data.Time.Clock.UTC, - Data.Time.Clock.CTimeval, - Data.Time.Clock.UTCDiff, - Data.Time.LocalTime.TimeZone, - Data.Time.LocalTime.TimeOfDay, - Data.Time.LocalTime.LocalTime, - Data.Time.Format.Parse - Extra-Source-Files: - aclocal.m4 configure.ac configure - include/HsTime.h include/HsTimeConfig.h.in - Extra-Tmp-Files: - config.log config.status autom4te.cache - include/HsTimeConfig.h + Data.Time.Calendar.Private, + Data.Time.Calendar.Days, + Data.Time.Calendar.Gregorian, + Data.Time.Calendar.JulianYearDay, + Data.Time.Clock.Scale, + Data.Time.Clock.UTC, + Data.Time.Clock.CTimeval, + Data.Time.Clock.UTCDiff, + Data.Time.LocalTime.TimeZone, + Data.Time.LocalTime.TimeOfDay, + Data.Time.LocalTime.LocalTime, + Data.Time.Format.Parse Include-Dirs: include Install-Includes: - HsTime.h HsTimeConfig.h + HsTime.h HsTimeConfig.h } From git at git.haskell.org Fri Jan 23 22:58:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:36 +0000 (UTC) Subject: [commit: packages/time] master: Fixed Cabal-induced breakage, once again... (635d902) Message-ID: <20150123225836.F30A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/635d902b2a9ddcece575ae4b2873f793201e5684 >--------------------------------------------------------------- commit 635d902b2a9ddcece575ae4b2873f793201e5684 Author: sven.panne Date: Sat Sep 8 09:02:56 2007 -0700 Fixed Cabal-induced breakage, once again... MERGE TO STABLE (if we have a concept of "stable libraries") darcs-hash:20070908160256-96103-c5c21e89632939ac5896cf44abc9aa381df7ed4e >--------------------------------------------------------------- 635d902b2a9ddcece575ae4b2873f793201e5684 Setup.hs | 5 ----- 1 file changed, 5 deletions(-) diff --git a/Setup.hs b/Setup.hs index d57f1c9..1863d6e 100644 --- a/Setup.hs +++ b/Setup.hs @@ -2,13 +2,11 @@ module Main (main) where import Control.Exception import Distribution.PackageDescription -import Distribution.Setup import Distribution.Simple import Distribution.Simple.LocalBuildInfo import Distribution.Simple.Utils import System.Cmd import System.Directory -import System.Info main :: IO () main = do let hooks = defaultUserHooks { runTests = runTestScript } @@ -23,6 +21,3 @@ withCurrentDirectory path f = do runTestScript :: Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO () runTestScript _args _flag _pd _lbi = maybeExit $ withCurrentDirectory "test" $ system "make" - -type ConfHook = PackageDescription -> ConfigFlags -> IO LocalBuildInfo - From git at git.haskell.org Fri Jan 23 22:58:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:39 +0000 (UTC) Subject: [commit: packages/time] master: Allow a colon between the hours and minutes when parsing with %z and %Z. (e6e4837) Message-ID: <20150123225839.05BD23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e6e4837310610731a112dced280b3a14e9fe9e8b >--------------------------------------------------------------- commit e6e4837310610731a112dced280b3a14e9fe9e8b Author: bjorn Date: Tue Oct 16 12:52:39 2007 -0700 Allow a colon between the hours and minutes when parsing with %z and %Z. darcs-hash:20071016195239-6cdb2-17cf31be16d40e755740f2d3d264094be8e344a3 >--------------------------------------------------------------- e6e4837310610731a112dced280b3a14e9fe9e8b Data/Time/Format/Parse.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/Data/Time/Format/Parse.hs b/Data/Time/Format/Parse.hs index bee16e8..7e4c319 100644 --- a/Data/Time/Format/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -110,9 +110,9 @@ parseInput l = liftM catMaybes . mapM p parseValue :: TimeLocale -> Char -> ReadP String parseValue l c = case c of - 'z' -> liftM2 (:) (choice [char '+', char '-']) (digits 4) + 'z' -> numericTZ 'Z' -> munch1 isUpper <++ - liftM2 (:) (choice [char '+', char '-']) (digits 4) <++ + numericTZ <++ return "" -- produced by %Z for LocalTime 'P' -> oneOf (let (am,pm) = amPm l in [map toLower am, map toLower pm]) @@ -154,8 +154,11 @@ parseValue l c = upTo :: Int -> ReadP a -> ReadP [a] upTo 0 _ = return [] upTo n x = liftM2 (:) x (upTo (n-1) x) <++ return [] - - + numericTZ = do s <- choice [char '+', char '-'] + h <- digits 2 + optional (char ':') + m <- digits 2 + return (s:h++m) -- -- * Instances for the time package types From git at git.haskell.org Fri Jan 23 22:58:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:41 +0000 (UTC) Subject: [commit: packages/time] master: Document the format used for output with %z. (894b1f8) Message-ID: <20150123225841.0B6F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/894b1f8e83bee2e25b93441e01b72953150d5931 >--------------------------------------------------------------- commit 894b1f8e83bee2e25b93441e01b72953150d5931 Author: bjorn Date: Tue Oct 16 12:54:49 2007 -0700 Document the format used for output with %z. darcs-hash:20071016195449-6cdb2-282aead0b5077d6d80d15d2110c9316b910ff13a >--------------------------------------------------------------- 894b1f8e83bee2e25b93441e01b72953150d5931 Data/Time/Format.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Time/Format.hs b/Data/Time/Format.hs index 64f73ef..5e10cd1 100644 --- a/Data/Time/Format.hs +++ b/Data/Time/Format.hs @@ -37,7 +37,7 @@ class FormatTime t where -- -- For TimeZone (and ZonedTime and UTCTime): -- --- [@%z@] timezone offset +-- [@%z@] timezone offset on the format @-HHMM at . -- -- [@%Z@] timezone name -- From git at git.haskell.org Fri Jan 23 22:58:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:43 +0000 (UTC) Subject: [commit: packages/time] master: Haddock for parseTime and friends. (0f2e21b) Message-ID: <20150123225843.119AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/0f2e21b7e9a01b5deea2ece7173b91d45a145c30 >--------------------------------------------------------------- commit 0f2e21b7e9a01b5deea2ece7173b91d45a145c30 Author: bjorn Date: Tue Oct 16 13:19:31 2007 -0700 Haddock for parseTime and friends. darcs-hash:20071016201931-6cdb2-3cfa3dd21381bb0fd52398f717d5ba9ad4eaa7b2 >--------------------------------------------------------------- 0f2e21b7e9a01b5deea2ece7173b91d45a145c30 Data/Time/Format/Parse.hs | 17 +++++++++++------ 1 file changed, 11 insertions(+), 6 deletions(-) diff --git a/Data/Time/Format/Parse.hs b/Data/Time/Format/Parse.hs index 7e4c319..c4a258d 100644 --- a/Data/Time/Format/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -36,8 +36,15 @@ class ParseTime t where -- corresponding part of the input. -> t --- | Parse a time value given a format string. Supports the same %-codes as --- 'formatTime'. +-- | Parses a time value given a format string. Supports the same %-codes as +-- 'formatTime'. Leading and trailing whitespace is accepted. +-- Some variations in the input are accepted: +-- +-- [@%z@] accepts any of @-HHMM@ or @-HH:MM at . +-- +-- [@%Z@] accepts any string of upper case letters, or any +-- of the formats accepted by @%z at . +-- parseTime :: ParseTime t => TimeLocale -- ^ Time locale. -> String -- ^ Format string. @@ -49,8 +56,7 @@ parseTime l fmt s = case readsTime l fmt s of _ -> Nothing -- | Parse a time value given a format string. Fails if the input could --- not be parsed using the given format. Supports the same %-codes as --- 'formatTime'. +-- not be parsed using the given format. See 'parseTime' for details. readTime :: ParseTime t => TimeLocale -- ^ Time locale. -> String -- ^ Format string. @@ -61,8 +67,7 @@ readTime l fmt s = case readsTime l fmt s of [(_,x)] -> error $ "readTime: junk at end of " ++ show x _ -> error $ "readsTime: bad input " ++ show s --- | Parse a time value given a format string. Supports the same %-codes as --- 'formatTime'. +-- | Parse a time value given a format string. See 'parseTime' for details. readsTime :: ParseTime t => TimeLocale -- ^ Time locale. -> String -- ^ Format string From git at git.haskell.org Fri Jan 23 22:58:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:45 +0000 (UTC) Subject: [commit: packages/time] master: Use configurations to allow building with ghc-6.6, 6.8 (eff99ca) Message-ID: <20150123225845.17D0F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/eff99ca5fd0da086e3fcb75203ff3d76fc4f2d00 >--------------------------------------------------------------- commit eff99ca5fd0da086e3fcb75203ff3d76fc4f2d00 Author: Duncan Coutts Date: Thu Oct 18 10:38:27 2007 -0700 Use configurations to allow building with ghc-6.6, 6.8 Specify build-type: Custom since there is test code in Setup.hs darcs-hash:20071018173827-adfee-6a7bc524d8bade80a2276c809006e48faeb701dd >--------------------------------------------------------------- eff99ca5fd0da086e3fcb75203ff3d76fc4f2d00 time.cabal | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/time.cabal b/time.cabal index f9c0c17..e2c477e 100644 --- a/time.cabal +++ b/time.cabal @@ -8,6 +8,8 @@ Maintainer: Homepage: http://semantic.org/TimeLib/ Synopsis: time library Category: +Build-Type: Custom +Cabal-Version: >=1.2 Extra-Source-Files: aclocal.m4 configure.ac configure @@ -16,11 +18,16 @@ Extra-Tmp-Files: config.log config.status autom4te.cache include/HsTimeConfig.h +Flag split-base + Library { - Build-Depends: base, old-locale - if os(mingw32) { + Build-Depends: base >= 2 + if flag(split-base) + Build-Depends: base >= 3, old-locale + else + Build-Depends: base < 3 + if os(windows) Build-Depends: Win32 - } Exposed-Modules: Data.Time.Calendar, Data.Time.Calendar.MonthDay, From git at git.haskell.org Fri Jan 23 22:58:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:47 +0000 (UTC) Subject: [commit: packages/time] master: Bump version number (39c0eef) Message-ID: <20150123225847.1E6F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/39c0eef062a890c38565b4d2ff65494d6c9b87b8 >--------------------------------------------------------------- commit 39c0eef062a890c38565b4d2ff65494d6c9b87b8 Author: Ian Lynagh Date: Sat Oct 27 05:49:20 2007 -0700 Bump version number darcs-hash:20071027124920-3fd76-1e1832bf4e7b70abd50fd5f502f04781e30836b2 >--------------------------------------------------------------- 39c0eef062a890c38565b4d2ff65494d6c9b87b8 time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index e2c477e..0e7c244 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ Name: time -Version: 1.1.1 +Version: 1.1.2.0 Stability: stable License: BSD3 License-File: LICENSE From git at git.haskell.org Fri Jan 23 22:58:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:49 +0000 (UTC) Subject: [commit: packages/time] master: document how to get a POSIXTime from an EpochTime or CTime. (2869c91) Message-ID: <20150123225849.25DAC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2869c91e34012c0dc1834db50c79b5e68d4b95f2 >--------------------------------------------------------------- commit 2869c91e34012c0dc1834db50c79b5e68d4b95f2 Author: Simon Marlow Date: Wed Dec 5 01:15:37 2007 -0800 document how to get a POSIXTime from an EpochTime or CTime. darcs-hash:20071205091537-760e2-5c6cf6c587c9f72fe962cedd4a33b764a627016d >--------------------------------------------------------------- 2869c91e34012c0dc1834db50c79b5e68d4b95f2 Data/Time/Clock/POSIX.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/Data/Time/Clock/POSIX.hs b/Data/Time/Clock/POSIX.hs index b877bf7..84137c1 100644 --- a/Data/Time/Clock/POSIX.hs +++ b/Data/Time/Clock/POSIX.hs @@ -24,6 +24,9 @@ posixDayLength :: NominalDiffTime posixDayLength = 86400 -- | POSIX time is the nominal time since 1970-01-01 00:00 UTC +-- +-- To convert from a 'Foreign.C.CTime' or 'System.Posix.EpochTime', use 'realToFrac'. +-- type POSIXTime = NominalDiffTime unixEpochDay :: Day From git at git.haskell.org Fri Jan 23 22:58:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:51 +0000 (UTC) Subject: [commit: packages/time] master: Figure out timezone offset from timezone name (3c404c3) Message-ID: <20150123225851.2D2843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3c404c3416cd4610b1189b1b40193e5617a143eb >--------------------------------------------------------------- commit 3c404c3416cd4610b1189b1b40193e5617a143eb Author: David Leuschner Date: Sat Feb 2 03:33:17 2008 -0800 Figure out timezone offset from timezone name darcs-hash:20080202113317-3c698-73870973cd45d7f9ca67476c4d46e39db79e8402 >--------------------------------------------------------------- 3c404c3416cd4610b1189b1b40193e5617a143eb Data/Time/Format/Parse.hs | 232 ++++++++++++++++++++++++++++++++++++++++++++-- 1 file changed, 226 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3c404c3416cd4610b1189b1b40193e5617a143eb From git at git.haskell.org Fri Jan 23 22:58:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:53 +0000 (UTC) Subject: [commit: packages/time] master: Bump version to 1.1.2.1 (71f2aa9) Message-ID: <20150123225853.34E7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/71f2aa9d7792783ae7fe4dc19f1d90bfa92f380d >--------------------------------------------------------------- commit 71f2aa9d7792783ae7fe4dc19f1d90bfa92f380d Author: Ian Lynagh Date: Wed Jun 4 05:13:53 2008 -0700 Bump version to 1.1.2.1 darcs-hash:20080604121353-3fd76-d2a8d0737dfac619589ac8d511c9712259c7a7a8 >--------------------------------------------------------------- 71f2aa9d7792783ae7fe4dc19f1d90bfa92f380d time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 0e7c244..43cf8a0 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ Name: time -Version: 1.1.2.0 +Version: 1.1.2.1 Stability: stable License: BSD3 License-File: LICENSE From git at git.haskell.org Fri Jan 23 22:58:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:55 +0000 (UTC) Subject: [commit: packages/time] master: Remove -Wall and -Werror, they don't belong here (c46f680) Message-ID: <20150123225855.3C7D63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c46f680fc0d2eec0a2c85b344478010097bcb05a >--------------------------------------------------------------- commit c46f680fc0d2eec0a2c85b344478010097bcb05a Author: Simon Marlow Date: Thu Jun 19 07:12:19 2008 -0700 Remove -Wall and -Werror, they don't belong here this fixes GHC HEAD right now, which generates a warning for -ffi. darcs-hash:20080619141219-12142-2fdb57eb762347e667e8e5d1ed92e82afd5ef599 >--------------------------------------------------------------- c46f680fc0d2eec0a2c85b344478010097bcb05a Data/Time/Clock/CTimeval.hs | 2 +- Data/Time/LocalTime/TimeZone.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/Data/Time/Clock/CTimeval.hs b/Data/Time/Clock/CTimeval.hs index 8025bdb..0e83072 100644 --- a/Data/Time/Clock/CTimeval.hs +++ b/Data/Time/Clock/CTimeval.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -ffi -Wall -Werror -cpp #-} +{-# OPTIONS -ffi -cpp #-} -- #hide module Data.Time.Clock.CTimeval where diff --git a/Data/Time/LocalTime/TimeZone.hs b/Data/Time/LocalTime/TimeZone.hs index d80671e..81f15d3 100644 --- a/Data/Time/LocalTime/TimeZone.hs +++ b/Data/Time/LocalTime/TimeZone.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -ffi -Wall -Werror #-} +{-# OPTIONS -ffi #-} -- #hide module Data.Time.LocalTime.TimeZone From git at git.haskell.org Fri Jan 23 22:58:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:57 +0000 (UTC) Subject: [commit: packages/time] master: Change "accuracy" to "precision". (cc3dae0) Message-ID: <20150123225857.4304C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/cc3dae057e2bdcd8423b8beb9b46d2651e114de7 >--------------------------------------------------------------- commit cc3dae057e2bdcd8423b8beb9b46d2651e114de7 Author: Alexander Dunlap Date: Tue Jul 29 11:37:58 2008 -0700 Change "accuracy" to "precision". See . darcs-hash:20080729183758-e80da-955fe221e10854ee27e143cdb282caae7c010d33 >--------------------------------------------------------------- cc3dae057e2bdcd8423b8beb9b46d2651e114de7 Data/Time/Clock/Scale.hs | 2 +- Data/Time/Clock/UTC.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs index 053c515..cb3fbee 100644 --- a/Data/Time/Clock/Scale.hs +++ b/Data/Time/Clock/Scale.hs @@ -21,7 +21,7 @@ newtype UniversalTime = ModJulianDate {getModJulianDate :: Rational} deriving (E -- | This is a length of time, as measured by a clock. -- Conversion functions will treat it as seconds. --- It has an accuracy of 10^-12 s. +-- It has a precision of 10^-12 s. newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord) -- necessary because H98 doesn't have "cunning newtype" derivation diff --git a/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs index 57daa6b..a76a805 100644 --- a/Data/Time/Clock/UTC.hs +++ b/Data/Time/Clock/UTC.hs @@ -39,7 +39,7 @@ instance Ord UTCTime where -- | This is a length of time, as measured by UTC. -- Conversion functions will treat it as seconds. --- It has an accuracy of 10^-12 s. +-- It has a precision of 10^-12 s. -- It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. -- For instance, 23:00 UTC + 2 hours of NominalDiffTime = 01:00 UTC (+ 1 day), -- regardless of whether a leap-second intervened. From git at git.haskell.org Fri Jan 23 22:58:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:58:59 +0000 (UTC) Subject: [commit: packages/time] master: don't warn about orphan instances; they're real warnings now (i.e. errors with -Werror) (b010dd2) Message-ID: <20150123225859.4ADE93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b010dd2b7c8e852a85d4f1c2136f17dad8e33ddf >--------------------------------------------------------------- commit b010dd2b7c8e852a85d4f1c2136f17dad8e33ddf Author: Ashley Yakeley Date: Tue Aug 12 00:35:46 2008 -0700 don't warn about orphan instances; they're real warnings now (i.e. errors with -Werror) darcs-hash:20080812073546-ac6dd-936d990eb8c2e6293124aec9f646a7988edca214 >--------------------------------------------------------------- b010dd2b7c8e852a85d4f1c2136f17dad8e33ddf Data/Time/Calendar/Gregorian.hs | 2 +- Data/Time/Format/Parse.hs | 2 +- Data/Time/LocalTime/LocalTime.hs | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/Data/Time/Calendar/Gregorian.hs b/Data/Time/Calendar/Gregorian.hs index 2d3546c..1887838 100644 --- a/Data/Time/Calendar/Gregorian.hs +++ b/Data/Time/Calendar/Gregorian.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -Wall -Werror #-} +{-# OPTIONS -Wall -Werror -fno-warn-orphans #-} -- #hide module Data.Time.Calendar.Gregorian diff --git a/Data/Time/Format/Parse.hs b/Data/Time/Format/Parse.hs index 9f97cfd..aa9e2c3 100644 --- a/Data/Time/Format/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -Wall -Werror #-} +{-# OPTIONS -Wall -Werror -fno-warn-orphans #-} -- #hide module Data.Time.Format.Parse diff --git a/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs index c902bb6..6c8bbb6 100644 --- a/Data/Time/LocalTime/LocalTime.hs +++ b/Data/Time/LocalTime/LocalTime.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -Wall -Werror #-} +{-# OPTIONS -Wall -Werror -fno-warn-orphans #-} -- #hide module Data.Time.LocalTime.LocalTime From git at git.haskell.org Fri Jan 23 22:59:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:01 +0000 (UTC) Subject: [commit: packages/time] master: remove -ffi options (in favour of -XForeignFunctionInterface) (e581e9c) Message-ID: <20150123225901.525793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e581e9cbf1fc840663fa0e154ae99fc476223d5a >--------------------------------------------------------------- commit e581e9cbf1fc840663fa0e154ae99fc476223d5a Author: Ashley Yakeley Date: Sun Sep 14 17:19:01 2008 -0700 remove -ffi options (in favour of -XForeignFunctionInterface) darcs-hash:20080915001901-ac6dd-48abe6364ead4d30656f5a1ca6a05a854f9bd0fb >--------------------------------------------------------------- e581e9cbf1fc840663fa0e154ae99fc476223d5a Data/Time/Clock/CTimeval.hs | 2 +- test/TestEaster.hs | 2 +- test/TestFormat.hs | 2 +- test/TestParseDAT.hs | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/Data/Time/Clock/CTimeval.hs b/Data/Time/Clock/CTimeval.hs index 0e83072..ab5fd79 100644 --- a/Data/Time/Clock/CTimeval.hs +++ b/Data/Time/Clock/CTimeval.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -ffi -cpp #-} +{-# OPTIONS -cpp #-} -- #hide module Data.Time.Clock.CTimeval where diff --git a/test/TestEaster.hs b/test/TestEaster.hs index 290c066..8aae5ce 100644 --- a/test/TestEaster.hs +++ b/test/TestEaster.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -ffi -Wall -Werror #-} +{-# OPTIONS -Wall -Werror #-} module Main where diff --git a/test/TestFormat.hs b/test/TestFormat.hs index ecfa9fa..b827e0a 100644 --- a/test/TestFormat.hs +++ b/test/TestFormat.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -ffi -Wall -Werror #-} +{-# OPTIONS -XForeignFunctionInterface -Wall -Werror #-} module Main where diff --git a/test/TestParseDAT.hs b/test/TestParseDAT.hs index ee56d49..181ca08 100644 --- a/test/TestParseDAT.hs +++ b/test/TestParseDAT.hs @@ -1,4 +1,4 @@ -{-# OPTIONS -ffi -Wall -Werror #-} +{-# OPTIONS -Wall -Werror #-} module Main where From git at git.haskell.org Fri Jan 23 22:59:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:03 +0000 (UTC) Subject: [commit: packages/time] master: Add x-follows-version-policy tag (230f9ee) Message-ID: <20150123225903.588163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/230f9ee15609e6e5b43d32f71041f18c15857ccb >--------------------------------------------------------------- commit 230f9ee15609e6e5b43d32f71041f18c15857ccb Author: Duncan Coutts Date: Fri Oct 10 20:47:42 2008 -0700 Add x-follows-version-policy tag darcs-hash:20081011034742-adfee-ceabc7cef114c6bc02d37cba7cdcd56e71e15744 >--------------------------------------------------------------- 230f9ee15609e6e5b43d32f71041f18c15857ccb time.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/time.cabal b/time.cabal index 43cf8a0..287ac1a 100644 --- a/time.cabal +++ b/time.cabal @@ -10,6 +10,7 @@ Synopsis: time library Category: Build-Type: Custom Cabal-Version: >=1.2 +x-follows-version-policy: Extra-Source-Files: aclocal.m4 configure.ac configure From git at git.haskell.org Fri Jan 23 22:59:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:05 +0000 (UTC) Subject: [commit: packages/time] master: Bump version number to 1.1.2.2 (3f174bc) Message-ID: <20150123225905.5F4F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3f174bc80dc7342572622da4a83db83fc90e8622 >--------------------------------------------------------------- commit 3f174bc80dc7342572622da4a83db83fc90e8622 Author: Duncan Coutts Date: Fri Oct 10 20:48:01 2008 -0700 Bump version number to 1.1.2.2 Only warning and doc changes since the last release darcs-hash:20081011034801-adfee-f2cb7e23c6e6f767ee8b80bfa30c5fd78fefd7ab >--------------------------------------------------------------- 3f174bc80dc7342572622da4a83db83fc90e8622 time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 287ac1a..aad656a 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ Name: time -Version: 1.1.2.1 +Version: 1.1.2.2 Stability: stable License: BSD3 License-File: LICENSE From git at git.haskell.org Fri Jan 23 22:59:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:07 +0000 (UTC) Subject: [commit: packages/time] master: Improve meta-data (989fc61) Message-ID: <20150123225907.67F9C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/989fc61698038e6b230ce1c92b63167ccfe979e6 >--------------------------------------------------------------- commit 989fc61698038e6b230ce1c92b63167ccfe979e6 Author: Don Stewart Date: Sat Oct 11 15:04:12 2008 -0700 Improve meta-data darcs-hash:20081011220412-cba2c-18eac614e5ee4b1c7cc34abf7c6a91d3a28166c0 >--------------------------------------------------------------- 989fc61698038e6b230ce1c92b63167ccfe979e6 time.cabal | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/time.cabal b/time.cabal index aad656a..3b3dcde 100644 --- a/time.cabal +++ b/time.cabal @@ -6,8 +6,9 @@ License-File: LICENSE Author: Ashley Yakeley Maintainer: Homepage: http://semantic.org/TimeLib/ -Synopsis: time library -Category: +Synopsis: A time library +Description: A time library +Category: System Build-Type: Custom Cabal-Version: >=1.2 x-follows-version-policy: From git at git.haskell.org Fri Jan 23 22:59:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:09 +0000 (UTC) Subject: [commit: packages/time] master: Ix instance for Day. This is useful for e.g. storing daily tabulated data in arrays. (b94d3b7) Message-ID: <20150123225909.6E6633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b94d3b7c106b06acd57822dee8bf464022c3e53c >--------------------------------------------------------------- commit b94d3b7c106b06acd57822dee8bf464022c3e53c Author: Bjorn Buckwalter Date: Sat Nov 29 18:22:54 2008 -0800 Ix instance for Day. This is useful for e.g. storing daily tabulated data in arrays. darcs-hash:20081130022254-03283-3e7adc8ff05bff3fb416856f6a1e58697a073cf6 >--------------------------------------------------------------- b94d3b7c106b06acd57822dee8bf464022c3e53c Data/Time/Calendar/Days.hs | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/Data/Time/Calendar/Days.hs b/Data/Time/Calendar/Days.hs index 9d91db0..2e62400 100644 --- a/Data/Time/Calendar/Days.hs +++ b/Data/Time/Calendar/Days.hs @@ -5,6 +5,8 @@ module Data.Time.Calendar.Days Day(..),addDays,diffDays ) where +import Data.Ix + -- | The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17. newtype Day = ModifiedJulianDay {toModifiedJulianDay :: Integer} deriving (Eq,Ord) @@ -19,6 +21,13 @@ instance Enum Day where enumFromTo (ModifiedJulianDay a) (ModifiedJulianDay b) = fmap ModifiedJulianDay (enumFromTo a b) enumFromThenTo (ModifiedJulianDay a) (ModifiedJulianDay b) (ModifiedJulianDay c) = fmap ModifiedJulianDay (enumFromThenTo a b c) +-- necessary because H98 doesn't have "cunning newtype" derivation +instance Ix Day where + range (ModifiedJulianDay a,ModifiedJulianDay b) = fmap ModifiedJulianDay (range (a,b)) + index (ModifiedJulianDay a,ModifiedJulianDay b) (ModifiedJulianDay c) = index (a,b) c + inRange (ModifiedJulianDay a,ModifiedJulianDay b) (ModifiedJulianDay c) = inRange (a,b) c + rangeSize (ModifiedJulianDay a,ModifiedJulianDay b) = rangeSize (a,b) + addDays :: Integer -> Day -> Day addDays n (ModifiedJulianDay a) = ModifiedJulianDay (a + n) From git at git.haskell.org Fri Jan 23 22:59:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:11 +0000 (UTC) Subject: [commit: packages/time] master: fix warnings; fix tests; remove GHC cruft; bump to 1.1.2.3 (578a832) Message-ID: <20150123225911.762193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/578a832dbdba861430513fa4ef6c778af722fe37 >--------------------------------------------------------------- commit 578a832dbdba861430513fa4ef6c778af722fe37 Author: Ashley Yakeley Date: Sun Jan 4 14:37:28 2009 -0800 fix warnings; fix tests; remove GHC cruft; bump to 1.1.2.3 darcs-hash:20090104223728-ac6dd-4019748e20d222ef709e509c98869e59c238b2aa >--------------------------------------------------------------- 578a832dbdba861430513fa4ef6c778af722fe37 Data/Time/LocalTime/TimeZone.hs | 2 +- Setup.hs | 2 +- configure.ac | 2 +- include/Makefile | 11 - prologue.txt | 2 - test/TestParseTime.hs | 2 +- time.cabal | 2 +- time.xcodeproj/cabalbuild | 8 - time.xcodeproj/fixerrormsgs | 10 - time.xcodeproj/project.pbxproj | 441 ---------------------------------------- 10 files changed, 5 insertions(+), 477 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 578a832dbdba861430513fa4ef6c778af722fe37 From git at git.haskell.org Fri Jan 23 22:59:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:13 +0000 (UTC) Subject: [commit: packages/time] master: fix Julian haddock docs (6a4e1ea) Message-ID: <20150123225913.7D5BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/6a4e1ea5f1a477ded35b7eedec59a55b18cbc4b1 >--------------------------------------------------------------- commit 6a4e1ea5f1a477ded35b7eedec59a55b18cbc4b1 Author: Ashley Yakeley Date: Sun Jan 4 14:43:39 2009 -0800 fix Julian haddock docs darcs-hash:20090104224339-ac6dd-d7e1a83ebcdace7c2f9638aa855efc18f9b6b0ae >--------------------------------------------------------------- 6a4e1ea5f1a477ded35b7eedec59a55b18cbc4b1 Data/Time/Calendar/JulianYearDay.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/Data/Time/Calendar/JulianYearDay.hs b/Data/Time/Calendar/JulianYearDay.hs index ba10c8f..26e4660 100644 --- a/Data/Time/Calendar/JulianYearDay.hs +++ b/Data/Time/Calendar/JulianYearDay.hs @@ -10,7 +10,7 @@ module Data.Time.Calendar.JulianYearDay import Data.Time.Calendar.Days import Data.Time.Calendar.Private --- | convert to ISO 8601 Ordinal Day format. First element of result is year (proleptic Gregoran calendar), +-- | convert to proleptic Julian year and day format. First element of result is year (proleptic Julian calendar), -- second is the day of the year, with 1 for Jan 1, and 365 (or 366 in leap years) for Dec 31. toJulianYearAndDay :: Day -> (Integer,Int) toJulianYearAndDay (ModifiedJulianDay mjd) = (year,yd) where @@ -21,18 +21,18 @@ toJulianYearAndDay (ModifiedJulianDay mjd) = (year,yd) where yd = fromInteger (d - (y * 365) + 1) year = quad * 4 + y + 1 --- | convert from ISO 8601 Ordinal Day format. +-- | convert from proleptic Julian year and day format. -- Invalid day numbers will be clipped to the correct range (1 to 365 or 366). fromJulianYearAndDay :: Integer -> Int -> Day fromJulianYearAndDay year day = ModifiedJulianDay mjd where y = year - 1 mjd = (fromIntegral (clip 1 (if isJulianLeapYear year then 366 else 365) day)) + (365 * y) + (div y 4) - 678578 --- | show in ISO 8601 Ordinal Day format (yyyy-ddd) +-- | show in proleptic Julian year and day format (yyyy-ddd) showJulianYearAndDay :: Day -> String showJulianYearAndDay date = (show4 y) ++ "-" ++ (show3 d) where (y,d) = toJulianYearAndDay date --- | Is this year a leap year according to the proleptic Gregorian calendar? +-- | Is this year a leap year according to the proleptic Julian calendar? isJulianLeapYear :: Integer -> Bool isJulianLeapYear year = (mod year 4 == 0) From git at git.haskell.org Fri Jan 23 22:59:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:15 +0000 (UTC) Subject: [commit: packages/time] master: add Makefile for development building; remove OPTIONS -Wall -Werror in each file (a8f5da7) Message-ID: <20150123225915.8794B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/a8f5da7d9d7d32114977b566f1f0f0546e07c219 >--------------------------------------------------------------- commit a8f5da7d9d7d32114977b566f1f0f0546e07c219 Author: Ashley Yakeley Date: Sun Jan 4 15:03:18 2009 -0800 add Makefile for development building; remove OPTIONS -Wall -Werror in each file darcs-hash:20090104230318-ac6dd-8719d86331f9b46e617e53665bc12e6e067c21f9 >--------------------------------------------------------------- a8f5da7d9d7d32114977b566f1f0f0546e07c219 Data/Time.hs | 2 -- Data/Time/Calendar.hs | 2 -- Data/Time/Calendar/Days.hs | 2 -- Data/Time/Calendar/Easter.hs | 2 -- Data/Time/Calendar/Gregorian.hs | 3 ++- Data/Time/Calendar/Julian.hs | 2 -- Data/Time/Calendar/JulianYearDay.hs | 2 -- Data/Time/Calendar/MonthDay.hs | 2 -- Data/Time/Calendar/OrdinalDate.hs | 2 -- Data/Time/Calendar/Private.hs | 2 -- Data/Time/Calendar/WeekDate.hs | 2 -- Data/Time/Clock.hs | 2 -- Data/Time/Clock/CTimeval.hs | 2 -- Data/Time/Clock/POSIX.hs | 2 -- Data/Time/Clock/Scale.hs | 2 -- Data/Time/Clock/TAI.hs | 2 -- Data/Time/Clock/UTC.hs | 2 -- Data/Time/Clock/UTCDiff.hs | 2 -- Data/Time/Format.hs | 2 -- Data/Time/Format/Parse.hs | 2 +- Data/Time/LocalTime.hs | 2 -- Data/Time/LocalTime/LocalTime.hs | 3 ++- Data/Time/LocalTime/TimeOfDay.hs | 2 -- Makefile | 29 +++++++++++++++++++++++++++++ 24 files changed, 34 insertions(+), 43 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a8f5da7d9d7d32114977b566f1f0f0546e07c219 From git at git.haskell.org Fri Jan 23 22:59:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:17 +0000 (UTC) Subject: [commit: packages/time] master: prop_name helper for defining named properties. (c8bba9b) Message-ID: <20150123225917.917A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c8bba9b75c9ea49bfa955a2c5913b5322446923d >--------------------------------------------------------------- commit c8bba9b75c9ea49bfa955a2c5913b5322446923d Author: Bjorn Buckwalter Date: Sat Jan 17 17:10:08 2009 -0800 prop_name helper for defining named properties. darcs-hash:20090118011008-03283-d383aaaec1c96d8ca8a0f23ca2464d29e6e7d428 >--------------------------------------------------------------- c8bba9b75c9ea49bfa955a2c5913b5322446923d test/TestParseTime.hs | 17 ++++++++--------- 1 file changed, 8 insertions(+), 9 deletions(-) diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index 8e313ba..11b8787 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -124,14 +124,17 @@ prop_fromSundayStartWeek d = -- * format and parse -- +-- | Helper for defining named properties. +prop_named :: (Arbitrary t, Show t, Testable a) + => String -> (FormatString s -> t -> a) -> String -> FormatString s -> NamedProperty +prop_named name prop typeName f = (name ++ " " ++ typeName ++ " " ++ show f, property (prop f)) + prop_parse_format :: (Eq t, FormatTime t, ParseTime t) => FormatString t -> t -> Bool prop_parse_format (FormatString f) t = parse f (format f t) == Just t prop_parse_format_named :: (Arbitrary t, Eq t, Show t, FormatTime t, ParseTime t) => String -> FormatString t -> NamedProperty -prop_parse_format_named typeName f = - ("prop_parse_format " ++ typeName ++ " " ++ show f, - property (prop_parse_format f)) +prop_parse_format_named = prop_named "prop_parse_format" prop_parse_format prop_format_parse_format :: (FormatTime t, ParseTime t) => FormatString t -> t -> Bool prop_format_parse_format (FormatString f) t = @@ -139,9 +142,7 @@ prop_format_parse_format (FormatString f) t = prop_format_parse_format_named :: (Arbitrary t, Show t, FormatTime t, ParseTime t) => String -> FormatString t -> NamedProperty -prop_format_parse_format_named typeName f = - ("prop_format_parse_format " ++ typeName ++ " " ++ show f, - property (prop_format_parse_format f)) +prop_format_parse_format_named = prop_named "prop_format_parse_format" prop_format_parse_format -- -- * crashes in parse @@ -166,9 +167,7 @@ prop_no_crash_bad_input fs@(FormatString f) (Input s) = property $ where prop_no_crash_bad_input_named :: (Eq t, ParseTime t) => String -> FormatString t -> NamedProperty -prop_no_crash_bad_input_named typeName f = - ("prop_no_crash_bad_input " ++ typeName ++ " " ++ show f, - property (prop_no_crash_bad_input f)) +prop_no_crash_bad_input_named = prop_named "prop_no_crash_bad_input" prop_no_crash_bad_input -- -- From git at git.haskell.org Fri Jan 23 22:59:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:19 +0000 (UTC) Subject: [commit: packages/time] master: Properties for testing case-insensitivity. (bd8607f) Message-ID: <20150123225919.9ACB83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/bd8607fd727c79c066aeae398104eee74b3faa53 >--------------------------------------------------------------- commit bd8607fd727c79c066aeae398104eee74b3faa53 Author: Bjorn Buckwalter Date: Sun Jan 18 13:51:43 2009 -0800 Properties for testing case-insensitivity. Note that not all formats being tested have alphabetical characters. The additional testing of those is "wasteful". darcs-hash:20090118215143-03283-5ed4f9ba7cdc8fa09afdb4584e52ac017c4421db >--------------------------------------------------------------- bd8607fd727c79c066aeae398104eee74b3faa53 test/TestParseTime.hs | 30 ++++++++++++++++++++++++++++++ 1 file changed, 30 insertions(+) diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index 11b8787..76b897a 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -136,6 +136,22 @@ prop_parse_format_named :: (Arbitrary t, Eq t, Show t, FormatTime t, ParseTime t => String -> FormatString t -> NamedProperty prop_parse_format_named = prop_named "prop_parse_format" prop_parse_format +-- Verify case-insensitivity with upper case. +prop_parse_format_upper :: (Eq t, FormatTime t, ParseTime t) => FormatString t -> t -> Bool +prop_parse_format_upper (FormatString f) t = parse f (map toUpper $ format f t) == Just t + +prop_parse_format_upper_named :: (Arbitrary t, Eq t, Show t, FormatTime t, ParseTime t) + => String -> FormatString t -> NamedProperty +prop_parse_format_upper_named = prop_named "prop_parse_format_upper" prop_parse_format_upper + +-- Verify case-insensitivity with lower case. +prop_parse_format_lower :: (Eq t, FormatTime t, ParseTime t) => FormatString t -> t -> Bool +prop_parse_format_lower (FormatString f) t = parse f (map toLower $ format f t) == Just t + +prop_parse_format_lower_named :: (Arbitrary t, Eq t, Show t, FormatTime t, ParseTime t) + => String -> FormatString t -> NamedProperty +prop_parse_format_lower_named = prop_named "prop_parse_format_lower" prop_parse_format_lower + prop_format_parse_format :: (FormatTime t, ParseTime t) => FormatString t -> t -> Bool prop_format_parse_format (FormatString f) t = fmap (format f) (parse f (format f t) `asTypeOf` Just t) == Just (format f t) @@ -207,6 +223,20 @@ properties = ++ map (prop_parse_format_named "ZonedTime") zonedTimeFormats ++ map (prop_parse_format_named "UTCTime") utcTimeFormats + ++ map (prop_parse_format_upper_named "Day") dayFormats + ++ map (prop_parse_format_upper_named "TimeOfDay") timeOfDayFormats + ++ map (prop_parse_format_upper_named "LocalTime") localTimeFormats + ++ map (prop_parse_format_upper_named "TimeZone") timeZoneFormats + ++ map (prop_parse_format_upper_named "ZonedTime") zonedTimeFormats + ++ map (prop_parse_format_upper_named "UTCTime") utcTimeFormats + + ++ map (prop_parse_format_lower_named "Day") dayFormats + ++ map (prop_parse_format_lower_named "TimeOfDay") timeOfDayFormats + ++ map (prop_parse_format_lower_named "LocalTime") localTimeFormats + ++ map (prop_parse_format_lower_named "TimeZone") timeZoneFormats + ++ map (prop_parse_format_lower_named "ZonedTime") zonedTimeFormats + ++ map (prop_parse_format_lower_named "UTCTime") utcTimeFormats + ++ map (prop_format_parse_format_named "Day") partialDayFormats ++ map (prop_format_parse_format_named "TimeOfDay") partialTimeOfDayFormats ++ map (prop_format_parse_format_named "LocalTime") partialLocalTimeFormats From git at git.haskell.org Fri Jan 23 22:59:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:21 +0000 (UTC) Subject: [commit: packages/time] master: Case-insensitive parsing. (781548a) Message-ID: <20150123225921.A15273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/781548a552f78bba54abcdd2e3fb178786bdf547 >--------------------------------------------------------------- commit 781548a552f78bba54abcdd2e3fb178786bdf547 Author: Bjorn Buckwalter Date: Sun Jan 18 13:54:47 2009 -0800 Case-insensitive parsing. Note that when a TimeZone is parsed the timeZoneName is converted to upper case. The capitalization of the input could just as easily be preserved instead. It is unclear whether there is any clear advantage to either option. darcs-hash:20090118215447-03283-5df560167dff9f5cfaa4a40988befc60b0029696 >--------------------------------------------------------------- 781548a552f78bba54abcdd2e3fb178786bdf547 Data/Time/Format/Parse.hs | 49 +++++++++++++++++++++++++++++++---------------- 1 file changed, 32 insertions(+), 17 deletions(-) diff --git a/Data/Time/Format/Parse.hs b/Data/Time/Format/Parse.hs index 7218bfb..1aaf0d0 100644 --- a/Data/Time/Format/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -22,7 +22,23 @@ import Data.List import Data.Maybe import Data.Ratio import System.Locale -import Text.ParserCombinators.ReadP +import Text.ParserCombinators.ReadP hiding (char, string) + + +-- | Case-insensitive version of 'Text.ParserCombinators.ReadP.char'. +char :: Char -> ReadP Char +char c = satisfy (\x -> toUpper c == toUpper x) +-- | Case-insensitive version of 'Text.ParserCombinators.ReadP.string'. +string :: String -> ReadP String +string this = do s <- look; scan this s + where + scan [] _ = do return this + scan (x:xs) (y:ys) | toUpper x == toUpper y = do get; scan xs ys + scan _ _ = do pfail +-- | Convert string to upper case. +up :: String -> String +up = map toUpper + -- | The class of types which can be parsed given a UNIX-style time format -- string. @@ -37,12 +53,12 @@ class ParseTime t where -> t -- | Parses a time value given a format string. Supports the same %-codes as --- 'formatTime'. Leading and trailing whitespace is accepted. --- Some variations in the input are accepted: +-- 'formatTime'. Leading and trailing whitespace is accepted. Case is not +-- significant. Some variations in the input are accepted: -- -- [@%z@] accepts any of @-HHMM@ or @-HH:MM at . -- --- [@%Z@] accepts any string of upper case letters, or any +-- [@%Z@] accepts any string of letters, or any -- of the formats accepted by @%z at . -- parseTime :: ParseTime t => @@ -116,11 +132,10 @@ parseValue :: TimeLocale -> Char -> ReadP String parseValue l c = case c of 'z' -> numericTZ - 'Z' -> munch1 isUpper <++ + 'Z' -> munch1 isAlpha <++ numericTZ <++ return "" -- produced by %Z for LocalTime - 'P' -> oneOf (let (am,pm) = amPm l - in [map toLower am, map toLower pm]) + 'P' -> oneOf (let (am,pm) = amPm l in [am, pm]) 'p' -> oneOf (let (am,pm) = amPm l in [am, pm]) 'H' -> digits 2 'I' -> digits 2 @@ -191,9 +206,9 @@ instance ParseTime Day where -- %C: century (being the first two digits of the year), 00 - 99 'C' -> [Century (read x)] -- %B: month name, long form (fst from months locale), January - December - 'B' -> [Month (1 + fromJust (elemIndex x (map fst (months l))))] + 'B' -> [Month (1 + fromJust (elemIndex (up x) (map (up . fst) (months l))))] -- %b: month name, short form (snd from months locale), Jan - Dec - 'b' -> [Month (1 + fromJust (elemIndex x (map snd (months l))))] + 'b' -> [Month (1 + fromJust (elemIndex (up x) (map (up . snd) (months l))))] -- %m: month of year, leading 0 as needed, 01 - 12 'm' -> [Month (read x)] -- %d: day of month, leading 0 as needed, 01 - 31 @@ -213,9 +228,9 @@ instance ParseTime Day where -- %u: day for Week Date format, 1 - 7 'u' -> [WeekDay (read x)] -- %a: day of week, short form (snd from wDays locale), Sun - Sat - 'a' -> [WeekDay (1 + (fromJust (elemIndex x (map snd (wDays l))) + 6) `mod` 7)] + 'a' -> [WeekDay (1 + (fromJust (elemIndex (up x) (map (up . snd) (wDays l))) + 6) `mod` 7)] -- %A: day of week, long form (fst from wDays locale), Sunday - Saturday - 'A' -> [WeekDay (1 + (fromJust (elemIndex x (map fst (wDays l))) + 6) `mod` 7)] + 'A' -> [WeekDay (1 + (fromJust (elemIndex (up x) (map (up . fst) (wDays l))) + 6) `mod` 7)] -- %U: week number of year, where weeks start on Sunday (as sundayStartWeek), 01 - 53 'U' -> [Week SundayWeek (read x)] -- %w: day of week number, 0 (= Sunday) - 6 (= Saturday) @@ -248,8 +263,8 @@ instance ParseTime TimeOfDay where where f t@(TimeOfDay h m s) (c,x) = case c of - 'P' -> if x == map toLower (fst (amPm l)) then am else pm - 'p' -> if x == fst (amPm l) then am else pm + 'P' -> if up x == fst (amPm l) then am else pm + 'p' -> if up x == fst (amPm l) then am else pm 'H' -> TimeOfDay (read x) m s 'I' -> TimeOfDay (read x) m s 'k' -> TimeOfDay (read x) m s @@ -280,10 +295,10 @@ instance ParseTime TimeZone where case c of 'z' -> zone 'Z' | null x -> t - | isUpper (head x) -> - case lookup x _TIMEZONES_ of - Just (offset', dst') -> TimeZone offset' dst' x - Nothing -> TimeZone offset dst x + | isAlpha (head x) -> let y = up x in + case lookup y _TIMEZONES_ of + Just (offset', dst') -> TimeZone offset' dst' y + Nothing -> TimeZone offset dst y | otherwise -> zone _ -> t where zone = TimeZone (readTzOffset x) dst name From git at git.haskell.org Fri Jan 23 22:59:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:23 +0000 (UTC) Subject: [commit: packages/time] master: clean up .cabal; first attempt at Windows compilability (1e426ff) Message-ID: <20150123225923.A73CD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1e426fff781e9bee333e4c1d0ffe28ebbe9360b4 >--------------------------------------------------------------- commit 1e426fff781e9bee333e4c1d0ffe28ebbe9360b4 Author: Ashley Yakeley Date: Thu Apr 16 23:36:49 2009 -0700 clean up .cabal; first attempt at Windows compilability darcs-hash:20090417063649-ac6dd-223499b4d550028c3f5cc97094745c4eb72ca60e >--------------------------------------------------------------- 1e426fff781e9bee333e4c1d0ffe28ebbe9360b4 Setup.hs | 6 +++-- include/HsTime.h | 4 ++++ time.cabal | 69 +++++++++++++++++++++++++++++++------------------------- 3 files changed, 46 insertions(+), 33 deletions(-) diff --git a/Setup.hs b/Setup.hs index 2211a91..ac50db8 100644 --- a/Setup.hs +++ b/Setup.hs @@ -7,10 +7,12 @@ import Distribution.Simple.LocalBuildInfo import Distribution.Simple.Utils import System.Cmd import System.Directory +import System.Info main :: IO () -main = do let hooks = autoconfUserHooks { runTests = runTestScript } - defaultMainWithHooks hooks +main = if os == "windows" + then defaultMain + else let hooks = autoconfUserHooks { runTests = runTestScript } in defaultMainWithHooks hooks withCurrentDirectory :: FilePath -> IO a -> IO a withCurrentDirectory path f = do diff --git a/include/HsTime.h b/include/HsTime.h index c02cc53..12d45bd 100644 --- a/include/HsTime.h +++ b/include/HsTime.h @@ -1,6 +1,9 @@ #ifndef __HSTIME_H__ #define __HSTIME_H__ +#if defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32) +#else + #include "HsTimeConfig.h" // Otherwise these clash with similar definitions from other packages: #undef PACKAGE_BUGREPORT @@ -12,6 +15,7 @@ #if HAVE_TIME_H #include #endif +#endif long int get_current_timezone_seconds (time_t,int* pdst,char const* * pname); diff --git a/time.cabal b/time.cabal index 84b17b5..2850397 100644 --- a/time.cabal +++ b/time.cabal @@ -1,36 +1,42 @@ -Name: time -Version: 1.1.2.3 -Stability: stable -License: BSD3 -License-File: LICENSE -Author: Ashley Yakeley -Maintainer: -Homepage: http://semantic.org/TimeLib/ -Synopsis: A time library -Description: A time library -Category: System -Build-Type: Custom -Cabal-Version: >=1.2 +name: time +version: 1.1.2.4 +stability: stable +license: BSD3 +license-file: LICENSE +author: Ashley Yakeley +maintainer: +homepage: http://semantic.org/TimeLib/ +synopsis: A time library +description: A time library +category: System +build-type: Custom +cabal-version: >=1.2 x-follows-version-policy: -Extra-Source-Files: - aclocal.m4 configure.ac configure - include/HsTime.h include/HsTimeConfig.h.in -Extra-Tmp-Files: - config.log config.status autom4te.cache - include/HsTimeConfig.h +extra-source-files: + aclocal.m4 + configure.ac + configure + include/HsTime.h + include/HsTimeConfig.h.in +extra-tmp-files: + config.log + config.status + autom4te.cache + include/HsTimeConfig.h -Flag split-base +flag split-base -Library { - Build-Depends: base >= 2 +library +{ + build-depends: base >= 2 if flag(split-base) - Build-Depends: base >= 3, old-locale + Build-Depends: base >= 3, old-locale else - Build-Depends: base < 3 + Build-Depends: base < 3 if os(windows) Build-Depends: Win32 - Exposed-Modules: + exposed-modules: Data.Time.Calendar, Data.Time.Calendar.MonthDay, Data.Time.Calendar.OrdinalDate, @@ -43,9 +49,9 @@ Library { Data.Time.LocalTime, Data.Time.Format, Data.Time - Extensions: ForeignFunctionInterface, CPP - C-Sources: cbits/HsTime.c - Other-Modules: + extensions: ForeignFunctionInterface, CPP + c-sources: cbits/HsTime.c + other-modules: Data.Time.Calendar.Private, Data.Time.Calendar.Days, Data.Time.Calendar.Gregorian, @@ -58,8 +64,9 @@ Library { Data.Time.LocalTime.TimeOfDay, Data.Time.LocalTime.LocalTime, Data.Time.Format.Parse - Include-Dirs: include - Install-Includes: - HsTime.h HsTimeConfig.h + include-dirs: include + install-includes: + HsTime.h + HsTimeConfig.h } From git at git.haskell.org Fri Jan 23 22:59:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:25 +0000 (UTC) Subject: [commit: packages/time] master: get building on Windows (89e52b0) Message-ID: <20150123225925.ADAEF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/89e52b024e4b9600af3bb30debd6ac43711cdc04 >--------------------------------------------------------------- commit 89e52b024e4b9600af3bb30debd6ac43711cdc04 Author: ashley Date: Fri Apr 17 00:58:14 2009 -0700 get building on Windows Ignore-this: 7f61aa6f76736ff855aa665991f2a2c6 darcs-hash:20090417075814-ca2d0-d459b191878a61b0ac33b05230ecba1d94f93e69 >--------------------------------------------------------------- 89e52b024e4b9600af3bb30debd6ac43711cdc04 Setup.hs | 7 ++++--- include/HsTime.h | 3 ++- time.cabal | 10 +++++++--- 3 files changed, 13 insertions(+), 7 deletions(-) diff --git a/Setup.hs b/Setup.hs index ac50db8..cdd46de 100644 --- a/Setup.hs +++ b/Setup.hs @@ -10,9 +10,10 @@ import System.Directory import System.Info main :: IO () -main = if os == "windows" - then defaultMain - else let hooks = autoconfUserHooks { runTests = runTestScript } in defaultMainWithHooks hooks +main = case os of + "windows" -> defaultMain + "mingw32" -> defaultMain + _ -> let hooks = autoconfUserHooks { runTests = runTestScript } in defaultMainWithHooks hooks withCurrentDirectory :: FilePath -> IO a -> IO a withCurrentDirectory path f = do diff --git a/include/HsTime.h b/include/HsTime.h index 12d45bd..5296437 100644 --- a/include/HsTime.h +++ b/include/HsTime.h @@ -2,6 +2,7 @@ #define __HSTIME_H__ #if defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32) +#define HAVE_TIME_H 1 #else #include "HsTimeConfig.h" @@ -11,11 +12,11 @@ #undef PACKAGE_STRING #undef PACKAGE_TARNAME #undef PACKAGE_VERSION +#endif #if HAVE_TIME_H #include #endif -#endif long int get_current_timezone_seconds (time_t,int* pdst,char const* * pname); diff --git a/time.cabal b/time.cabal index 2850397..9c74c9e 100644 --- a/time.cabal +++ b/time.cabal @@ -65,8 +65,12 @@ library Data.Time.LocalTime.LocalTime, Data.Time.Format.Parse include-dirs: include - install-includes: - HsTime.h - HsTimeConfig.h + if os(windows) + install-includes: + HsTime.h + else + install-includes: + HsTime.h + HsTimeConfig.h } From git at git.haskell.org Fri Jan 23 22:59:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:27 +0000 (UTC) Subject: [commit: packages/time] master: next version will be 1.1.3 (1b7d9c2) Message-ID: <20150123225927.B3F6E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1b7d9c29efb67bcc7488cb67bd8c964fa1582d1c >--------------------------------------------------------------- commit 1b7d9c29efb67bcc7488cb67bd8c964fa1582d1c Author: Ashley Yakeley Date: Sun Apr 26 17:07:46 2009 -0700 next version will be 1.1.3 Ignore-this: 5ba6f9cb1bf0e27b3f461f77ac6a9787 darcs-hash:20090427000746-ac6dd-4a8d881865f225955e9445bfc0aa33e3748ac158 >--------------------------------------------------------------- 1b7d9c29efb67bcc7488cb67bd8c964fa1582d1c time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 9c74c9e..a5bc5b2 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.1.2.4 +version: 1.1.3 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 22:59:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:29 +0000 (UTC) Subject: [commit: packages/time] master: Typeable instances for all types (1b0f97e) Message-ID: <20150123225929.BAE2C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1b0f97ef5603d21c23a8db6485e2aeb602196cb5 >--------------------------------------------------------------- commit 1b0f97ef5603d21c23a8db6485e2aeb602196cb5 Author: Ashley Yakeley Date: Sun Apr 26 17:48:05 2009 -0700 Typeable instances for all types Ignore-this: 48421f072110ddf70b09bd4c030af863 darcs-hash:20090427004805-ac6dd-4cf4de606d27096343156c687b2a37991e055312 >--------------------------------------------------------------- 1b0f97ef5603d21c23a8db6485e2aeb602196cb5 Data/Time/Calendar/Days.hs | 4 ++++ Data/Time/Clock/Scale.hs | 7 +++++++ Data/Time/Clock/TAI.hs | 4 ++++ Data/Time/Clock/UTC.hs | 7 +++++++ Data/Time/LocalTime/LocalTime.hs | 7 +++++++ Data/Time/LocalTime/TimeOfDay.hs | 4 ++++ Data/Time/LocalTime/TimeZone.hs | 4 ++++ 7 files changed, 37 insertions(+) diff --git a/Data/Time/Calendar/Days.hs b/Data/Time/Calendar/Days.hs index 2e62400..ad493c4 100644 --- a/Data/Time/Calendar/Days.hs +++ b/Data/Time/Calendar/Days.hs @@ -6,10 +6,14 @@ module Data.Time.Calendar.Days ) where import Data.Ix +import Data.Typeable -- | The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17. newtype Day = ModifiedJulianDay {toModifiedJulianDay :: Integer} deriving (Eq,Ord) +instance Typeable Day where + typeOf _ = mkTyConApp (mkTyCon "Data.Time.Calendar.Days.Day") [] + -- necessary because H98 doesn't have "cunning newtype" derivation instance Enum Day where succ (ModifiedJulianDay a) = ModifiedJulianDay (succ a) diff --git a/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs index 30f585b..101b770 100644 --- a/Data/Time/Clock/Scale.hs +++ b/Data/Time/Clock/Scale.hs @@ -12,16 +12,23 @@ module Data.Time.Clock.Scale import Data.Ratio ((%)) import Data.Fixed +import Data.Typeable -- | The Modified Julian Date is the day with the fraction of the day, measured from UT midnight. -- It's used to represent UT1, which is time as measured by the earth's rotation, adjusted for various wobbles. newtype UniversalTime = ModJulianDate {getModJulianDate :: Rational} deriving (Eq,Ord) +instance Typeable UniversalTime where + typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.Scale.UniversalTime") [] + -- | This is a length of time, as measured by a clock. -- Conversion functions will treat it as seconds. -- It has a precision of 10^-12 s. newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord) +instance Typeable DiffTime where + typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.Scale.DiffTime") [] + -- necessary because H98 doesn't have "cunning newtype" derivation instance Enum DiffTime where succ (MkDiffTime a) = MkDiffTime (succ a) diff --git a/Data/Time/Clock/TAI.hs b/Data/Time/Clock/TAI.hs index 835746c..a43e75e 100644 --- a/Data/Time/Clock/TAI.hs +++ b/Data/Time/Clock/TAI.hs @@ -16,11 +16,15 @@ module Data.Time.Clock.TAI import Data.Time.LocalTime import Data.Time.Calendar.Days import Data.Time.Clock +import Data.Typeable import Data.Fixed -- | AbsoluteTime is TAI, time as measured by a clock. newtype AbsoluteTime = MkAbsoluteTime {unAbsoluteTime :: DiffTime} deriving (Eq,Ord) +instance Typeable AbsoluteTime where + typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.TAI.AbsoluteTime") [] + instance Show AbsoluteTime where show t = show (utcToLocalTime utc (taiToUTCTime (const 0) t)) ++ " TAI" -- ugly, but standard apparently diff --git a/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs index e28ce77..74df8d7 100644 --- a/Data/Time/Clock/UTC.hs +++ b/Data/Time/Clock/UTC.hs @@ -16,6 +16,7 @@ module Data.Time.Clock.UTC import Data.Time.Calendar.Days import Data.Time.Clock.Scale import Data.Fixed +import Data.Typeable -- | This is the simplest representation of UTC. -- It consists of the day number, and a time offset from midnight. @@ -27,6 +28,9 @@ data UTCTime = UTCTime { utctDayTime :: DiffTime } +instance Typeable UTCTime where + typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.UTC.UTCTime") [] + instance Eq UTCTime where (UTCTime da ta) == (UTCTime db tb) = (da == db) && (ta == tb) @@ -43,6 +47,9 @@ instance Ord UTCTime where -- regardless of whether a leap-second intervened. newtype NominalDiffTime = MkNominalDiffTime Pico deriving (Eq,Ord) +instance Typeable NominalDiffTime where + typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.UTC.NominalDiffTime") [] + instance Enum NominalDiffTime where succ (MkNominalDiffTime a) = MkNominalDiffTime (succ a) pred (MkNominalDiffTime a) = MkNominalDiffTime (pred a) diff --git a/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs index 6d8f219..7125a55 100644 --- a/Data/Time/LocalTime/LocalTime.hs +++ b/Data/Time/LocalTime/LocalTime.hs @@ -16,6 +16,7 @@ import Data.Time.LocalTime.TimeOfDay import Data.Time.LocalTime.TimeZone import Data.Time.Calendar import Data.Time.Clock +import Data.Typeable -- | A simple day and time aggregate, where the day is of the specified parameter, -- and the time is a TimeOfDay. @@ -26,6 +27,9 @@ data LocalTime = LocalTime { localTimeOfDay :: TimeOfDay } deriving (Eq,Ord) +instance Typeable LocalTime where + typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.LocalTime.LocalTime") [] + instance Show LocalTime where show (LocalTime d t) = (showGregorian d) ++ " " ++ (show t) @@ -56,6 +60,9 @@ data ZonedTime = ZonedTime { zonedTimeZone :: TimeZone } +instance Typeable ZonedTime where + typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.LocalTime.ZonedTime") [] + utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime utcToZonedTime zone time = ZonedTime (utcToLocalTime zone time) zone diff --git a/Data/Time/LocalTime/TimeOfDay.hs b/Data/Time/LocalTime/TimeOfDay.hs index 8134d1d..c0b4608 100644 --- a/Data/Time/LocalTime/TimeOfDay.hs +++ b/Data/Time/LocalTime/TimeOfDay.hs @@ -11,6 +11,7 @@ module Data.Time.LocalTime.TimeOfDay import Data.Time.LocalTime.TimeZone import Data.Time.Calendar.Private import Data.Time.Clock +import Data.Typeable import Data.Fixed -- | Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day. @@ -24,6 +25,9 @@ data TimeOfDay = TimeOfDay { todSec :: Pico } deriving (Eq,Ord) +instance Typeable TimeOfDay where + typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.TimeOfDay.TimeOfDay") [] + -- | Hour zero midnight :: TimeOfDay midnight = TimeOfDay 0 0 0 diff --git a/Data/Time/LocalTime/TimeZone.hs b/Data/Time/LocalTime/TimeZone.hs index da4a9cb..34c85a5 100644 --- a/Data/Time/LocalTime/TimeZone.hs +++ b/Data/Time/LocalTime/TimeZone.hs @@ -17,6 +17,7 @@ import Data.Time.Clock.POSIX import Foreign import Foreign.C +import Data.Typeable -- | A TimeZone is a whole number of minutes offset from UTC, together with a name and a \"just for summer\" flag. data TimeZone = TimeZone { @@ -28,6 +29,9 @@ data TimeZone = TimeZone { timeZoneName :: String } deriving (Eq,Ord) +instance Typeable TimeZone where + typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.TimeZone.TimeZone") [] + -- | Create a nameless non-summer timezone for this number of minutes minutesToTimeZone :: Int -> TimeZone minutesToTimeZone m = TimeZone m False "" From git at git.haskell.org Fri Jan 23 22:59:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:31 +0000 (UTC) Subject: [commit: packages/time] master: cap in .cabal (6d9856b) Message-ID: <20150123225931.C2F4E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/6d9856b700ad8c10333f344b06ddfa1c4555b8e7 >--------------------------------------------------------------- commit 6d9856b700ad8c10333f344b06ddfa1c4555b8e7 Author: Ashley Yakeley Date: Mon Jun 1 21:04:36 2009 -0700 cap in .cabal Ignore-this: edc82bb754c59d5acd39a6d8b4c75cd4 darcs-hash:20090602040436-ac6dd-ae0eacca055d2f75b4d1410707434625c4e288b7 >--------------------------------------------------------------- 6d9856b700ad8c10333f344b06ddfa1c4555b8e7 time.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/time.cabal b/time.cabal index a5bc5b2..15bde6b 100644 --- a/time.cabal +++ b/time.cabal @@ -31,11 +31,11 @@ library { build-depends: base >= 2 if flag(split-base) - Build-Depends: base >= 3, old-locale + build-depends: base >= 3, old-locale else - Build-Depends: base < 3 + build-depends: base < 3 if os(windows) - Build-Depends: Win32 + build-depends: Win32 exposed-modules: Data.Time.Calendar, Data.Time.Calendar.MonthDay, From git at git.haskell.org Fri Jan 23 22:59:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:33 +0000 (UTC) Subject: [commit: packages/time] master: add validating converters (0cf7847) Message-ID: <20150123225933.CD1663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/0cf7847561972882b17979ca1213525f8cba5ae2 >--------------------------------------------------------------- commit 0cf7847561972882b17979ca1213525f8cba5ae2 Author: Ashley Yakeley Date: Mon Jun 1 23:51:42 2009 -0700 add validating converters Ignore-this: 4b18a44adbcb288e62f8dbce1377be8b darcs-hash:20090602065142-ac6dd-8e4090d57516369e58f07fbf5872fadd5b30db9c >--------------------------------------------------------------- 0cf7847561972882b17979ca1213525f8cba5ae2 Data/Time/Calendar/Gregorian.hs | 9 ++++++++- Data/Time/Calendar/Julian.hs | 9 ++++++++- Data/Time/Calendar/JulianYearDay.hs | 10 ++++++++++ Data/Time/Calendar/MonthDay.hs | 14 +++++++++++++- Data/Time/Calendar/OrdinalDate.hs | 10 ++++++++++ Data/Time/Calendar/Private.hs | 5 +++++ Data/Time/Calendar/WeekDate.hs | 14 ++++++++++++++ test/ConvertBack.hs | 17 +++++++++++------ 8 files changed, 79 insertions(+), 9 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0cf7847561972882b17979ca1213525f8cba5ae2 From git at git.haskell.org Fri Jan 23 22:59:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:35 +0000 (UTC) Subject: [commit: packages/time] master: use base==4.* (1a31e47) Message-ID: <20150123225935.D3E083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1a31e473c9c5827233abb7d7eccbd81ffdc16fa2 >--------------------------------------------------------------- commit 1a31e473c9c5827233abb7d7eccbd81ffdc16fa2 Author: Ashley Yakeley Date: Wed Jun 17 01:48:43 2009 -0700 use base==4.* Ignore-this: e37c8cafd9ef17ff3eff6980162e41e5 darcs-hash:20090617084843-ac6dd-bb32d062e0f968ce9f7cd3f1cd0ab09732956943 >--------------------------------------------------------------- 1a31e473c9c5827233abb7d7eccbd81ffdc16fa2 time.cabal | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/time.cabal b/time.cabal index 15bde6b..ef27092 100644 --- a/time.cabal +++ b/time.cabal @@ -25,15 +25,9 @@ extra-tmp-files: autom4te.cache include/HsTimeConfig.h -flag split-base - library { - build-depends: base >= 2 - if flag(split-base) - build-depends: base >= 3, old-locale - else - build-depends: base < 3 + build-depends: base == 4.*, old-locale if os(windows) build-depends: Win32 exposed-modules: From git at git.haskell.org Fri Jan 23 22:59:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:37 +0000 (UTC) Subject: [commit: packages/time] master: add validating constructors (9884b31) Message-ID: <20150123225937.DACDC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/9884b31fcca197b64f6e356142d9d99e1422ab38 >--------------------------------------------------------------- commit 9884b31fcca197b64f6e356142d9d99e1422ab38 Author: Ashley Yakeley Date: Wed Jun 17 01:49:36 2009 -0700 add validating constructors Ignore-this: e01e75f9d860f34285265b39b20cf225 darcs-hash:20090617084936-ac6dd-5ecf266acb8e2dabaa0b7a33fc2cda0cf6d44727 >--------------------------------------------------------------- 9884b31fcca197b64f6e356142d9d99e1422ab38 Data/Time/Calendar/OrdinalDate.hs | 31 +++++++++++++++++++++++++++++++ Data/Time/LocalTime/TimeOfDay.hs | 9 ++++++++- 2 files changed, 39 insertions(+), 1 deletion(-) diff --git a/Data/Time/Calendar/OrdinalDate.hs b/Data/Time/Calendar/OrdinalDate.hs index 327c561..4e5b2b9 100644 --- a/Data/Time/Calendar/OrdinalDate.hs +++ b/Data/Time/Calendar/OrdinalDate.hs @@ -79,6 +79,21 @@ fromMondayStartWeek y w d = ModifiedJulianDay (firstDay + yd) -- 0-based year day of first monday of the year firstMonday = (5 - firstDay) `mod` 7 +fromMondayStartWeekValid :: Integer -- ^ Year. + -> Int -- ^ Monday-starting week number. + -> Int -- ^ Day of week. + -- Monday is 1, Sunday is 7 (as \"%u\" in 'Data.Time.Format.formatTime'). + -> Maybe Day +fromMondayStartWeekValid year w d = do + d' <- clipValid 1 7 d + -- first day of the year + let firstDay = toModifiedJulianDay (fromOrdinalDate year 1) + -- 0-based year day of first monday of the year + let firstMonday = (5 - firstDay) `mod` 7 + let yd = firstMonday + 7 * toInteger (w-1) + toInteger d' + yd' <- clipValid 1 (if isLeapYear year then 366 else 365) yd + return (ModifiedJulianDay (firstDay - 1 + yd')) + -- | The inverse of 'sundayStartWeek'. Get a 'Day' given the year and -- the number of the day of a Sunday-starting week. -- The first Sunday is the first day of week 1, any earlier days in the @@ -94,3 +109,19 @@ fromSundayStartWeek y w d = ModifiedJulianDay (firstDay + yd) firstDay = toModifiedJulianDay (fromOrdinalDate y 1) -- 0-based year day of first sunday of the year firstSunday = (4 - firstDay) `mod` 7 + +fromSundayStartWeekValid :: Integer -- ^ Year. + -> Int -- ^ Monday-starting week number. + -> Int -- ^ Day of week. + -- Monday is 1, Sunday is 7 (as \"%u\" in 'Data.Time.Format.formatTime'). + -> Maybe Day +fromSundayStartWeekValid year w d = do + d' <- clipValid 1 7 d + -- first day of the year + let firstDay = toModifiedJulianDay (fromOrdinalDate year 1) + -- 0-based year day of first sunday of the year + let firstMonday = (4 - firstDay) `mod` 7 + let yd = firstMonday + 7 * toInteger (w-1) + toInteger d' + yd' <- clipValid 1 (if isLeapYear year then 366 else 365) yd + return (ModifiedJulianDay (firstDay - 1 + yd')) + diff --git a/Data/Time/LocalTime/TimeOfDay.hs b/Data/Time/LocalTime/TimeOfDay.hs index c0b4608..9639545 100644 --- a/Data/Time/LocalTime/TimeOfDay.hs +++ b/Data/Time/LocalTime/TimeOfDay.hs @@ -2,7 +2,7 @@ module Data.Time.LocalTime.TimeOfDay ( -- * Time of day - TimeOfDay(..),midnight,midday, + TimeOfDay(..),midnight,midday,makeTimeOfDayValid, utcToLocalTimeOfDay,localToUTCTimeOfDay, timeToTimeOfDay,timeOfDayToTime, dayFractionToTimeOfDay,timeOfDayToDayFraction @@ -39,6 +39,13 @@ midday = TimeOfDay 12 0 0 instance Show TimeOfDay where show (TimeOfDay h m s) = (show2 h) ++ ":" ++ (show2 m) ++ ":" ++ (show2Fixed s) +makeTimeOfDayValid :: Int -> Int -> Pico -> Maybe TimeOfDay +makeTimeOfDayValid h m s = do + clipValid 0 23 h + clipValid 0 59 m + clipValid 0 60.999999999999 s + return (TimeOfDay h m s) + -- | Convert a ToD in UTC to a ToD in some timezone, together with a day adjustment. utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer,TimeOfDay) utcToLocalTimeOfDay zone (TimeOfDay h m s) = (fromIntegral (div h' 24),TimeOfDay (mod h' 24) (mod m' 60) s) where From git at git.haskell.org Fri Jan 23 22:59:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:39 +0000 (UTC) Subject: [commit: packages/time] master: version 1.1.4 (2c8d2f1) Message-ID: <20150123225939.E30D13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2c8d2f18f7ac245413c03b10589f0a9c479b03f7 >--------------------------------------------------------------- commit 2c8d2f18f7ac245413c03b10589f0a9c479b03f7 Author: Ashley Yakeley Date: Sat Jul 11 00:50:07 2009 -0700 version 1.1.4 Ignore-this: e431293abfeda1f8459f0b737d23fd7b darcs-hash:20090711075007-ac6dd-296363021486c36779a7414beb5df74b6891096d >--------------------------------------------------------------- 2c8d2f18f7ac245413c03b10589f0a9c479b03f7 time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index ef27092..943570a 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.1.3 +version: 1.1.4 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 22:59:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:41 +0000 (UTC) Subject: [commit: packages/time] master: formatTime: glibc-style modifier flags (2dc3703) Message-ID: <20150123225941.EB6B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2dc370310ded2f5d49393b15aa06cb5fe37a5fe4 >--------------------------------------------------------------- commit 2dc370310ded2f5d49393b15aa06cb5fe37a5fe4 Author: Ashley Yakeley Date: Sat Jul 11 01:01:32 2009 -0700 formatTime: glibc-style modifier flags Ignore-this: 8331c2248a9b7613bec5547b491345e4 darcs-hash:20090711080132-ac6dd-d47e07a220f2aeb88b27e621fdcf3c3498fb8875 >--------------------------------------------------------------- 2dc370310ded2f5d49393b15aa06cb5fe37a5fe4 Data/Time/Calendar/Gregorian.hs | 2 +- Data/Time/Calendar/Julian.hs | 2 +- Data/Time/Calendar/JulianYearDay.hs | 2 +- Data/Time/Calendar/OrdinalDate.hs | 2 +- Data/Time/Calendar/Private.hs | 48 ++++++------ Data/Time/Calendar/WeekDate.hs | 4 +- Data/Time/Format.hs | 143 ++++++++++++++++++++---------------- Data/Time/LocalTime/TimeOfDay.hs | 2 +- Data/Time/LocalTime/TimeZone.hs | 14 ++-- test/TestFormat.hs | 21 +++++- 10 files changed, 137 insertions(+), 103 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2dc370310ded2f5d49393b15aa06cb5fe37a5fe4 From git at git.haskell.org Fri Jan 23 22:59:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:43 +0000 (UTC) Subject: [commit: packages/time] master: update cabal-version constraint (2084584) Message-ID: <20150123225943.F39043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2084584ab23d68190b1962a83dce55364fe59fa3 >--------------------------------------------------------------- commit 2084584ab23d68190b1962a83dce55364fe59fa3 Author: Ross Paterson Date: Fri Jul 17 09:02:55 2009 -0700 update cabal-version constraint Ignore-this: 8afa55b6e44d52192aca8b1c94e59b4a The syntax 'base == 4.*' requires cabal version 1.6 or later. darcs-hash:20090717160255-b47d3-1ea8d54339e500897925ccd5fc60b37769f4e12f >--------------------------------------------------------------- 2084584ab23d68190b1962a83dce55364fe59fa3 time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 943570a..b86a5cf 100644 --- a/time.cabal +++ b/time.cabal @@ -10,7 +10,7 @@ synopsis: A time library description: A time library category: System build-type: Custom -cabal-version: >=1.2 +cabal-version: >=1.6 x-follows-version-policy: extra-source-files: From git at git.haskell.org Fri Jan 23 22:59:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:46 +0000 (UTC) Subject: [commit: packages/time] master: copyright date (f071372) Message-ID: <20150123225946.063BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f0713723994cc5ddbcbd7243aaf893ba942fb187 >--------------------------------------------------------------- commit f0713723994cc5ddbcbd7243aaf893ba942fb187 Author: Ashley Yakeley Date: Sat Apr 10 20:25:06 2010 -0700 copyright date Ignore-this: 198dfe29d0077290f955c72688527bc8 darcs-hash:20100411032506-ac6dd-104beb14b3799423c78ee5053baf16cd9dd18c41 >--------------------------------------------------------------- f0713723994cc5ddbcbd7243aaf893ba942fb187 LICENSE | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/LICENSE b/LICENSE index af649fe..485d7f6 100644 --- a/LICENSE +++ b/LICENSE @@ -1,4 +1,4 @@ -TimeLib is Copyright (c) Ashley Yakeley, 2004-2007. +TimeLib is Copyright (c) Ashley Yakeley, 2004-2010. All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: From git at git.haskell.org Fri Jan 23 22:59:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:48 +0000 (UTC) Subject: [commit: packages/time] master: sort out GHC 6.12 warnings (66ee658) Message-ID: <20150123225948.0CBAE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/66ee658898559bfff6f7de50015f4827f5e7a967 >--------------------------------------------------------------- commit 66ee658898559bfff6f7de50015f4827f5e7a967 Author: Ashley Yakeley Date: Sat Apr 10 20:34:14 2010 -0700 sort out GHC 6.12 warnings Ignore-this: f97673c30230c03de97445fbab0e4bf6 darcs-hash:20100411033414-ac6dd-1c96f2e3e15eb0296f7e20aaf5b695b7dff225ef >--------------------------------------------------------------- 66ee658898559bfff6f7de50015f4827f5e7a967 Data/Time/Format/Parse.hs | 2 +- Data/Time/LocalTime/TimeOfDay.hs | 6 +++--- Makefile | 2 +- time.cabal | 1 + 4 files changed, 6 insertions(+), 5 deletions(-) diff --git a/Data/Time/Format/Parse.hs b/Data/Time/Format/Parse.hs index 1aaf0d0..d30d75c 100644 --- a/Data/Time/Format/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -33,7 +33,7 @@ string :: String -> ReadP String string this = do s <- look; scan this s where scan [] _ = do return this - scan (x:xs) (y:ys) | toUpper x == toUpper y = do get; scan xs ys + scan (x:xs) (y:ys) | toUpper x == toUpper y = do _ <- get; scan xs ys scan _ _ = do pfail -- | Convert string to upper case. up :: String -> String diff --git a/Data/Time/LocalTime/TimeOfDay.hs b/Data/Time/LocalTime/TimeOfDay.hs index 8b5ef19..1a360b7 100644 --- a/Data/Time/LocalTime/TimeOfDay.hs +++ b/Data/Time/LocalTime/TimeOfDay.hs @@ -41,9 +41,9 @@ instance Show TimeOfDay where makeTimeOfDayValid :: Int -> Int -> Pico -> Maybe TimeOfDay makeTimeOfDayValid h m s = do - clipValid 0 23 h - clipValid 0 59 m - clipValid 0 60.999999999999 s + _ <- clipValid 0 23 h + _ <- clipValid 0 59 m + _ <- clipValid 0 60.999999999999 s return (TimeOfDay h m s) -- | Convert a ToD in UTC to a ToD in some timezone, together with a day adjustment. diff --git a/Makefile b/Makefile index 1b6d17b..d56bf1a 100644 --- a/Makefile +++ b/Makefile @@ -9,7 +9,7 @@ configure: cabal configure --enable-library-profiling --enable-executable-profiling build: configure - cabal build --ghc-options="-Wall -Werror" + cabal build --ghc-options=-Werror test: build cabal test diff --git a/time.cabal b/time.cabal index b86a5cf..51a77db 100644 --- a/time.cabal +++ b/time.cabal @@ -28,6 +28,7 @@ extra-tmp-files: library { build-depends: base == 4.*, old-locale + ghc-options: -Wall if os(windows) build-depends: Win32 exposed-modules: From git at git.haskell.org Fri Jan 23 22:59:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:50 +0000 (UTC) Subject: [commit: packages/time] master: version 1.2; add Data instance, conditional on support (1bf713f) Message-ID: <20150123225950.14DFB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1bf713fdcc3d3e2e8bb85f261822ba5933c7a7cf >--------------------------------------------------------------- commit 1bf713fdcc3d3e2e8bb85f261822ba5933c7a7cf Author: Ashley Yakeley Date: Sat Apr 10 22:19:39 2010 -0700 version 1.2; add Data instance, conditional on support Ignore-this: fd76cc60dee7fdee543cf9156d7be919 darcs-hash:20100411051939-ac6dd-28dd1696fee060935dbe26a49da0f53dc0f4490d >--------------------------------------------------------------- 1bf713fdcc3d3e2e8bb85f261822ba5933c7a7cf Data/Time/Calendar/Days.hs | 13 ++++++++++++- Data/Time/Clock/Scale.hs | 21 +++++++++++++++++++-- Data/Time/Clock/TAI.hs | 13 ++++++++++++- Data/Time/Clock/UTC.hs | 18 +++++++++++++++++- Data/Time/Format/Parse.hs | 13 ++++++++++++- Data/Time/LocalTime/LocalTime.hs | 18 +++++++++++++++++- Data/Time/LocalTime/TimeOfDay.hs | 13 ++++++++++++- Data/Time/LocalTime/TimeZone.hs | 13 ++++++++++++- time.cabal | 9 ++++++++- 9 files changed, 121 insertions(+), 10 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1bf713fdcc3d3e2e8bb85f261822ba5933c7a7cf From git at git.haskell.org Fri Jan 23 22:59:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:52 +0000 (UTC) Subject: [commit: packages/time] master: fix tests (cec60a0) Message-ID: <20150123225952.1B4EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/cec60a0b5e84c4240d2fe0419b215f6fe3da43dc >--------------------------------------------------------------- commit cec60a0b5e84c4240d2fe0419b215f6fe3da43dc Author: Ashley Yakeley Date: Sat Apr 10 22:40:58 2010 -0700 fix tests Ignore-this: 98e1f1b38f6d01fbcaff8ffbc45ec492 darcs-hash:20100411054058-ac6dd-b658c36af21af9caa015dc3fda05bad7f53457fc >--------------------------------------------------------------- cec60a0b5e84c4240d2fe0419b215f6fe3da43dc Makefile | 2 +- test/AddDays.hs | 1 - test/Makefile | 4 +--- test/TestParseTime.hs | 1 - 4 files changed, 2 insertions(+), 6 deletions(-) diff --git a/Makefile b/Makefile index d56bf1a..de4898f 100644 --- a/Makefile +++ b/Makefile @@ -11,7 +11,7 @@ configure: build: configure cabal build --ghc-options=-Werror -test: build +test: install cabal test haddock: configure diff --git a/test/AddDays.hs b/test/AddDays.hs index 719f70a..a867905 100644 --- a/test/AddDays.hs +++ b/test/AddDays.hs @@ -3,7 +3,6 @@ module Main where import Data.Time.Calendar -import Control.Monad days ::[Day] days = diff --git a/test/Makefile b/test/Makefile index ecfaa96..307adcc 100644 --- a/test/Makefile +++ b/test/Makefile @@ -2,9 +2,7 @@ GHC = ghc GHCFLAGS = -package time default: - cd ..; runhaskell Setup.hs register --user --inplace make CurrentTime.run ShowDST.run test - cd ..; runhaskell Setup.hs unregister --user TestMonthDay: TestMonthDay.o $(GHC) $(GHCFLAGS) $^ -o $@ @@ -66,7 +64,7 @@ test: \ TestFormat.diff0 \ TestParseDAT.diff \ TestEaster.diff \ - TestParseTime.run \ +# TestParseTime.run \ UseCases.o clean: diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index 76b897a..b727f3f 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -6,7 +6,6 @@ import Data.Ratio import Data.Time import Data.Time.Calendar.OrdinalDate import Data.Time.Calendar.WeekDate -import Data.Time.Clock import Data.Time.Clock.POSIX import System.Locale import Test.QuickCheck From git at git.haskell.org Fri Jan 23 22:59:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:54 +0000 (UTC) Subject: [commit: packages/time] master: get working with both GHC 6.10 and 6.12 (f4a0fd3) Message-ID: <20150123225954.25DAC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f4a0fd3f8168c2ea9296eb96ec8acb1577be4561 >--------------------------------------------------------------- commit f4a0fd3f8168c2ea9296eb96ec8acb1577be4561 Author: Ashley Yakeley Date: Sun Apr 11 01:26:03 2010 -0700 get working with both GHC 6.10 and 6.12 Ignore-this: 700ee8cb739e67c438d40313d8e38378 darcs-hash:20100411082603-ac6dd-e5eaf0e878baa6b4348ccb11e1533d8279316952 >--------------------------------------------------------------- f4a0fd3f8168c2ea9296eb96ec8acb1577be4561 Data/Time/Calendar/Days.hs | 10 +++++----- Data/Time/Clock/Scale.hs | 17 ++++++++++------- Data/Time/Clock/TAI.hs | 12 +++++++----- Data/Time/Clock/UTC.hs | 18 +++++++++++------- Data/Time/Format/Parse.hs | 13 +++++++------ Data/Time/LocalTime/LocalTime.hs | 19 +++++++++++-------- Data/Time/LocalTime/TimeOfDay.hs | 12 +++++++----- Data/Time/LocalTime/TimeZone.hs | 10 +++++----- include/HsConfigure.h | 7 +++++++ time.cabal | 4 ++-- 10 files changed, 72 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f4a0fd3f8168c2ea9296eb96ec8acb1577be4561 From git at git.haskell.org Fri Jan 23 22:59:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:56 +0000 (UTC) Subject: [commit: packages/time] master: 1.2.0.1, include missing HsConfigure in sdist (bfa764f) Message-ID: <20150123225956.2C7CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/bfa764fe8086315833df9f74727951d7118e279d >--------------------------------------------------------------- commit bfa764fe8086315833df9f74727951d7118e279d Author: Ashley Yakeley Date: Sun Apr 11 13:35:07 2010 -0700 1.2.0.1, include missing HsConfigure in sdist Ignore-this: 78dfddb786e7c1103f1ea70a33a43683 darcs-hash:20100411203507-ac6dd-93f6581e5deec6bb709669222630b210dd3b2e55 >--------------------------------------------------------------- bfa764fe8086315833df9f74727951d7118e279d time.cabal | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 9b0d75e..22fa857 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.2 +version: 1.2.0.1 stability: stable license: BSD3 license-file: LICENSE @@ -17,6 +17,7 @@ extra-source-files: aclocal.m4 configure.ac configure + include/HsConfigure.h include/HsTime.h include/HsTimeConfig.h.in extra-tmp-files: From git at git.haskell.org Fri Jan 23 22:59:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 22:59:58 +0000 (UTC) Subject: [commit: packages/time] master: include test files in package (5c73538) Message-ID: <20150123225958.3413D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/5c73538f7d5ba0d850089b255360c5fb49f21ab7 >--------------------------------------------------------------- commit 5c73538f7d5ba0d850089b255360c5fb49f21ab7 Author: Ashley Yakeley Date: Mon Apr 26 23:55:11 2010 -0700 include test files in package Ignore-this: f13d5c23a548692e9700359316171b3f darcs-hash:20100427065511-ac6dd-0010c3787102b0df85f73274c78edf094d477936 >--------------------------------------------------------------- 5c73538f7d5ba0d850089b255360c5fb49f21ab7 time.cabal | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 22fa857..5db8d82 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.2.0.1 +version: 1.2.0.2 stability: stable license: BSD3 license-file: LICENSE @@ -20,6 +20,13 @@ extra-source-files: include/HsConfigure.h include/HsTime.h include/HsTimeConfig.h.in + test/Makefile + test/*.hs + test/*.lhs + test/*.ref + test/*.dat + test/*.c + test/*.h extra-tmp-files: config.log config.status From git at git.haskell.org Fri Jan 23 23:00:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:00 +0000 (UTC) Subject: [commit: packages/time] master: Fixed loss of accuracy in timeOfDayToDayFraction. (2677235) Message-ID: <20150123230000.3A3853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2677235d39a575502782af06898f3b80ee8a460c >--------------------------------------------------------------- commit 2677235d39a575502782af06898f3b80ee8a460c Author: Bjorn Buckwalter Date: Mon Jun 21 01:04:47 2010 -0700 Fixed loss of accuracy in timeOfDayToDayFraction. Ignore-this: 4ba8be01f14c2838bede8c16866ad134 darcs-hash:20100621080447-6cbaf-00ccf839cf4be9821b7c2456a4d96e29ec5753ea >--------------------------------------------------------------- 2677235d39a575502782af06898f3b80ee8a460c Data/Time/LocalTime/TimeOfDay.hs | 2 +- test/TestTime.hs | 10 ++++++++++ test/TestTime.ref | 5 +++++ 3 files changed, 16 insertions(+), 1 deletion(-) diff --git a/Data/Time/LocalTime/TimeOfDay.hs b/Data/Time/LocalTime/TimeOfDay.hs index e7618e4..37b2079 100644 --- a/Data/Time/LocalTime/TimeOfDay.hs +++ b/Data/Time/LocalTime/TimeOfDay.hs @@ -93,4 +93,4 @@ dayFractionToTimeOfDay df = timeToTimeOfDay (realToFrac (df * 86400)) -- | Get the fraction of a day since midnight given a TimeOfDay. timeOfDayToDayFraction :: TimeOfDay -> Rational -timeOfDayToDayFraction tod = realToFrac (timeOfDayToTime tod / posixDayLength) +timeOfDayToDayFraction tod = realToFrac (timeOfDayToTime tod) / realToFrac posixDayLength diff --git a/test/TestTime.hs b/test/TestTime.hs index 159d001..5fb35c2 100644 --- a/test/TestTime.hs +++ b/test/TestTime.hs @@ -80,8 +80,18 @@ testUT1 = do putStrLn (show (ut1ToLocalTime poslong (ModJulianDate 51604.0))) putStrLn (show (ut1ToLocalTime poslong (ModJulianDate 51604.5))) +testTimeOfDayToDayFraction :: IO () +testTimeOfDayToDayFraction = do + putStrLn "" + let f = dayFractionToTimeOfDay . timeOfDayToDayFraction + putStrLn (show (f (TimeOfDay 12 34 56.789))) + putStrLn (show (f (TimeOfDay 12 34 56.789123))) + putStrLn (show (f (TimeOfDay 12 34 56.789123456))) + putStrLn (show (f (TimeOfDay 12 34 56.789123456789))) + main :: IO () main = do testCal testUTC testUT1 + testTimeOfDayToDayFraction diff --git a/test/TestTime.ref b/test/TestTime.ref index 00cb151..9f8dd39 100644 --- a/test/TestTime.ref +++ b/test/TestTime.ref @@ -867,3 +867,8 @@ 2000-03-01 04:00:00 2000-03-01 08:00:00 2000-03-01 20:00:00 + +12:34:56.789 +12:34:56.789123 +12:34:56.789123456 +12:34:56.789123456789 From git at git.haskell.org Fri Jan 23 23:00:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:02 +0000 (UTC) Subject: [commit: packages/time] master: set version to 1.2.1 (5c06110) Message-ID: <20150123230002.422903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/5c06110cf659ea939b3cf1649224ef461e66330f >--------------------------------------------------------------- commit 5c06110cf659ea939b3cf1649224ef461e66330f Author: Ashley Yakeley Date: Mon Jun 21 01:35:26 2010 -0700 set version to 1.2.1 Ignore-this: 91693f57fdce225a96d5464e6b2fea8 darcs-hash:20100621083526-ac6dd-f26575ae0f18ee7643bcd4db109d27b10d87657a >--------------------------------------------------------------- 5c06110cf659ea939b3cf1649224ef461e66330f configure.ac | 2 +- time.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac index 885bb01..9b071fd 100644 --- a/configure.ac +++ b/configure.ac @@ -1,4 +1,4 @@ -AC_INIT([Haskell time package], [1.1.2.3], [ashley at semantic.org], [time]) +AC_INIT([Haskell time package], [1.2.1], [ashley at semantic.org], [time]) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([include/HsTime.h]) diff --git a/time.cabal b/time.cabal index 5db8d82..fff80ca 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.2.0.2 +version: 1.2.1 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 23:00:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:04 +0000 (UTC) Subject: [commit: packages/time] master: version 1.2.0.3 is more appropriate than 1.2.1. (aeb4c0e) Message-ID: <20150123230004.496DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/aeb4c0ea777413874e3c84b7159f45f9a6d012b2 >--------------------------------------------------------------- commit aeb4c0ea777413874e3c84b7159f45f9a6d012b2 Author: Ashley Yakeley Date: Mon Jun 21 20:58:47 2010 -0700 version 1.2.0.3 is more appropriate than 1.2.1. Ignore-this: 9f96c2b5545fc859d43ae3bb1284860a darcs-hash:20100622035847-ac6dd-e660685ec54477b1d73da5e537b1fe36c632a584 >--------------------------------------------------------------- aeb4c0ea777413874e3c84b7159f45f9a6d012b2 configure.ac | 2 +- time.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac index 9b071fd..b04e8cd 100644 --- a/configure.ac +++ b/configure.ac @@ -1,4 +1,4 @@ -AC_INIT([Haskell time package], [1.2.1], [ashley at semantic.org], [time]) +AC_INIT([Haskell time package], [1.2.0.3], [ashley at semantic.org], [time]) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([include/HsTime.h]) diff --git a/time.cabal b/time.cabal index fff80ca..3f88c02 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.2.1 +version: 1.2.0.3 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 23:00:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:06 +0000 (UTC) Subject: [commit: packages/time] master: test says Success (f3d2c2a) Message-ID: <20150123230006.4EB923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f3d2c2af9a0319280a3ea7ccba31a28ee2e62001 >--------------------------------------------------------------- commit f3d2c2af9a0319280a3ea7ccba31a28ee2e62001 Author: Ashley Yakeley Date: Sun Jan 23 17:55:11 2011 -0800 test says Success Ignore-this: 91a0f645a63f9a42877122ae2121f59f darcs-hash:20110124015511-ac6dd-71e1db4e1a45886cdb5038dc5ed3d4995b01258f >--------------------------------------------------------------- f3d2c2af9a0319280a3ea7ccba31a28ee2e62001 test/Makefile | 1 + 1 file changed, 1 insertion(+) diff --git a/test/Makefile b/test/Makefile index 307adcc..f97252e 100644 --- a/test/Makefile +++ b/test/Makefile @@ -66,6 +66,7 @@ test: \ TestEaster.diff \ # TestParseTime.run \ UseCases.o + @echo "Success!" clean: rm -rf TestMonthDay ConvertBack TestCalendars TestTime LongWeekYears ClipDates \ From git at git.haskell.org Fri Jan 23 23:00:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:08 +0000 (UTC) Subject: [commit: packages/time] master: fix parse "undefined" bug; added TestParseTime into tests (c5041a7) Message-ID: <20150123230008.568133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c5041a75c0c4ac903d4b6aa8ce4494b3fd75138b >--------------------------------------------------------------- commit c5041a75c0c4ac903d4b6aa8ce4494b3fd75138b Author: Ashley Yakeley Date: Wed Feb 2 21:32:19 2011 -0800 fix parse "undefined" bug; added TestParseTime into tests Ignore-this: aa74ebeef71272fda0a79962ed2e8f93 darcs-hash:20110203053219-ac6dd-38e9068fa7badb315aa19be8f1f77f75f06c03cc >--------------------------------------------------------------- c5041a75c0c4ac903d4b6aa8ce4494b3fd75138b Data/Time/Format.hs | 2 +- Data/Time/Format/Parse.hs | 7 ++++-- Makefile | 2 +- test/Makefile | 10 ++++---- test/TestFormat.hs | 59 +++++++++++++++++++++++++++++++++++++++++++++-- test/TestParseTime.hs | 42 +++++++++++++++++++++++---------- time.cabal | 2 +- 7 files changed, 99 insertions(+), 25 deletions(-) diff --git a/Data/Time/Format.hs b/Data/Time/Format.hs index 8d27f83..174bbea 100644 --- a/Data/Time/Format.hs +++ b/Data/Time/Format.hs @@ -55,7 +55,7 @@ formatChar c locale mpado t = case (formatCharacter c) of -- -- For 'TimeZone' (and 'ZonedTime' and 'UTCTime'): -- --- [@%z@] timezone offset on the format @-HHMM at . +-- [@%z@] timezone offset in the format @-HHMM at . -- -- [@%Z@] timezone name -- diff --git a/Data/Time/Format/Parse.hs b/Data/Time/Format/Parse.hs index 4fd2282..aa0b66d 100644 --- a/Data/Time/Format/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -179,10 +179,13 @@ parseValue l c = where oneOf = choice . map string digits n = count n (satisfy isDigit) - spdigits n = skipSpaces >> upTo n (satisfy isDigit) + spdigits n = skipSpaces >> oneUpTo n (satisfy isDigit) + oneUpTo :: Int -> ReadP a -> ReadP [a] + oneUpTo 0 _ = pfail + oneUpTo n x = liftM2 (:) x (upTo (n-1) x) upTo :: Int -> ReadP a -> ReadP [a] upTo 0 _ = return [] - upTo n x = liftM2 (:) x (upTo (n-1) x) <++ return [] + upTo n x = (oneUpTo n x) <++ return [] numericTZ = do s <- choice [char '+', char '-'] h <- digits 2 optional (char ':') diff --git a/Makefile b/Makefile index de4898f..a0b37a9 100644 --- a/Makefile +++ b/Makefile @@ -1,4 +1,4 @@ -default: build +default: install # Building diff --git a/test/Makefile b/test/Makefile index f97252e..5c1487a 100644 --- a/test/Makefile +++ b/test/Makefile @@ -64,26 +64,27 @@ test: \ TestFormat.diff0 \ TestParseDAT.diff \ TestEaster.diff \ -# TestParseTime.run \ + TestParseTime.run \ UseCases.o @echo "Success!" clean: rm -rf TestMonthDay ConvertBack TestCalendars TestTime LongWeekYears ClipDates \ AddDays TestFormat TestParseDAT TestEaster CurrentTime ShowDST TimeZone TimeZone.ref TestParseTime \ - *.out *.o *.hi Makefile.bak + *.out *.run *.o *.hi Makefile.bak %.diff: %.ref %.out diff -u $^ %.diff0: %.out - echo -n | diff -u - $^ + diff -u /dev/null $^ %.out: % ./$< > $@ %.run: % ./$< + touch $@ %.hi: %.o @: @@ -98,6 +99,3 @@ FORCE: .SECONDARY: -# TestTime.o TestFormat.o CurrentTime.o ShowDST.o TimeZone.o: $(patsubst %.hs,%.hi,$(SRCS)) - -TestFixed.o: ../Data/Fixed.hi diff --git a/test/TestFormat.hs b/test/TestFormat.hs index bcc18d4..65ca575 100644 --- a/test/TestFormat.hs +++ b/test/TestFormat.hs @@ -9,6 +9,7 @@ import Data.Char import System.Locale import Foreign import Foreign.C +import Control.Exception; {- size_t format_time ( @@ -93,9 +94,63 @@ formats = ["%G-W%V-%u","%U-%w","%W-%u"] ++ (fmap (\char -> '%':char:[]) chars) hashformats :: [String] hashformats = (fmap (\char -> '%':'#':char:[]) chars) +somestrings :: [String] +somestrings = ["", " ", "-", "\n"] + +getBottom :: a -> IO (Maybe Control.Exception.SomeException); +getBottom a = Control.Exception.catch (seq a (return Nothing)) (return . Just); + +safeString :: String -> IO String +safeString s = do + msx <- getBottom s + case msx of + Just sx -> return (show sx) + Nothing -> case s of + (c:cc) -> do + mcx <- getBottom c + case mcx of + Just cx -> return (show cx) + Nothing -> do + ss <- safeString cc + return (c:ss) + [] -> return "" + +compareExpected :: (Eq t,Show t,ParseTime t) => String -> String -> String -> Maybe t -> IO () +compareExpected ts fmt str expected = let + found = parseTime defaultTimeLocale fmt str + in do + mex <- getBottom found + case mex of + Just ex -> putStrLn ("Exception with " ++ fmt ++ " for " ++ ts ++" " ++ (show str) ++ ": expected " ++ (show expected) ++ ", caught " ++ (show ex)) + Nothing -> if found == expected + then return () + else do + sf <- safeString (show found) + putStrLn ("Mismatch with " ++ fmt ++ " for " ++ ts ++" " ++ (show str) ++ ": expected " ++ (show expected) ++ ", found " ++ sf) + +class (ParseTime t) => TestParse t where + expectedParse :: String -> String -> Maybe t + expectedParse "%Z" str | all isSpace str = Just (buildTime defaultTimeLocale []) + expectedParse _ _ = Nothing + +instance TestParse Day +instance TestParse TimeOfDay +instance TestParse LocalTime +instance TestParse TimeZone +instance TestParse ZonedTime +instance TestParse UTCTime + +checkParse :: String -> String -> IO () +checkParse fmt str = do + compareExpected "Day" fmt str (expectedParse fmt str :: Maybe Day) + compareExpected "TimeOfDay" fmt str (expectedParse fmt str :: Maybe TimeOfDay) + compareExpected "LocalTime" fmt str (expectedParse fmt str :: Maybe LocalTime) + compareExpected "TimeZone" fmt str (expectedParse fmt str :: Maybe TimeZone) + compareExpected "UTCTime" fmt str (expectedParse fmt str :: Maybe UTCTime) main :: IO () -main = - mapM_ (\fmt -> mapM_ (\time -> mapM_ (\zone -> compareFormat id fmt zone time) zones) times) formats >> +main = do + mapM_ (\fmt -> mapM_ (checkParse fmt) somestrings) formats + mapM_ (\fmt -> mapM_ (\time -> mapM_ (\zone -> compareFormat id fmt zone time) zones) times) formats mapM_ (\fmt -> mapM_ (\time -> mapM_ (\zone -> compareFormat (fmap toLower) fmt zone time) zones) times) hashformats diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index b727f3f..37d13f6 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -8,7 +8,9 @@ import Data.Time.Calendar.OrdinalDate import Data.Time.Calendar.WeekDate import Data.Time.Clock.POSIX import System.Locale +import System.Exit import Test.QuickCheck +import Test.QuickCheck.Batch ntest :: Int @@ -16,19 +18,35 @@ ntest = 1000 main :: IO () main = do putStrLn "Should work:" - checkAll properties + good <- checkAll properties putStrLn "Known failures:" - checkAll knownFailures - -checkAll :: [NamedProperty] -> IO () -checkAll ps = mapM_ (checkOne config) ps - where config = defaultConfig { configMaxTest = ntest } - -checkOne :: Config -> NamedProperty -> IO () -checkOne config (n,p) = - do putStr (rpad 65 ' ' n) - check config p - where rpad n' c xs = xs ++ replicate (n' - length xs) c + _ <- checkAll knownFailures + exitWith (if good then ExitSuccess else ExitFailure 1) + + +checkAll :: [NamedProperty] -> IO Bool +checkAll ps = fmap and (mapM checkOne ps) + +trMessage :: TestResult -> String +trMessage (TestOk s _ _) = s +trMessage (TestExausted s i ss) = "Exhausted " ++ (show s) ++ " " ++ (show i) ++ " " ++ (show ss) +trMessage (TestFailed ss i) = "Failed " ++ (show ss) ++ " " ++ (show i) +trMessage (TestAborted ex) = "Aborted " ++ (show ex) + +trGood :: TestResult -> Bool +trGood (TestOk _ _ _) = True +trGood _ = False + +checkOne :: NamedProperty -> IO Bool +checkOne (n,p) = + do + putStr (rpad 65 ' ' n) + tr <- run p options + putStrLn (trMessage tr) + return (trGood tr) + where + rpad n' c xs = xs ++ replicate (n' - length xs) c + options = TestOptions {no_of_tests = 10000,length_of_tests = 0,debug_tests = False} parse :: ParseTime t => String -> String -> Maybe t diff --git a/time.cabal b/time.cabal index 3f88c02..2759127 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.2.0.3 +version: 1.2.0.4 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 23:00:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:10 +0000 (UTC) Subject: [commit: packages/time] master: .run files are boring (ff06923) Message-ID: <20150123230010.5D9463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ff069238035c36b43d10502a9a02cf10f9497c80 >--------------------------------------------------------------- commit ff069238035c36b43d10502a9a02cf10f9497c80 Author: Ashley Yakeley Date: Wed Feb 2 21:34:07 2011 -0800 .run files are boring Ignore-this: 7d76b141e01b923879e5e432d41b933c darcs-hash:20110203053407-ac6dd-f4ffed0f583b01ebeb95bc92770c60fab025d047 >--------------------------------------------------------------- ff069238035c36b43d10502a9a02cf10f9497c80 .darcs-boring | 1 + 1 file changed, 1 insertion(+) diff --git a/.darcs-boring b/.darcs-boring index 0b4f6cb..ca040f7 100644 --- a/.darcs-boring +++ b/.darcs-boring @@ -52,6 +52,7 @@ _split$ ^include/HsTimeConfig\.h$ ^include/HsTimeConfig\.h.in$ ^test/.*\.out$ +^test/.*\.run$ ^test/AddDays$ ^test/ClipDates$ ^test/ConvertBack$ From git at git.haskell.org Fri Jan 23 23:00:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:12 +0000 (UTC) Subject: [commit: packages/time] master: specify QuickCheck version (1c69e66) Message-ID: <20150123230012.6375D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1c69e66cfbf65a7e224ef97023063b9c7d39e112 >--------------------------------------------------------------- commit 1c69e66cfbf65a7e224ef97023063b9c7d39e112 Author: Ashley Yakeley Date: Sat May 7 21:21:47 2011 -0700 specify QuickCheck version Ignore-this: b82b874985d6bc74cf6f7989f46f5a96 darcs-hash:20110508042147-ac6dd-0198670fb2c4e5ecc8e0ffa16dcc2b6618564ac7 >--------------------------------------------------------------- 1c69e66cfbf65a7e224ef97023063b9c7d39e112 test/Makefile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/test/Makefile b/test/Makefile index 5c1487a..f8ef07d 100644 --- a/test/Makefile +++ b/test/Makefile @@ -1,5 +1,5 @@ GHC = ghc -GHCFLAGS = -package time +GHCFLAGS = -package time -package QuickCheck-1.2.0.1 default: make CurrentTime.run ShowDST.run test @@ -50,7 +50,7 @@ TimeZone.ref: FORCE date +%z > $@ TestParseTime: TestParseTime.o - $(GHC) $(GHCFLAGS) -package QuickCheck $^ -o $@ + $(GHC) $(GHCFLAGS) $^ -o $@ test: \ TestMonthDay.diff \ From git at git.haskell.org Fri Jan 23 23:00:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:14 +0000 (UTC) Subject: [commit: packages/time] master: test for %y parse to 1969 - 2068 (ac3fc0b) Message-ID: <20150123230014.6A2773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ac3fc0bf4d197ed82fdd6dff4383a07d8766d433 >--------------------------------------------------------------- commit ac3fc0bf4d197ed82fdd6dff4383a07d8766d433 Author: Ashley Yakeley Date: Sat May 7 21:22:16 2011 -0700 test for %y parse to 1969 - 2068 Ignore-this: ac903c931b2fe745f073a5cb474e9d95 darcs-hash:20110508042216-ac6dd-e6e305e2cb3804511eefdd74dc4b558fcfd00f51 >--------------------------------------------------------------- ac3fc0bf4d197ed82fdd6dff4383a07d8766d433 test/TestParseTime.hs | 54 ++++++++++++++++++++++++++++++++++++++++----------- 1 file changed, 43 insertions(+), 11 deletions(-) diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index 37d13f6..64a4504 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -1,8 +1,10 @@ {-# OPTIONS -Wall -Werror -fno-warn-type-defaults -fno-warn-unused-binds -fno-warn-orphans #-} +{-# LANGUAGE FlexibleInstances, ExistentialQuantification #-} import Control.Monad import Data.Char import Data.Ratio +import Data.Maybe import Data.Time import Data.Time.Calendar.OrdinalDate import Data.Time.Calendar.WeekDate @@ -13,18 +15,49 @@ import Test.QuickCheck import Test.QuickCheck.Batch +class RunTest p where + runTest :: p -> IO TestResult + +instance RunTest (IO TestResult) where + runTest iob = iob + +instance RunTest Property where + runTest p = run p (TestOptions {no_of_tests = 10000,length_of_tests = 0,debug_tests = False}) + +data ExhaustiveTest = forall t. (Show t) => MkExhaustiveTest [t] (t -> IO Bool) + +instance RunTest ExhaustiveTest where + runTest (MkExhaustiveTest cases f) = do + results <- mapM (\t -> do {b <- f t;return (b,show t)}) cases + let failures = mapMaybe (\(b,n) -> if b then Nothing else Just n) results + let fcount = length failures + return (if fcount == 0 then TestOk "OK" 0 [] else TestFailed failures fcount) + ntest :: Int ntest = 1000 main :: IO () -main = do putStrLn "Should work:" - good <- checkAll properties - putStrLn "Known failures:" - _ <- checkAll knownFailures - exitWith (if good then ExitSuccess else ExitFailure 1) - - -checkAll :: [NamedProperty] -> IO Bool +main = do + putStrLn "Should work:" + good1 <- checkAll extests + putStrLn "Should work:" + good2 <- checkAll properties + putStrLn "Known failures:" + _ <- checkAll knownFailures + exitWith (if good1 && good2 then ExitSuccess else ExitFailure 1) + +extests :: [(String,ExhaustiveTest)] +extests = [("parse %y",MkExhaustiveTest [0..99] parseYY)] + +-- | 1969 - 2068 +expectedYear :: Integer -> Integer +expectedYear i | i >= 69 = 1900 + i +expectedYear i = 2000 + i + +parseYY :: Integer -> IO Bool +parseYY i = return (parse "%y" ((show (div i 10)) ++ (show (mod i 10))) == Just (fromGregorian (expectedYear i) 1 1)) + +checkAll :: RunTest p => [(String,p)] -> IO Bool checkAll ps = fmap and (mapM checkOne ps) trMessage :: TestResult -> String @@ -37,16 +70,15 @@ trGood :: TestResult -> Bool trGood (TestOk _ _ _) = True trGood _ = False -checkOne :: NamedProperty -> IO Bool +checkOne :: RunTest p => (String,p) -> IO Bool checkOne (n,p) = do putStr (rpad 65 ' ' n) - tr <- run p options + tr <- runTest p putStrLn (trMessage tr) return (trGood tr) where rpad n' c xs = xs ++ replicate (n' - length xs) c - options = TestOptions {no_of_tests = 10000,length_of_tests = 0,debug_tests = False} parse :: ParseTime t => String -> String -> Maybe t From git at git.haskell.org Fri Jan 23 23:00:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:16 +0000 (UTC) Subject: [commit: packages/time] master: test parse %C %y (c3d1c28) Message-ID: <20150123230016.72F713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c3d1c2821373e6dbc62923ab74d89c4a6b1b0b18 >--------------------------------------------------------------- commit c3d1c2821373e6dbc62923ab74d89c4a6b1b0b18 Author: Ashley Yakeley Date: Sat May 7 21:29:05 2011 -0700 test parse %C %y Ignore-this: 22f6db0e1424c95dece1fdf7740d982e darcs-hash:20110508042905-ac6dd-5026d47053631acb8848806368fb17bbf8bc9837 >--------------------------------------------------------------- c3d1c2821373e6dbc62923ab74d89c4a6b1b0b18 test/TestParseTime.hs | 16 ++++++++++++++-- 1 file changed, 14 insertions(+), 2 deletions(-) diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index 64a4504..5594f34 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -47,15 +47,27 @@ main = do exitWith (if good1 && good2 then ExitSuccess else ExitFailure 1) extests :: [(String,ExhaustiveTest)] -extests = [("parse %y",MkExhaustiveTest [0..99] parseYY)] +extests = [ + ("parse %y",MkExhaustiveTest [0..99] parseYY), + ("parse %C %y 1900s",MkExhaustiveTest [0..99] (parseCYY 19)), + ("parse %C %y 2000s",MkExhaustiveTest [0..99] (parseCYY 20)), + ("parse %C %y 1400s",MkExhaustiveTest [0..99] (parseCYY 14)), + ("parse %C %y 700s",MkExhaustiveTest [0..99] (parseCYY 7)) + ] -- | 1969 - 2068 expectedYear :: Integer -> Integer expectedYear i | i >= 69 = 1900 + i expectedYear i = 2000 + i +show2 :: Integer -> String +show2 i = (show (div i 10)) ++ (show (mod i 10)) + parseYY :: Integer -> IO Bool -parseYY i = return (parse "%y" ((show (div i 10)) ++ (show (mod i 10))) == Just (fromGregorian (expectedYear i) 1 1)) +parseYY i = return (parse "%y" (show2 i) == Just (fromGregorian (expectedYear i) 1 1)) + +parseCYY :: Integer -> Integer -> IO Bool +parseCYY c i = return (parse "%C %y" ((show2 c) ++ " " ++ (show2 i)) == Just (fromGregorian ((c * 100) + i) 1 1)) checkAll :: RunTest p => [(String,p)] -> IO Bool checkAll ps = fmap and (mapM checkOne ps) From git at git.haskell.org Fri Jan 23 23:00:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:18 +0000 (UTC) Subject: [commit: packages/time] master: parse %y range 1969 - 2068, bug #2671 (84f1505) Message-ID: <20150123230018.794583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/84f1505205d9edfce0315fe18cba3fa506554a85 >--------------------------------------------------------------- commit 84f1505205d9edfce0315fe18cba3fa506554a85 Author: Ashley Yakeley Date: Sat May 7 21:36:17 2011 -0700 parse %y range 1969 - 2068, bug #2671 Ignore-this: 30d5c56ed53c337433764e109aaa5ac4 darcs-hash:20110508043617-ac6dd-8e192552d6fd229ccc824600cba2bb74170ebd6a >--------------------------------------------------------------- 84f1505205d9edfce0315fe18cba3fa506554a85 Data/Time/Format/Parse.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Data/Time/Format/Parse.hs b/Data/Time/Format/Parse.hs index aa0b66d..135fc01 100644 --- a/Data/Time/Format/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -254,8 +254,9 @@ instance ParseTime Day where buildDay cs = rest cs where - y = let c = safeLast 19 [x | Century x <- cs] + y = let d = safeLast 70 [x | Year x <- cs] + c = safeLast (if d >= 69 then 19 else 20) [x | Century x <- cs] in 100 * c + d rest (Month m:_) = let d = safeLast 1 [x | Day x <- cs] From git at git.haskell.org Fri Jan 23 23:00:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:20 +0000 (UTC) Subject: [commit: packages/time] master: test for parse %m single digit (3dd4c2c) Message-ID: <20150123230020.802CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3dd4c2cab3b79fb33933f5d64108e474de3f1a06 >--------------------------------------------------------------- commit 3dd4c2cab3b79fb33933f5d64108e474de3f1a06 Author: Ashley Yakeley Date: Sat May 7 22:16:09 2011 -0700 test for parse %m single digit Ignore-this: a79ecf3b70510657aca907e78c70f012 darcs-hash:20110508051609-ac6dd-9ad32ef4836008a307a1de03594d405fd79daec3 >--------------------------------------------------------------- 3dd4c2cab3b79fb33933f5d64108e474de3f1a06 test/TestParseTime.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index 5594f34..c8eabd2 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -52,9 +52,14 @@ extests = [ ("parse %C %y 1900s",MkExhaustiveTest [0..99] (parseCYY 19)), ("parse %C %y 2000s",MkExhaustiveTest [0..99] (parseCYY 20)), ("parse %C %y 1400s",MkExhaustiveTest [0..99] (parseCYY 14)), - ("parse %C %y 700s",MkExhaustiveTest [0..99] (parseCYY 7)) + ("parse %C %y 700s",MkExhaustiveTest [0..99] (parseCYY 7)), + ("parseYearDay",MkExhaustiveTest [(fromGregorian 2011 1 1) .. (fromGregorian 2011 12 31)] parseYearDay) ] +parseYearDay :: Day -> IO Bool +parseYearDay day = case toGregorian day of + (y,m,d) -> return $ (parse "%Y %m %e" ((show y) ++ " " ++ (show m) ++ " " ++ (show d))) == Just day + -- | 1969 - 2068 expectedYear :: Integer -> Integer expectedYear i | i >= 69 = 1900 + i From git at git.haskell.org Fri Jan 23 23:00:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:22 +0000 (UTC) Subject: [commit: packages/time] master: test parse %d %e single digit (8028949) Message-ID: <20150123230022.876A63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/802894907b34d4f3979ea2a88d0393c7d404e9ec >--------------------------------------------------------------- commit 802894907b34d4f3979ea2a88d0393c7d404e9ec Author: Ashley Yakeley Date: Sat May 7 22:21:09 2011 -0700 test parse %d %e single digit Ignore-this: 81b90faa6de38d80462fc534b5e0f101 darcs-hash:20110508052109-ac6dd-6c9689e1cf5500fb02b7172ba2e6dd731a81f1b9 >--------------------------------------------------------------- 802894907b34d4f3979ea2a88d0393c7d404e9ec test/TestParseTime.hs | 26 ++++++++++++++++++++++---- 1 file changed, 22 insertions(+), 4 deletions(-) diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index c8eabd2..1d2d1c2 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -46,6 +46,9 @@ main = do _ <- checkAll knownFailures exitWith (if good1 && good2 then ExitSuccess else ExitFailure 1) +days2011 :: [Day] +days2011 = [(fromGregorian 2011 1 1) .. (fromGregorian 2011 12 31)] + extests :: [(String,ExhaustiveTest)] extests = [ ("parse %y",MkExhaustiveTest [0..99] parseYY), @@ -53,19 +56,34 @@ extests = [ ("parse %C %y 2000s",MkExhaustiveTest [0..99] (parseCYY 20)), ("parse %C %y 1400s",MkExhaustiveTest [0..99] (parseCYY 14)), ("parse %C %y 700s",MkExhaustiveTest [0..99] (parseCYY 7)), - ("parseYearDay",MkExhaustiveTest [(fromGregorian 2011 1 1) .. (fromGregorian 2011 12 31)] parseYearDay) + ("parseYearDay %Y %m %d",MkExhaustiveTest days2011 parseYearDayD), + ("parseYearDay %Y %m %d 0-pad",MkExhaustiveTest days2011 parseYearDayD2), + ("parseYearDay %Y %m %e",MkExhaustiveTest days2011 parseYearDayE), + ("parseYearDay %Y %m %e 0-pad",MkExhaustiveTest days2011 parseYearDayE2) ] -parseYearDay :: Day -> IO Bool -parseYearDay day = case toGregorian day of +parseYearDayD :: Day -> IO Bool +parseYearDayD day = case toGregorian day of + (y,m,d) -> return $ (parse "%Y %m %d" ((show y) ++ " " ++ (show m) ++ " " ++ (show d))) == Just day + +parseYearDayD2 :: Day -> IO Bool +parseYearDayD2 day = case toGregorian day of + (y,m,d) -> return $ (parse "%Y %m %d" ((show y) ++ " " ++ (show2 m) ++ " " ++ (show2 d))) == Just day + +parseYearDayE :: Day -> IO Bool +parseYearDayE day = case toGregorian day of (y,m,d) -> return $ (parse "%Y %m %e" ((show y) ++ " " ++ (show m) ++ " " ++ (show d))) == Just day +parseYearDayE2 :: Day -> IO Bool +parseYearDayE2 day = case toGregorian day of + (y,m,d) -> return $ (parse "%Y %m %e" ((show y) ++ " " ++ (show2 m) ++ " " ++ (show2 d))) == Just day + -- | 1969 - 2068 expectedYear :: Integer -> Integer expectedYear i | i >= 69 = 1900 + i expectedYear i = 2000 + i -show2 :: Integer -> String +show2 :: (Integral n) => n -> String show2 i = (show (div i 10)) ++ (show (mod i 10)) parseYY :: Integer -> IO Bool From git at git.haskell.org Fri Jan 23 23:00:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:24 +0000 (UTC) Subject: [commit: packages/time] master: test parse %-m single digit (7cef519) Message-ID: <20150123230024.8DA593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/7cef51954de82636ac53c25858531569c0fbebbe >--------------------------------------------------------------- commit 7cef51954de82636ac53c25858531569c0fbebbe Author: Ashley Yakeley Date: Sat May 7 22:31:58 2011 -0700 test parse %-m single digit Ignore-this: 32fc454ea7f34c9985e4d2cab174021 darcs-hash:20110508053158-ac6dd-3c4acb3124184955ea67bc432067ec40d11558a8 >--------------------------------------------------------------- 7cef51954de82636ac53c25858531569c0fbebbe test/TestParseTime.hs | 21 ++++++++------------- 1 file changed, 8 insertions(+), 13 deletions(-) diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index 1d2d1c2..a8b3832 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -56,27 +56,22 @@ extests = [ ("parse %C %y 2000s",MkExhaustiveTest [0..99] (parseCYY 20)), ("parse %C %y 1400s",MkExhaustiveTest [0..99] (parseCYY 14)), ("parse %C %y 700s",MkExhaustiveTest [0..99] (parseCYY 7)), - ("parseYearDay %Y %m %d",MkExhaustiveTest days2011 parseYearDayD), - ("parseYearDay %Y %m %d 0-pad",MkExhaustiveTest days2011 parseYearDayD2), - ("parseYearDay %Y %m %e",MkExhaustiveTest days2011 parseYearDayE), - ("parseYearDay %Y %m %e 0-pad",MkExhaustiveTest days2011 parseYearDayE2) + ("parse %Y%m%d",MkExhaustiveTest days2011 parseYMD), + ("parse %Y %m %d",MkExhaustiveTest days2011 parseYearDayD), + ("parse %Y %-m %e",MkExhaustiveTest days2011 parseYearDayE) ] +parseYMD :: Day -> IO Bool +parseYMD day = case toGregorian day of + (y,m,d) -> return $ (parse "%Y%m%d" ((show y) ++ (show2 m) ++ (show2 d))) == Just day + parseYearDayD :: Day -> IO Bool parseYearDayD day = case toGregorian day of - (y,m,d) -> return $ (parse "%Y %m %d" ((show y) ++ " " ++ (show m) ++ " " ++ (show d))) == Just day - -parseYearDayD2 :: Day -> IO Bool -parseYearDayD2 day = case toGregorian day of (y,m,d) -> return $ (parse "%Y %m %d" ((show y) ++ " " ++ (show2 m) ++ " " ++ (show2 d))) == Just day parseYearDayE :: Day -> IO Bool parseYearDayE day = case toGregorian day of - (y,m,d) -> return $ (parse "%Y %m %e" ((show y) ++ " " ++ (show m) ++ " " ++ (show d))) == Just day - -parseYearDayE2 :: Day -> IO Bool -parseYearDayE2 day = case toGregorian day of - (y,m,d) -> return $ (parse "%Y %m %e" ((show y) ++ " " ++ (show2 m) ++ " " ++ (show2 d))) == Just day + (y,m,d) -> return $ (parse "%Y %-m %e" ((show y) ++ " " ++ (show m) ++ " " ++ (show d))) == Just day -- | 1969 - 2068 expectedYear :: Integer -> Integer From git at git.haskell.org Fri Jan 23 23:00:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:26 +0000 (UTC) Subject: [commit: packages/time] master: allow - _ 0 modifiers in % parsing (b2902c9) Message-ID: <20150123230026.952D53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b2902c953cbe901a755539cdde45458d6b623c74 >--------------------------------------------------------------- commit b2902c953cbe901a755539cdde45458d6b623c74 Author: Ashley Yakeley Date: Sat May 7 22:57:59 2011 -0700 allow - _ 0 modifiers in % parsing Ignore-this: 275981732f80ca7fd14bf2a33a578632 darcs-hash:20110508055759-ac6dd-aff88a854a40ff2ad6e168ed5c719bdf55b72d31 >--------------------------------------------------------------- b2902c953cbe901a755539cdde45458d6b623c74 Data/Time/Format/Parse.hs | 89 +++++++++++++++++++++++++---------------------- test/TestFormat.hs | 3 ++ 2 files changed, 51 insertions(+), 41 deletions(-) diff --git a/Data/Time/Format/Parse.hs b/Data/Time/Format/Parse.hs index 135fc01..b8855c1 100644 --- a/Data/Time/Format/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -104,9 +104,12 @@ readsTime l f = readP_to_S (liftM (buildTime l) r) -- * Internals -- +data Padding = NoPadding | SpacePadding | ZeroPadding + deriving Show + type DateFormat = [DateFormatSpec] -data DateFormatSpec = Value Char +data DateFormatSpec = Value (Maybe Padding) Char | WhiteSpace | Literal Char deriving Show @@ -114,31 +117,33 @@ data DateFormatSpec = Value Char parseFormat :: TimeLocale -> String -> DateFormat parseFormat l = p where p "" = [] - p ('%': c :cs) = s ++ p cs - where s = case c of - 'c' -> p (dateTimeFmt l) - 'R' -> p "%H:%M" - 'T' -> p "%H:%M:%S" - 'X' -> p (timeFmt l) - 'r' -> p (time12Fmt l) - 'D' -> p "%m/%d/%y" - 'F' -> p "%Y-%m-%d" - 'x' -> p (dateFmt l) - 'h' -> p "%b" - '%' -> [Literal '%'] - _ -> [Value c] + p ('%': '-' : c :cs) = (pc (Just NoPadding) c) ++ p cs + p ('%': '_' : c :cs) = (pc (Just SpacePadding) c) ++ p cs + p ('%': '0' : c :cs) = (pc (Just ZeroPadding) c) ++ p cs + p ('%': c :cs) = (pc Nothing c) ++ p cs p (c:cs) | isSpace c = WhiteSpace : p cs p (c:cs) = Literal c : p cs + pc _ 'c' = p (dateTimeFmt l) + pc _ 'R' = p "%H:%M" + pc _ 'T' = p "%H:%M:%S" + pc _ 'X' = p (timeFmt l) + pc _ 'r' = p (time12Fmt l) + pc _ 'D' = p "%m/%d/%y" + pc _ 'F' = p "%Y-%m-%d" + pc _ 'x' = p (dateFmt l) + pc _ 'h' = p "%b" + pc _ '%' = [Literal '%'] + pc mpad c = [Value mpad c] parseInput :: TimeLocale -> DateFormat -> ReadP [(Char,String)] parseInput l = liftM catMaybes . mapM p - where p (Value c) = parseValue l c >>= return . Just . (,) c + where p (Value mpad c) = parseValue l mpad c >>= return . Just . (,) c p WhiteSpace = skipSpaces >> return Nothing p (Literal c) = char c >> return Nothing -- | Get the string corresponding to the given format specifier. -parseValue :: TimeLocale -> Char -> ReadP String -parseValue l c = +parseValue :: TimeLocale -> Maybe Padding -> Char -> ReadP String +parseValue l mpad c = case c of 'z' -> numericTZ 'Z' -> munch1 isAlpha <++ @@ -146,40 +151,42 @@ parseValue l c = return "" -- produced by %Z for LocalTime 'P' -> oneOf (let (am,pm) = amPm l in [am, pm]) 'p' -> oneOf (let (am,pm) = amPm l in [am, pm]) - 'H' -> digits 2 - 'I' -> digits 2 - 'k' -> spdigits 2 - 'l' -> spdigits 2 - 'M' -> digits 2 - 'S' -> digits 2 - 'q' -> digits 12 + 'H' -> digits ZeroPadding 2 + 'I' -> digits ZeroPadding 2 + 'k' -> digits NoPadding 2 + 'l' -> digits NoPadding 2 + 'M' -> digits ZeroPadding 2 + 'S' -> digits ZeroPadding 2 + 'q' -> digits ZeroPadding 12 'Q' -> liftM2 (:) (char '.') (munch isDigit) <++ return "" 's' -> (char '-' >> liftM ('-':) (munch1 isDigit)) <++ munch1 isDigit - 'Y' -> digits 4 - 'y' -> digits 2 - 'C' -> digits 2 + 'Y' -> digits ZeroPadding 4 + 'y' -> digits ZeroPadding 2 + 'C' -> digits ZeroPadding 2 'B' -> oneOf (map fst (months l)) 'b' -> oneOf (map snd (months l)) - 'm' -> digits 2 - 'd' -> digits 2 - 'e' -> spdigits 2 - 'j' -> digits 3 - 'G' -> digits 4 - 'g' -> digits 2 - 'f' -> digits 2 - 'V' -> digits 2 + 'm' -> digits ZeroPadding 2 + 'd' -> digits ZeroPadding 2 + 'e' -> digits NoPadding 2 + 'j' -> digits ZeroPadding 3 + 'G' -> digits ZeroPadding 4 + 'g' -> digits ZeroPadding 2 + 'f' -> digits ZeroPadding 2 + 'V' -> digits ZeroPadding 2 'u' -> oneOf $ map (:[]) ['1'..'7'] 'a' -> oneOf (map snd (wDays l)) 'A' -> oneOf (map fst (wDays l)) - 'U' -> digits 2 + 'U' -> digits ZeroPadding 2 'w' -> oneOf $ map (:[]) ['0'..'6'] - 'W' -> digits 2 + 'W' -> digits ZeroPadding 2 _ -> fail $ "Unknown format character: " ++ show c where oneOf = choice . map string - digits n = count n (satisfy isDigit) - spdigits n = skipSpaces >> oneUpTo n (satisfy isDigit) + digitsforce ZeroPadding n = count n (satisfy isDigit) + digitsforce SpacePadding n = skipSpaces >> oneUpTo n (satisfy isDigit) + digitsforce NoPadding n = skipSpaces >> oneUpTo n (satisfy isDigit) + digits pad = digitsforce (fromMaybe pad mpad) oneUpTo :: Int -> ReadP a -> ReadP [a] oneUpTo 0 _ = pfail oneUpTo n x = liftM2 (:) x (upTo (n-1) x) @@ -187,9 +194,9 @@ parseValue l c = upTo 0 _ = return [] upTo n x = (oneUpTo n x) <++ return [] numericTZ = do s <- choice [char '+', char '-'] - h <- digits 2 + h <- digitsforce ZeroPadding 2 optional (char ':') - m <- digits 2 + m <- digitsforce ZeroPadding 2 return (s:h++m) #endif diff --git a/test/TestFormat.hs b/test/TestFormat.hs index 65ca575..19173b6 100644 --- a/test/TestFormat.hs +++ b/test/TestFormat.hs @@ -131,6 +131,9 @@ compareExpected ts fmt str expected = let class (ParseTime t) => TestParse t where expectedParse :: String -> String -> Maybe t expectedParse "%Z" str | all isSpace str = Just (buildTime defaultTimeLocale []) + expectedParse "%_Z" str | all isSpace str = Just (buildTime defaultTimeLocale []) + expectedParse "%-Z" str | all isSpace str = Just (buildTime defaultTimeLocale []) + expectedParse "%0Z" str | all isSpace str = Just (buildTime defaultTimeLocale []) expectedParse _ _ = Nothing instance TestParse Day From git at git.haskell.org Fri Jan 23 23:00:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:28 +0000 (UTC) Subject: [commit: packages/time] master: version 1.2.0.5 (c8c840a) Message-ID: <20150123230028.9C13B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c8c840a328c38acc6a2f243832e474715d4d1568 >--------------------------------------------------------------- commit c8c840a328c38acc6a2f243832e474715d4d1568 Author: Ashley Yakeley Date: Tue May 10 23:34:37 2011 -0700 version 1.2.0.5 Ignore-this: 3def541a0b608a54c482ada9b0ab89ff darcs-hash:20110511063437-ac6dd-fd171d1311e7e6247158b5b132abffb0cc088948 >--------------------------------------------------------------- c8c840a328c38acc6a2f243832e474715d4d1568 time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index 2759127..5ca5557 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.2.0.4 +version: 1.2.0.5 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 23:00:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:30 +0000 (UTC) Subject: [commit: packages/time] master: correct padding in parse; doc (83ec536) Message-ID: <20150123230030.A2DA13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/83ec536b75b3bd342ee273a7db061d35830afc32 >--------------------------------------------------------------- commit 83ec536b75b3bd342ee273a7db061d35830afc32 Author: Ashley Yakeley Date: Wed May 11 00:40:32 2011 -0700 correct padding in parse; doc Ignore-this: b922ed3e94021edde3d9d78bdb9844b2 darcs-hash:20110511074032-ac6dd-51fd06ffe64b8c2c3b836ebc511b990c1d9a0662 >--------------------------------------------------------------- 83ec536b75b3bd342ee273a7db061d35830afc32 Data/Time/Format/Parse.hs | 19 ++++++++++--------- 1 file changed, 10 insertions(+), 9 deletions(-) diff --git a/Data/Time/Format/Parse.hs b/Data/Time/Format/Parse.hs index b8855c1..aaf7029 100644 --- a/Data/Time/Format/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -55,20 +55,21 @@ class ParseTime t where -- If the input does not include all the information needed to -- construct a complete value, any missing parts should be taken -- from 1970-01-01 00:00:00 +0000 (which was a Thursday). + -- In the absence of @%C@ or @%Y@, century is 1969 - 2068. buildTime :: TimeLocale -- ^ The time locale. -> [(Char,String)] -- ^ Pairs of format characters and the -- corresponding part of the input. -> t #if LANGUAGE_Rank2Types --- | Parses a time value given a format string. Supports the same %-codes as --- 'formatTime'. Leading and trailing whitespace is accepted. Case is not --- significant. Some variations in the input are accepted: +-- | Parses a time value given a format string. +-- Supports the same %-codes as 'formatTime', including @%-@, @%_@ and @%0@ modifiers. +-- Leading and trailing whitespace is accepted. Case is not significant. +-- Some variations in the input are accepted: -- -- [@%z@] accepts any of @-HHMM@ or @-HH:MM at . -- --- [@%Z@] accepts any string of letters, or any --- of the formats accepted by @%z at . +-- [@%Z@] accepts any string of letters, or any of the formats accepted by @%z at . -- parseTime :: ParseTime t => TimeLocale -- ^ Time locale. @@ -153,8 +154,8 @@ parseValue l mpad c = 'p' -> oneOf (let (am,pm) = amPm l in [am, pm]) 'H' -> digits ZeroPadding 2 'I' -> digits ZeroPadding 2 - 'k' -> digits NoPadding 2 - 'l' -> digits NoPadding 2 + 'k' -> digits SpacePadding 2 + 'l' -> digits SpacePadding 2 'M' -> digits ZeroPadding 2 'S' -> digits ZeroPadding 2 'q' -> digits ZeroPadding 12 @@ -168,7 +169,7 @@ parseValue l mpad c = 'b' -> oneOf (map snd (months l)) 'm' -> digits ZeroPadding 2 'd' -> digits ZeroPadding 2 - 'e' -> digits NoPadding 2 + 'e' -> digits SpacePadding 2 'j' -> digits ZeroPadding 3 'G' -> digits ZeroPadding 4 'g' -> digits ZeroPadding 2 @@ -185,7 +186,7 @@ parseValue l mpad c = oneOf = choice . map string digitsforce ZeroPadding n = count n (satisfy isDigit) digitsforce SpacePadding n = skipSpaces >> oneUpTo n (satisfy isDigit) - digitsforce NoPadding n = skipSpaces >> oneUpTo n (satisfy isDigit) + digitsforce NoPadding n = oneUpTo n (satisfy isDigit) digits pad = digitsforce (fromMaybe pad mpad) oneUpTo :: Int -> ReadP a -> ReadP [a] oneUpTo 0 _ = pfail From git at git.haskell.org Fri Jan 23 23:00:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:32 +0000 (UTC) Subject: [commit: packages/time] master: version 1.3: instance RealFrac DiffTime (234e6ce) Message-ID: <20150123230032.AAF673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/234e6cef3c5ade6b46b7a55a90c12247d918bf0a >--------------------------------------------------------------- commit 234e6cef3c5ade6b46b7a55a90c12247d918bf0a Author: Ashley Yakeley Date: Tue Aug 9 19:12:09 2011 -0700 version 1.3: instance RealFrac DiffTime Ignore-this: db3b670e3c17170909ab4c5b34b83716 darcs-hash:20110810021209-ac6dd-915d3dcb3b6e543f834c997820182d669e7bb2ac >--------------------------------------------------------------- 234e6cef3c5ade6b46b7a55a90c12247d918bf0a Data/Time/Clock/Scale.hs | 8 ++++++++ configure.ac | 2 +- time.cabal | 2 +- 3 files changed, 10 insertions(+), 2 deletions(-) diff --git a/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs index f07fd64..fb67cc5 100644 --- a/Data/Time/Clock/Scale.hs +++ b/Data/Time/Clock/Scale.hs @@ -83,6 +83,14 @@ instance Fractional DiffTime where recip (MkDiffTime a) = MkDiffTime (recip a) fromRational r = MkDiffTime (fromRational r) +-- necessary because H98 doesn't have "cunning newtype" derivation +instance RealFrac DiffTime where + properFraction (MkDiffTime a) = let (b',a') = properFraction a in (b',MkDiffTime a') + truncate (MkDiffTime a) = truncate a + round (MkDiffTime a) = round a + ceiling (MkDiffTime a) = ceiling a + floor (MkDiffTime a) = floor a + -- | Create a 'DiffTime' which represents an integral number of seconds. secondsToDiffTime :: Integer -> DiffTime secondsToDiffTime = fromInteger diff --git a/configure.ac b/configure.ac index b04e8cd..dc58c49 100644 --- a/configure.ac +++ b/configure.ac @@ -1,4 +1,4 @@ -AC_INIT([Haskell time package], [1.2.0.3], [ashley at semantic.org], [time]) +AC_INIT([Haskell time package], [1.3], [ashley at semantic.org], [time]) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([include/HsTime.h]) diff --git a/time.cabal b/time.cabal index 5ca5557..21bf3e4 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.2.0.5 +version: 1.3 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 23:00:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:34 +0000 (UTC) Subject: [commit: packages/time] master: NFData instances, contributed by Herbert Valerio Riedel (4466857) Message-ID: <20150123230034.B14783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/4466857c177c0315e8400fe7d64b930d52e12ce1 >--------------------------------------------------------------- commit 4466857c177c0315e8400fe7d64b930d52e12ce1 Author: Ashley Yakeley Date: Mon Sep 12 03:08:07 2011 -0700 NFData instances, contributed by Herbert Valerio Riedel Ignore-this: 5279778ec762aa123b8ff68f417d5353 darcs-hash:20110912100807-ac6dd-182208624a89df2741cdc147aa1f6255cf35ee9d >--------------------------------------------------------------- 4466857c177c0315e8400fe7d64b930d52e12ce1 Data/Time/Calendar/Days.hs | 4 ++++ Data/Time/Clock/Scale.hs | 8 ++++++++ Data/Time/Clock/TAI.hs | 4 ++++ Data/Time/Clock/UTC.hs | 7 +++++++ Data/Time/LocalTime/LocalTime.hs | 7 +++++++ Data/Time/LocalTime/TimeOfDay.hs | 4 ++++ Data/Time/LocalTime/TimeZone.hs | 4 ++++ time.cabal | 4 ++-- 8 files changed, 40 insertions(+), 2 deletions(-) diff --git a/Data/Time/Calendar/Days.hs b/Data/Time/Calendar/Days.hs index bd2be33..c09a273 100644 --- a/Data/Time/Calendar/Days.hs +++ b/Data/Time/Calendar/Days.hs @@ -7,6 +7,7 @@ module Data.Time.Calendar.Days Day(..),addDays,diffDays ) where +import Control.DeepSeq import Data.Ix import Data.Typeable #if LANGUAGE_Rank2Types @@ -22,6 +23,9 @@ newtype Day = ModifiedJulianDay {toModifiedJulianDay :: Integer} deriving (Eq,Or #endif ) +instance NFData Day where + rnf (ModifiedJulianDay a) = rnf a + instance Typeable Day where typeOf _ = mkTyConApp (mkTyCon "Data.Time.Calendar.Days.Day") [] diff --git a/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs index fb67cc5..37c3f32 100644 --- a/Data/Time/Clock/Scale.hs +++ b/Data/Time/Clock/Scale.hs @@ -12,6 +12,7 @@ module Data.Time.Clock.Scale secondsToDiffTime, picosecondsToDiffTime ) where +import Control.DeepSeq import Data.Ratio ((%)) import Data.Fixed import Data.Typeable @@ -29,6 +30,10 @@ newtype UniversalTime = ModJulianDate {getModJulianDate :: Rational} deriving (E #endif ) +-- necessary because H98 doesn't have "cunning newtype" derivation +instance NFData UniversalTime where + rnf (ModJulianDate a) = rnf a + instance Typeable UniversalTime where typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.Scale.UniversalTime") [] @@ -46,6 +51,9 @@ newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord #endif ) +-- necessary because H98 doesn't have "cunning newtype" derivation +instance NFData DiffTime -- FIXME: Data.Fixed had no NFData instances yet at time of writing + instance Typeable DiffTime where typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.Scale.DiffTime") [] diff --git a/Data/Time/Clock/TAI.hs b/Data/Time/Clock/TAI.hs index 946e4ca..77c2134 100644 --- a/Data/Time/Clock/TAI.hs +++ b/Data/Time/Clock/TAI.hs @@ -18,6 +18,7 @@ module Data.Time.Clock.TAI import Data.Time.LocalTime import Data.Time.Calendar.Days import Data.Time.Clock +import Control.DeepSeq import Data.Typeable import Data.Fixed #if LANGUAGE_Rank2Types @@ -35,6 +36,9 @@ newtype AbsoluteTime = MkAbsoluteTime {unAbsoluteTime :: DiffTime} deriving (Eq, #endif ) +instance NFData AbsoluteTime where + rnf (MkAbsoluteTime a) = rnf a + instance Typeable AbsoluteTime where typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.TAI.AbsoluteTime") [] diff --git a/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs index 1153bf8..e172b15 100644 --- a/Data/Time/Clock/UTC.hs +++ b/Data/Time/Clock/UTC.hs @@ -15,6 +15,7 @@ module Data.Time.Clock.UTC UTCTime(..),NominalDiffTime ) where +import Control.DeepSeq import Data.Time.Calendar.Days import Data.Time.Clock.Scale import Data.Fixed @@ -40,6 +41,9 @@ data UTCTime = UTCTime { #endif #endif +instance NFData UTCTime where + rnf (UTCTime d t) = d `deepseq` t `deepseq` () + instance Typeable UTCTime where typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.UTC.UTCTime") [] @@ -67,6 +71,9 @@ newtype NominalDiffTime = MkNominalDiffTime Pico deriving (Eq,Ord #endif ) +-- necessary because H98 doesn't have "cunning newtype" derivation +instance NFData NominalDiffTime -- FIXME: Data.Fixed had no NFData instances yet at time of writing + instance Typeable NominalDiffTime where typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.UTC.NominalDiffTime") [] diff --git a/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs index 0a79728..feb0341 100644 --- a/Data/Time/LocalTime/LocalTime.hs +++ b/Data/Time/LocalTime/LocalTime.hs @@ -17,6 +17,7 @@ import Data.Time.LocalTime.TimeOfDay import Data.Time.LocalTime.TimeZone import Data.Time.Calendar import Data.Time.Clock +import Control.DeepSeq import Data.Typeable #if LANGUAGE_Rank2Types import Data.Data @@ -39,6 +40,9 @@ data LocalTime = LocalTime { #endif ) +instance NFData LocalTime where + rnf (LocalTime d t) = d `deepseq` t `deepseq` () + instance Typeable LocalTime where typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.LocalTime.LocalTime") [] @@ -79,6 +83,9 @@ data ZonedTime = ZonedTime { #endif #endif +instance NFData ZonedTime where + rnf (ZonedTime lt z) = lt `deepseq` z `deepseq` () + instance Typeable ZonedTime where typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.LocalTime.ZonedTime") [] diff --git a/Data/Time/LocalTime/TimeOfDay.hs b/Data/Time/LocalTime/TimeOfDay.hs index 37b2079..ed0dbed 100644 --- a/Data/Time/LocalTime/TimeOfDay.hs +++ b/Data/Time/LocalTime/TimeOfDay.hs @@ -13,6 +13,7 @@ module Data.Time.LocalTime.TimeOfDay import Data.Time.LocalTime.TimeZone import Data.Time.Calendar.Private import Data.Time.Clock +import Control.DeepSeq import Data.Typeable import Data.Fixed #if LANGUAGE_Rank2Types @@ -38,6 +39,9 @@ data TimeOfDay = TimeOfDay { #endif ) +instance NFData TimeOfDay where + rnf (TimeOfDay h m s) = h `deepseq` m `deepseq` s `seq` () -- FIXME: Data.Fixed had no NFData instances yet at time of writing + instance Typeable TimeOfDay where typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.TimeOfDay.TimeOfDay") [] diff --git a/Data/Time/LocalTime/TimeZone.hs b/Data/Time/LocalTime/TimeZone.hs index 35ffaab..16b2e52 100644 --- a/Data/Time/LocalTime/TimeZone.hs +++ b/Data/Time/LocalTime/TimeZone.hs @@ -19,6 +19,7 @@ import Data.Time.Clock.POSIX import Foreign import Foreign.C +import Control.DeepSeq import Data.Typeable #if LANGUAGE_Rank2Types import Data.Data @@ -40,6 +41,9 @@ data TimeZone = TimeZone { #endif ) +instance NFData TimeZone where + rnf (TimeZone m so n) = m `deepseq` so `deepseq` n `deepseq` () + instance Typeable TimeZone where typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.TimeZone.TimeZone") [] diff --git a/time.cabal b/time.cabal index 21bf3e4..c8f0f0f 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.3 +version: 1.4 stability: stable license: BSD3 license-file: LICENSE @@ -35,7 +35,7 @@ extra-tmp-files: library { - build-depends: base == 4.*, old-locale + build-depends: base == 4.*, deepseq >= 1.1 && < 1.2, old-locale ghc-options: -Wall if impl(ghc) extensions: Rank2Types DeriveDataTypeable StandaloneDeriving From git at git.haskell.org Fri Jan 23 23:00:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:36 +0000 (UTC) Subject: [commit: packages/time] master: remove upper bound on deepseq dependency (e395b77) Message-ID: <20150123230036.B76993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e395b77cdd1f2f7573ad8938c2a55c87152acc11 >--------------------------------------------------------------- commit e395b77cdd1f2f7573ad8938c2a55c87152acc11 Author: Ashley Yakeley Date: Tue Sep 13 02:22:50 2011 -0700 remove upper bound on deepseq dependency Ignore-this: d0b757647470d538d442591df4753e2 darcs-hash:20110913092250-ac6dd-41757c62fa83dafea4fbddac27038fcb405ba108 >--------------------------------------------------------------- e395b77cdd1f2f7573ad8938c2a55c87152acc11 time.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/time.cabal b/time.cabal index c8f0f0f..7acb243 100644 --- a/time.cabal +++ b/time.cabal @@ -35,7 +35,7 @@ extra-tmp-files: library { - build-depends: base == 4.*, deepseq >= 1.1 && < 1.2, old-locale + build-depends: base == 4.*, deepseq >= 1.1, old-locale ghc-options: -Wall if impl(ghc) extensions: Rank2Types DeriveDataTypeable StandaloneDeriving From git at git.haskell.org Fri Jan 23 23:00:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:38 +0000 (UTC) Subject: [commit: packages/time] master: RULES for realToFrac, for speed, contributed by Liyang HU (8eee78e) Message-ID: <20150123230038.C071E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/8eee78e5d4de47651bb837adb28f3550e0611a52 >--------------------------------------------------------------- commit 8eee78e5d4de47651bb837adb28f3550e0611a52 Author: Ashley Yakeley Date: Sun Oct 30 17:38:00 2011 -0700 RULES for realToFrac, for speed, contributed by Liyang HU Ignore-this: c277f94b61ec0c6eab64c1770478220b darcs-hash:20111031003800-ac6dd-affc63c79ba1478a0ebe610bdd42772a7fd85d86 >--------------------------------------------------------------- 8eee78e5d4de47651bb837adb28f3550e0611a52 Data/Time/Clock/Scale.hs | 6 ++++++ Data/Time/Clock/UTC.hs | 9 +++++++++ test/Makefile | 10 +++++++--- test/RealToFracBenchmark.hs | 22 ++++++++++++++++++++++ time.cabal | 2 +- 5 files changed, 45 insertions(+), 4 deletions(-) diff --git a/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs index 37c3f32..ffa52a2 100644 --- a/Data/Time/Clock/Scale.hs +++ b/Data/Time/Clock/Scale.hs @@ -106,3 +106,9 @@ secondsToDiffTime = fromInteger -- | Create a 'DiffTime' from a number of picoseconds. picosecondsToDiffTime :: Integer -> DiffTime picosecondsToDiffTime x = fromRational (x % 1000000000000) + +{-# RULES +"realToFrac/DiffTime->Pico" realToFrac = \ (MkDiffTime ps) -> ps +"realToFrac/Pico->DiffTime" realToFrac = MkDiffTime + #-} + diff --git a/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs index e172b15..4f3c23a 100644 --- a/Data/Time/Clock/UTC.hs +++ b/Data/Time/Clock/UTC.hs @@ -118,3 +118,12 @@ instance RealFrac NominalDiffTime where round (MkNominalDiffTime a) = round a ceiling (MkNominalDiffTime a) = ceiling a floor (MkNominalDiffTime a) = floor a + +{-# RULES +"realToFrac/DiffTime->NominalDiffTime" realToFrac = \ dt -> MkNominalDiffTime (realToFrac dt) +"realToFrac/NominalDiffTime->DiffTime" realToFrac = \ (MkNominalDiffTime ps) -> realToFrac ps + +"realToFrac/NominalDiffTime->Pico" realToFrac = \ (MkNominalDiffTime ps) -> ps +"realToFrac/Pico->NominalDiffTime" realToFrac = MkNominalDiffTime + #-} + diff --git a/test/Makefile b/test/Makefile index f8ef07d..ca57f7d 100644 --- a/test/Makefile +++ b/test/Makefile @@ -52,6 +52,9 @@ TimeZone.ref: FORCE TestParseTime: TestParseTime.o $(GHC) $(GHCFLAGS) $^ -o $@ +RealToFracBenchmark: RealToFracBenchmark.o + $(GHC) $(GHCFLAGS) $^ -o $@ + test: \ TestMonthDay.diff \ ConvertBack.diff0 \ @@ -64,13 +67,14 @@ test: \ TestFormat.diff0 \ TestParseDAT.diff \ TestEaster.diff \ - TestParseTime.run \ - UseCases.o + TestParseTime.run \ + UseCases.o \ + RealToFracBenchmark.run @echo "Success!" clean: rm -rf TestMonthDay ConvertBack TestCalendars TestTime LongWeekYears ClipDates \ - AddDays TestFormat TestParseDAT TestEaster CurrentTime ShowDST TimeZone TimeZone.ref TestParseTime \ + AddDays TestFormat TestParseDAT TestEaster CurrentTime ShowDST TimeZone TimeZone.ref TestParseTime RealToFracBenchmark \ *.out *.run *.o *.hi Makefile.bak %.diff: %.ref %.out diff --git a/test/RealToFracBenchmark.hs b/test/RealToFracBenchmark.hs new file mode 100644 index 0000000..be4eae2 --- /dev/null +++ b/test/RealToFracBenchmark.hs @@ -0,0 +1,22 @@ +{- Contributed by Liyang HU -} +module Main where + +import Prelude +import Control.Applicative +import Control.Monad +import Control.DeepSeq +import Data.Time +import Data.Time.Clock.POSIX +import System.Random + +main :: IO () +main = do + ts <- replicateM 100000 $ do + t <- posixSecondsToUTCTime . realToFrac <$> + ( (*) . fromInteger <$> randomRIO (-15*10^21, 15*10^21) <*> + randomIO :: IO Double ) :: IO UTCTime + rnf t `seq` return t + now <- getCurrentTime + print . sum $ map (diffUTCTime now) ts + print =<< flip diffUTCTime now <$> getCurrentTime + diff --git a/time.cabal b/time.cabal index 7acb243..cadeea7 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.4 +version: 1.4.0.1 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 23:00:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:40 +0000 (UTC) Subject: [commit: packages/time] master: fix for latest GHC (1674b5d) Message-ID: <20150123230040.C5ED33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1674b5d844d146915003beb46c152b3056cfd3a9 >--------------------------------------------------------------- commit 1674b5d844d146915003beb46c152b3056cfd3a9 Author: Ashley Yakeley Date: Sat Jul 7 19:59:16 2012 -0700 fix for latest GHC Ignore-this: b6ff8799465d56758c990e952c77e140 darcs-hash:20120708025916-ac6dd-6a0bae17c075e655e248024f48e0fed5a259433f >--------------------------------------------------------------- 1674b5d844d146915003beb46c152b3056cfd3a9 test/TestParseTime.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs index a8b3832..1ee7368 100644 --- a/test/TestParseTime.hs +++ b/test/TestParseTime.hs @@ -78,7 +78,7 @@ expectedYear :: Integer -> Integer expectedYear i | i >= 69 = 1900 + i expectedYear i = 2000 + i -show2 :: (Integral n) => n -> String +show2 :: (Integral n,Show n) => n -> String show2 i = (show (div i 10)) ++ (show (mod i 10)) parseYY :: Integer -> IO Bool From git at git.haskell.org Fri Jan 23 23:00:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:42 +0000 (UTC) Subject: [commit: packages/time] master: changed uses of mkTyCon to mkTyCon3 (8f9b7ae) Message-ID: <20150123230042.CCC703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/8f9b7ae035401105e311dcd8596da5d1aa2f5801 >--------------------------------------------------------------- commit 8f9b7ae035401105e311dcd8596da5d1aa2f5801 Author: blackredtree Date: Thu Sep 13 15:00:34 2012 -0700 changed uses of mkTyCon to mkTyCon3 Ignore-this: f31d15b2eccb114f507cadfcda0b0630 darcs-hash:20120913220034-08fed-bb57957a23120580281bea112d59d15509920b0e >--------------------------------------------------------------- 8f9b7ae035401105e311dcd8596da5d1aa2f5801 Data/Time/Calendar/Days.hs | 2 +- Data/Time/Clock/Scale.hs | 4 ++-- Data/Time/Clock/TAI.hs | 2 +- Data/Time/Clock/UTC.hs | 4 ++-- Data/Time/LocalTime/LocalTime.hs | 4 ++-- Data/Time/LocalTime/TimeOfDay.hs | 2 +- Data/Time/LocalTime/TimeZone.hs | 2 +- 7 files changed, 10 insertions(+), 10 deletions(-) diff --git a/Data/Time/Calendar/Days.hs b/Data/Time/Calendar/Days.hs index c09a273..6911833 100644 --- a/Data/Time/Calendar/Days.hs +++ b/Data/Time/Calendar/Days.hs @@ -27,7 +27,7 @@ instance NFData Day where rnf (ModifiedJulianDay a) = rnf a instance Typeable Day where - typeOf _ = mkTyConApp (mkTyCon "Data.Time.Calendar.Days.Day") [] + typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Calendar.Days" "Day") [] -- necessary because H98 doesn't have "cunning newtype" derivation instance Enum Day where diff --git a/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs index ffa52a2..237a77b 100644 --- a/Data/Time/Clock/Scale.hs +++ b/Data/Time/Clock/Scale.hs @@ -35,7 +35,7 @@ instance NFData UniversalTime where rnf (ModJulianDate a) = rnf a instance Typeable UniversalTime where - typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.Scale.UniversalTime") [] + typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.Scale" "UniversalTime") [] -- | This is a length of time, as measured by a clock. -- Conversion functions will treat it as seconds. @@ -55,7 +55,7 @@ newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord instance NFData DiffTime -- FIXME: Data.Fixed had no NFData instances yet at time of writing instance Typeable DiffTime where - typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.Scale.DiffTime") [] + typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.Scale" "DiffTime") [] -- necessary because H98 doesn't have "cunning newtype" derivation instance Enum DiffTime where diff --git a/Data/Time/Clock/TAI.hs b/Data/Time/Clock/TAI.hs index 77c2134..5e6bfef 100644 --- a/Data/Time/Clock/TAI.hs +++ b/Data/Time/Clock/TAI.hs @@ -40,7 +40,7 @@ instance NFData AbsoluteTime where rnf (MkAbsoluteTime a) = rnf a instance Typeable AbsoluteTime where - typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.TAI.AbsoluteTime") [] + typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.TAI" "AbsoluteTime") [] instance Show AbsoluteTime where show t = show (utcToLocalTime utc (taiToUTCTime (const 0) t)) ++ " TAI" -- ugly, but standard apparently diff --git a/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs index 4f3c23a..da1ecc2 100644 --- a/Data/Time/Clock/UTC.hs +++ b/Data/Time/Clock/UTC.hs @@ -45,7 +45,7 @@ instance NFData UTCTime where rnf (UTCTime d t) = d `deepseq` t `deepseq` () instance Typeable UTCTime where - typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.UTC.UTCTime") [] + typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.UTC" "UTCTime") [] instance Eq UTCTime where (UTCTime da ta) == (UTCTime db tb) = (da == db) && (ta == tb) @@ -75,7 +75,7 @@ newtype NominalDiffTime = MkNominalDiffTime Pico deriving (Eq,Ord instance NFData NominalDiffTime -- FIXME: Data.Fixed had no NFData instances yet at time of writing instance Typeable NominalDiffTime where - typeOf _ = mkTyConApp (mkTyCon "Data.Time.Clock.UTC.NominalDiffTime") [] + typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.UTC" "NominalDiffTime") [] instance Enum NominalDiffTime where succ (MkNominalDiffTime a) = MkNominalDiffTime (succ a) diff --git a/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs index feb0341..02f06a4 100644 --- a/Data/Time/LocalTime/LocalTime.hs +++ b/Data/Time/LocalTime/LocalTime.hs @@ -44,7 +44,7 @@ instance NFData LocalTime where rnf (LocalTime d t) = d `deepseq` t `deepseq` () instance Typeable LocalTime where - typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.LocalTime.LocalTime") [] + typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.LocalTime" "LocalTime") [] instance Show LocalTime where show (LocalTime d t) = (showGregorian d) ++ " " ++ (show t) @@ -87,7 +87,7 @@ instance NFData ZonedTime where rnf (ZonedTime lt z) = lt `deepseq` z `deepseq` () instance Typeable ZonedTime where - typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.LocalTime.ZonedTime") [] + typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.LocalTime" "ZonedTime") [] utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime utcToZonedTime zone time = ZonedTime (utcToLocalTime zone time) zone diff --git a/Data/Time/LocalTime/TimeOfDay.hs b/Data/Time/LocalTime/TimeOfDay.hs index ed0dbed..8fdf539 100644 --- a/Data/Time/LocalTime/TimeOfDay.hs +++ b/Data/Time/LocalTime/TimeOfDay.hs @@ -43,7 +43,7 @@ instance NFData TimeOfDay where rnf (TimeOfDay h m s) = h `deepseq` m `deepseq` s `seq` () -- FIXME: Data.Fixed had no NFData instances yet at time of writing instance Typeable TimeOfDay where - typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.TimeOfDay.TimeOfDay") [] + typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.TimeOfDay" "TimeOfDay") [] -- | Hour zero midnight :: TimeOfDay diff --git a/Data/Time/LocalTime/TimeZone.hs b/Data/Time/LocalTime/TimeZone.hs index 16b2e52..689288f 100644 --- a/Data/Time/LocalTime/TimeZone.hs +++ b/Data/Time/LocalTime/TimeZone.hs @@ -45,7 +45,7 @@ instance NFData TimeZone where rnf (TimeZone m so n) = m `deepseq` so `deepseq` n `deepseq` () instance Typeable TimeZone where - typeOf _ = mkTyConApp (mkTyCon "Data.Time.LocalTime.TimeZone.TimeZone") [] + typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.TimeZone" "TimeZone") [] -- | Create a nameless non-summer timezone for this number of minutes minutesToTimeZone :: Int -> TimeZone From git at git.haskell.org Fri Jan 23 23:00:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:44 +0000 (UTC) Subject: [commit: packages/time] master: revamped tests to use the new cabal testing interface (df3fc69) Message-ID: <20150123230044.E00BB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/df3fc69a5e9b5a668933b1c6cca88a9ab6d14db2 >--------------------------------------------------------------- commit df3fc69a5e9b5a668933b1c6cca88a9ab6d14db2 Author: blackredtree Date: Thu Sep 13 15:22:27 2012 -0700 revamped tests to use the new cabal testing interface Ignore-this: bf07a09bbbf9641fcaa104d0540b9646 tests now use string comparsion instead of diffing to determine test results .ref files were converted into hs modules exporting the same data darcs-hash:20120913222227-08fed-71851925b9e0a2a7b67d193b8e92fac37fc95c6f >--------------------------------------------------------------- df3fc69a5e9b5a668933b1c6cca88a9ab6d14db2 {test => Test}/AddDays.hs | 14 +- Test/AddDaysRef.hs | 249 ++++++++++ Test/ClipDates.hs | 56 +++ Test/ClipDatesRef.hs | 565 ++++++++++++++++++++++ Test/ConvertBack.hs | 46 ++ {test => Test}/CurrentTime.hs | 0 Test/LongWeekYears.hs | 26 + Test/LongWeekYearsRef.hs | 154 ++++++ {test => Test}/Makefile | 0 {test => Test}/RealToFracBenchmark.hs | 0 {test => Test}/ShowDST.hs | 0 Test/TAI_UTC_DAT.hs | 41 ++ {test => Test}/TestCalendars.hs | 20 +- Test/TestCalendarsRef.hs | 8 + Test/TestEaster.hs | 40 ++ Test/TestEasterRef.hs | 61 +++ {test => Test}/TestFormat.hs | 111 +++-- {test => Test}/TestFormatStuff.c | 0 {test => Test}/TestFormatStuff.h | 0 Test/TestMonthDay.hs | 29 ++ Test/TestMonthDayRef.hs | 750 +++++++++++++++++++++++++++++ {test => Test}/TestParseDAT.hs | 48 +- Test/TestParseDAT_Ref.hs | 94 ++++ {test => Test}/TestParseTime.hs | 23 +- Test/TestTime.hs | 112 +++++ Test/TestTimeRef.hs | 880 ++++++++++++++++++++++++++++++++++ {test => Test}/TimeZone.hs | 0 {test => Test}/UseCases.lhs | 0 test/AddDays.ref | 245 ---------- test/ClipDates.hs | 26 - test/ClipDates.ref | 561 ---------------------- test/ConvertBack.hs | 36 -- test/LongWeekYears.hs | 18 - test/LongWeekYears.ref | 150 ------ test/TestCalendars.ref | 4 - test/TestEaster.hs | 23 - test/TestEaster.ref | 57 --- test/TestMonthDay.hs | 20 - test/TestMonthDay.ref | 746 ---------------------------- test/TestParseDAT.ref | 90 ---- test/TestTime.hs | 97 ---- test/TestTime.ref | 874 --------------------------------- test/tai-utc.dat | 37 -- time.cabal | 66 ++- 44 files changed, 3307 insertions(+), 3070 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc df3fc69a5e9b5a668933b1c6cca88a9ab6d14db2 From git at git.haskell.org Fri Jan 23 23:00:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:46 +0000 (UTC) Subject: [commit: packages/time] master: removed unneccesary Makefile (b317b99) Message-ID: <20150123230046.E5C553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b317b9924e78b343f585a92cbb66d486a6e80bc4 >--------------------------------------------------------------- commit b317b9924e78b343f585a92cbb66d486a6e80bc4 Author: blackredtree Date: Thu Sep 13 15:24:52 2012 -0700 removed unneccesary Makefile Ignore-this: cf806b83e0305616c9ab0f403ee90cd0 darcs-hash:20120913222452-08fed-25ca1213291a7fafe793405b1b265ffddc4f1a5d >--------------------------------------------------------------- b317b9924e78b343f585a92cbb66d486a6e80bc4 Test/Makefile | 105 ---------------------------------------------------------- 1 file changed, 105 deletions(-) diff --git a/Test/Makefile b/Test/Makefile deleted file mode 100644 index ca57f7d..0000000 --- a/Test/Makefile +++ /dev/null @@ -1,105 +0,0 @@ -GHC = ghc -GHCFLAGS = -package time -package QuickCheck-1.2.0.1 - -default: - make CurrentTime.run ShowDST.run test - -TestMonthDay: TestMonthDay.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -ConvertBack: ConvertBack.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -TestCalendars: TestCalendars.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -TestTime: TestTime.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -LongWeekYears: LongWeekYears.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -ClipDates: ClipDates.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -AddDays: AddDays.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -TestFormat: TestFormat.o TestFormatStuff.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -TestFormatStuff.o: TestFormatStuff.c TestFormatStuff.h - gcc -o $@ -c $< - -TestParseDAT: TestParseDAT.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -TestEaster: TestEaster.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -CurrentTime: CurrentTime.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -ShowDST: ShowDST.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -TimeZone: TimeZone.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -TimeZone.ref: FORCE - date +%z > $@ - -TestParseTime: TestParseTime.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -RealToFracBenchmark: RealToFracBenchmark.o - $(GHC) $(GHCFLAGS) $^ -o $@ - -test: \ - TestMonthDay.diff \ - ConvertBack.diff0 \ - TestCalendars.diff \ - TestTime.diff \ - LongWeekYears.diff \ - ClipDates.diff \ - AddDays.diff \ - TimeZone.diff \ - TestFormat.diff0 \ - TestParseDAT.diff \ - TestEaster.diff \ - TestParseTime.run \ - UseCases.o \ - RealToFracBenchmark.run - @echo "Success!" - -clean: - rm -rf TestMonthDay ConvertBack TestCalendars TestTime LongWeekYears ClipDates \ - AddDays TestFormat TestParseDAT TestEaster CurrentTime ShowDST TimeZone TimeZone.ref TestParseTime RealToFracBenchmark \ - *.out *.run *.o *.hi Makefile.bak - -%.diff: %.ref %.out - diff -u $^ - -%.diff0: %.out - diff -u /dev/null $^ - -%.out: % - ./$< > $@ - -%.run: % - ./$< - touch $@ - -%.hi: %.o - @: - -%.o: %.hs - $(GHC) $(GHCFLAGS) -c $< -o $@ - -%.o: %.lhs - $(GHC) $(GHCFLAGS) -c $< -o $@ - -FORCE: - -.SECONDARY: - From git at git.haskell.org Fri Jan 23 23:00:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:48 +0000 (UTC) Subject: [commit: packages/time] master: added Test.Tests and Test.TestUtil modules (46ce767) Message-ID: <20150123230048.F01683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/46ce76714c2a83d851a644a170ac958673aaa86c >--------------------------------------------------------------- commit 46ce76714c2a83d851a644a170ac958673aaa86c Author: blackredtree Date: Thu Sep 20 15:41:04 2012 -0700 added Test.Tests and Test.TestUtil modules Ignore-this: d5fe357080d6ed4f83e2272ad789bbb3 darcs-hash:20120920224104-08fed-3afdeb091b1fab883b255c1be18af368c103dd2c >--------------------------------------------------------------- 46ce76714c2a83d851a644a170ac958673aaa86c Test/TestUtil.hs | 43 +++++++++++++++++++++++++++++++++++++++++++ Test/Tests.hs | 26 ++++++++++++++++++++++++++ 2 files changed, 69 insertions(+) diff --git a/Test/TestUtil.hs b/Test/TestUtil.hs new file mode 100644 index 0000000..237bcfb --- /dev/null +++ b/Test/TestUtil.hs @@ -0,0 +1,43 @@ +module Test.TestUtil + ( SimpleTest(..) + , IO_SimpleTest(..) + , diff + , module Distribution.TestSuite ) + where + +import Distribution.TestSuite + +import System.Cmd +import System.Exit + +-- + +data SimpleTest = SimpleTest String Result + +instance TestOptions SimpleTest where + name (SimpleTest s _) = s + options = const [] + defaultOptions _ = return $ Options [] + check _ _ = [] + +instance PureTestable SimpleTest where + run (SimpleTest _ r) _ = r + +-- + +data IO_SimpleTest = IO_SimpleTest String (IO Result) + +instance TestOptions IO_SimpleTest where + name (IO_SimpleTest s _) = s + options = const [] + defaultOptions _ = return $ Options [] + check _ _ = [] + +instance ImpureTestable IO_SimpleTest where + runM (IO_SimpleTest _ r) _ = r + +-- + +diff :: String -> String -> Result +diff s t + = if s == t then Pass else Fail "" diff --git a/Test/Tests.hs b/Test/Tests.hs new file mode 100644 index 0000000..d8e1cb2 --- /dev/null +++ b/Test/Tests.hs @@ -0,0 +1,26 @@ +module Test.Tests where + +import Distribution.TestSuite + +import Test.AddDays +import Test.ClipDates +import Test.ConvertBack +import Test.LongWeekYears +import Test.TestCalendars +import Test.TestEaster +import Test.TestFormat +import Test.TestMonthDay +import Test.TestParseDAT +import Test.TestTime + +tests :: [Test] +tests = [ addDaysTest + , clipDates + , convertBack + , longWeekYears + , testCalendars + , testEaster + , testFormat + , testMonthDay + , testParseDAT + , testTime ] From git at git.haskell.org Fri Jan 23 23:00:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:51 +0000 (UTC) Subject: [commit: packages/time] master: get working with Cabal 1.16; fix up build process (2fa30f7) Message-ID: <20150123230051.03C223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2fa30f752df06fad3f4245f99b9c3aefcdf447df >--------------------------------------------------------------- commit 2fa30f752df06fad3f4245f99b9c3aefcdf447df Author: Ashley Yakeley Date: Sun Oct 21 16:48:44 2012 -0700 get working with Cabal 1.16; fix up build process Ignore-this: f4503eb3fa2fbd1ac938024548d1176f darcs-hash:20121021234844-ac6dd-fc357fa538cdf5e1c09c14771cd37c204331a35a >--------------------------------------------------------------- 2fa30f752df06fad3f4245f99b9c3aefcdf447df Makefile | 10 +++++----- Setup.hs | 18 +----------------- Test/TestUtil.hs | 38 ++++++++------------------------------ Test/Tests.hs | 4 ++-- configure.ac | 2 ++ time.cabal | 6 +++--- 6 files changed, 21 insertions(+), 57 deletions(-) diff --git a/Makefile b/Makefile index a0b37a9..37a78fc 100644 --- a/Makefile +++ b/Makefile @@ -6,24 +6,24 @@ clean: cabal clean configure: - cabal configure --enable-library-profiling --enable-executable-profiling + cabal configure --enable-library-profiling --enable-executable-profiling --enable-tests build: configure cabal build --ghc-options=-Werror -test: install +test: build cabal test haddock: configure cabal haddock -install: build haddock +install: build test haddock cabal install --user --enable-library-profiling --enable-executable-profiling -sdist: configure +sdist: clean configure cabal sdist # switch off intermediate file deletion .SECONDARY: -.PHONY: default configure build haddock install test sdist +.PHONY: default clean configure build haddock install test sdist diff --git a/Setup.hs b/Setup.hs index cdd46de..26fdbce 100644 --- a/Setup.hs +++ b/Setup.hs @@ -1,26 +1,10 @@ module Main (main) where -import Control.Exception -import Distribution.PackageDescription import Distribution.Simple -import Distribution.Simple.LocalBuildInfo -import Distribution.Simple.Utils -import System.Cmd -import System.Directory import System.Info main :: IO () main = case os of "windows" -> defaultMain "mingw32" -> defaultMain - _ -> let hooks = autoconfUserHooks { runTests = runTestScript } in defaultMainWithHooks hooks - -withCurrentDirectory :: FilePath -> IO a -> IO a -withCurrentDirectory path f = do - cur <- getCurrentDirectory - setCurrentDirectory path - finally f (setCurrentDirectory cur) - -runTestScript :: Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO () -runTestScript _args _flag _pd _lbi - = maybeExit $ withCurrentDirectory "test" $ system "make" + _ -> defaultMainWithHooks autoconfUserHooks diff --git a/Test/TestUtil.hs b/Test/TestUtil.hs index 237bcfb..2c0be91 100644 --- a/Test/TestUtil.hs +++ b/Test/TestUtil.hs @@ -1,42 +1,20 @@ module Test.TestUtil - ( SimpleTest(..) - , IO_SimpleTest(..) - , diff - , module Distribution.TestSuite ) - where + ( + module Test.TestUtil + , module Distribution.TestSuite + ) where import Distribution.TestSuite -import System.Cmd -import System.Exit - --- - data SimpleTest = SimpleTest String Result -instance TestOptions SimpleTest where - name (SimpleTest s _) = s - options = const [] - defaultOptions _ = return $ Options [] - check _ _ = [] - -instance PureTestable SimpleTest where - run (SimpleTest _ r) _ = r - --- +pure :: SimpleTest -> Test +pure (SimpleTest name result) = Test (TestInstance (return (Finished result)) name [] [] (\_ _ -> Left "")) data IO_SimpleTest = IO_SimpleTest String (IO Result) -instance TestOptions IO_SimpleTest where - name (IO_SimpleTest s _) = s - options = const [] - defaultOptions _ = return $ Options [] - check _ _ = [] - -instance ImpureTestable IO_SimpleTest where - runM (IO_SimpleTest _ r) _ = r - --- +impure :: IO_SimpleTest -> Test +impure (IO_SimpleTest name mresult) = Test (TestInstance (fmap Finished mresult) name [] [] (\_ _ -> Left "")) diff :: String -> String -> Result diff s t diff --git a/Test/Tests.hs b/Test/Tests.hs index d8e1cb2..2185918 100644 --- a/Test/Tests.hs +++ b/Test/Tests.hs @@ -13,8 +13,8 @@ import Test.TestMonthDay import Test.TestParseDAT import Test.TestTime -tests :: [Test] -tests = [ addDaysTest +tests :: IO [Test] +tests = return [ addDaysTest , clipDates , convertBack , longWeekYears diff --git a/configure.ac b/configure.ac index dc58c49..927625a 100644 --- a/configure.ac +++ b/configure.ac @@ -6,6 +6,8 @@ AC_CONFIG_SRCDIR([include/HsTime.h]) AC_ARG_WITH([cc], [C compiler], [CC=$withval]) +AC_ARG_WITH([gcc],[Gnu C compiler]) +AC_ARG_WITH([compiler],[Haskell compiler]) AC_PROG_CC() AC_CONFIG_HEADERS([include/HsTimeConfig.h]) diff --git a/time.cabal b/time.cabal index e6e2668..ec13915 100644 --- a/time.cabal +++ b/time.cabal @@ -9,8 +9,8 @@ homepage: http://semantic.org/TimeLib/ synopsis: A time library description: A time library category: System -build-type: Simple -cabal-version: >=1.9.2 +build-type: Custom +cabal-version: >=1.16 x-follows-version-policy: extra-source-files: @@ -91,7 +91,7 @@ Test-Suite tests cpp-options: -DLANGUAGE_Rank2Types -DLANGUAGE_DeriveDataTypeable -DLANGUAGE_StandaloneDeriving c-sources: cbits/HsTime.c Test/TestFormatStuff.c include-dirs: include - build-depends: base, deepseq, Cabal >= 1.9.2, old-locale, process + build-depends: base, deepseq, Cabal >= 1.16, old-locale, process other-modules: Test.TestTime Test.TestTimeRef From git at git.haskell.org Fri Jan 23 23:00:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:53 +0000 (UTC) Subject: [commit: packages/time] master: clean up tests (54a7b3b) Message-ID: <20150123230053.0A7EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/54a7b3baccde8bcafd9238f587f728e9beb73b7f >--------------------------------------------------------------- commit 54a7b3baccde8bcafd9238f587f728e9beb73b7f Author: Ashley Yakeley Date: Sun Oct 28 17:05:35 2012 -0700 clean up tests Ignore-this: daf151d23ca95cf9938f58b2378b68df darcs-hash:20121029000535-ac6dd-aa7918f6f704d0591e929c58c506b69250593844 >--------------------------------------------------------------- 54a7b3baccde8bcafd9238f587f728e9beb73b7f Test/AddDays.hs | 2 +- Test/ClipDates.hs | 2 +- Test/ConvertBack.hs | 2 +- Test/LongWeekYears.hs | 2 +- Test/TestCalendars.hs | 2 +- Test/TestEaster.hs | 2 +- Test/TestFormat.hs | 103 ++++++++++++++++++++------------------------------ Test/TestMonthDay.hs | 2 +- Test/TestParseDAT.hs | 2 +- Test/TestTime.hs | 2 +- Test/TestUtil.hs | 37 ++++++++++++++++-- 11 files changed, 83 insertions(+), 75 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 54a7b3baccde8bcafd9238f587f728e9beb73b7f From git at git.haskell.org Fri Jan 23 23:00:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:55 +0000 (UTC) Subject: [commit: packages/time] master: clean up cabal (f3549c0) Message-ID: <20150123230055.1316E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f3549c01321318e863201c60fbab1cae0d7009c0 >--------------------------------------------------------------- commit f3549c01321318e863201c60fbab1cae0d7009c0 Author: Ashley Yakeley Date: Sun Oct 28 22:26:12 2012 -0700 clean up cabal Ignore-this: 5e5b69183c6e72366a4dd98122daa5ef darcs-hash:20121029052612-ac6dd-bcb9e948acbc01ea8ce0964bcbdd20afe27d0796 >--------------------------------------------------------------- f3549c01321318e863201c60fbab1cae0d7009c0 Setup.hs | 10 ---------- time.cabal | 14 ++++++++------ 2 files changed, 8 insertions(+), 16 deletions(-) diff --git a/Setup.hs b/Setup.hs deleted file mode 100644 index 26fdbce..0000000 --- a/Setup.hs +++ /dev/null @@ -1,10 +0,0 @@ -module Main (main) where - -import Distribution.Simple -import System.Info - -main :: IO () -main = case os of - "windows" -> defaultMain - "mingw32" -> defaultMain - _ -> defaultMainWithHooks autoconfUserHooks diff --git a/time.cabal b/time.cabal index ec13915..6574f89 100644 --- a/time.cabal +++ b/time.cabal @@ -9,7 +9,7 @@ homepage: http://semantic.org/TimeLib/ synopsis: A time library description: A time library category: System -build-type: Custom +build-type: Configure cabal-version: >=1.16 x-follows-version-policy: @@ -34,16 +34,17 @@ extra-tmp-files: include/HsTimeConfig.h library - Build-Depends: base >= 4, + build-depends: base >= 4, deepseq >= 1.1, old-locale ghc-options: -Wall + default-language: Haskell2010 if impl(ghc) - extensions: Rank2Types DeriveDataTypeable StandaloneDeriving + default-extensions: Rank2Types DeriveDataTypeable StandaloneDeriving cpp-options: -DLANGUAGE_Rank2Types -DLANGUAGE_DeriveDataTypeable -DLANGUAGE_StandaloneDeriving else if impl(hugs) - extensions: Rank2Types + default-extensions: Rank2Types cpp-options: -DLANGUAGE_Rank2Types if os(windows) build-depends: Win32 @@ -60,7 +61,7 @@ library Data.Time.LocalTime, Data.Time.Format, Data.Time - extensions: ForeignFunctionInterface, CPP + default-extensions: CPP c-sources: cbits/HsTime.c other-modules: Data.Time.Calendar.Private, @@ -87,7 +88,8 @@ library Test-Suite tests type: detailed-0.9 test-module: Test.Tests - extensions: Rank2Types, ForeignFunctionInterface, CPP, DeriveDataTypeable, StandaloneDeriving + default-language: Haskell2010 + default-extensions: Rank2Types, CPP, DeriveDataTypeable, StandaloneDeriving cpp-options: -DLANGUAGE_Rank2Types -DLANGUAGE_DeriveDataTypeable -DLANGUAGE_StandaloneDeriving c-sources: cbits/HsTime.c Test/TestFormatStuff.c include-dirs: include From git at git.haskell.org Fri Jan 23 23:00:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:57 +0000 (UTC) Subject: [commit: packages/time] master: more TestInstance clean-up (0417890) Message-ID: <20150123230057.195D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/041789051b0d6aa09d03560bf0b5b3c7fda9c645 >--------------------------------------------------------------- commit 041789051b0d6aa09d03560bf0b5b3c7fda9c645 Author: Ashley Yakeley Date: Sun Oct 28 22:28:49 2012 -0700 more TestInstance clean-up Ignore-this: 2596abdead9de1796655be9e58f2ce95 darcs-hash:20121029052849-ac6dd-ebd63fbd2dd9044bcd2ec8f5c5073c5514eac0f5 >--------------------------------------------------------------- 041789051b0d6aa09d03560bf0b5b3c7fda9c645 Test/AddDays.hs | 2 +- Test/ClipDates.hs | 2 +- Test/ConvertBack.hs | 2 +- Test/LongWeekYears.hs | 2 +- Test/TestCalendars.hs | 2 +- Test/TestEaster.hs | 2 +- Test/TestFormat.hs | 4 ++-- Test/TestMonthDay.hs | 2 +- Test/TestParseDAT.hs | 2 +- Test/TestTime.hs | 2 +- Test/TestUtil.hs | 38 +++++++++++++++++--------------------- 11 files changed, 28 insertions(+), 32 deletions(-) diff --git a/Test/AddDays.hs b/Test/AddDays.hs index a3754d9..0066673 100644 --- a/Test/AddDays.hs +++ b/Test/AddDays.hs @@ -43,5 +43,5 @@ resultDays = do addDaysTest :: Test addDaysTest - = Test $ pure $ SimpleTest "addDays" + = Test $ pure "addDays" $ diff addDaysRef $ unlines resultDays diff --git a/Test/ClipDates.hs b/Test/ClipDates.hs index 1b5d35f..761b9e9 100644 --- a/Test/ClipDates.hs +++ b/Test/ClipDates.hs @@ -35,7 +35,7 @@ tupleUp3 l1 l2 l3 clipDates :: Test clipDates - = Test $ pure $ SimpleTest "clipDates" + = Test $ pure "clipDates" $ let yad = unlines $ map yearAndDay $ tupleUp2 [1968,1969,1971] [-4,0,1,200,364,365,366,367,700] diff --git a/Test/ConvertBack.hs b/Test/ConvertBack.hs index ce0238b..857e80f 100644 --- a/Test/ConvertBack.hs +++ b/Test/ConvertBack.hs @@ -42,5 +42,5 @@ days = [ModifiedJulianDay 50000 .. ModifiedJulianDay 50200] ++ convertBack :: Test convertBack - = Test $ pure $ SimpleTest "convertBack" + = Test $ pure "convertBack" $ diff "" $ concatMap (\ch -> concatMap ch days) checkers diff --git a/Test/LongWeekYears.hs b/Test/LongWeekYears.hs index 7824425..220b3c7 100644 --- a/Test/LongWeekYears.hs +++ b/Test/LongWeekYears.hs @@ -22,5 +22,5 @@ showLongYear year longWeekYears :: Test longWeekYears - = Test $ pure $ SimpleTest "longWeekYears" + = Test $ pure "longWeekYears" $ diff longWeekYearsRef $ unlines $ map showLongYear [1901 .. 2050] diff --git a/Test/TestCalendars.hs b/Test/TestCalendars.hs index 324b792..5f1932c 100644 --- a/Test/TestCalendars.hs +++ b/Test/TestCalendars.hs @@ -29,7 +29,7 @@ days = [ testCalendars :: Test testCalendars - = Test $ pure $ SimpleTest "testCalendars" + = Test $ pure "testCalendars" $ diff testCalendarsRef $ unlines $ map (\d -> showShowers d) days where diff --git a/Test/TestEaster.hs b/Test/TestEaster.hs index b6b9bd7..e97c84e 100644 --- a/Test/TestEaster.hs +++ b/Test/TestEaster.hs @@ -21,7 +21,7 @@ showWithWDay = formatTime defaultTimeLocale "%F %A" testEaster :: Test testEaster - = Test $ pure $ SimpleTest "testEaster" + = Test $ pure "testEaster" $ let ds = unlines $ map (\day -> unwords [ showWithWDay day, "->" , showWithWDay (sundayAfter day)]) days diff --git a/Test/TestFormat.hs b/Test/TestFormat.hs index eb8b2ee..001de68 100644 --- a/Test/TestFormat.hs +++ b/Test/TestFormat.hs @@ -75,7 +75,7 @@ times = [baseTime0] ++ (fmap getDay [0..23]) ++ (fmap getDay [0..100]) ++ compareFormat :: String -> (String -> String) -> String -> TimeZone -> UTCTime -> TestInstance compareFormat testname modUnix fmt zone time = let ctime = utcToZonedTime zone time in - impure $ IO_SimpleTest (testname ++ ": " ++ (show fmt) ++ " of " ++ (show ctime)) $ + impure (testname ++ ": " ++ (show fmt) ++ " of " ++ (show ctime)) $ do let haskellText = formatTime locale fmt ctime unixText <- fmap modUnix (unixFormatTime fmt zone time) @@ -124,7 +124,7 @@ safeString s = do [] -> return "" compareExpected :: (Eq t,Show t,ParseTime t) => String -> String -> String -> Maybe t -> TestInstance -compareExpected testname fmt str expected = impure $ IO_SimpleTest (testname ++ ": " ++ (show fmt) ++ " on " ++ (show str)) $ do +compareExpected testname fmt str expected = impure (testname ++ ": " ++ (show fmt) ++ " on " ++ (show str)) $ do let found = parseTime defaultTimeLocale fmt str mex <- getBottom found case mex of diff --git a/Test/TestMonthDay.hs b/Test/TestMonthDay.hs index 0d3a665..fa3bdcc 100644 --- a/Test/TestMonthDay.hs +++ b/Test/TestMonthDay.hs @@ -15,7 +15,7 @@ showCompare a1 b a2 = "DIFF: " ++ (show a1) ++ " -> " ++ b ++ " -> " ++ (show a2 testMonthDay :: Test testMonthDay - = Test $ pure $ SimpleTest "testMonthDay" + = Test $ pure "testMonthDay" $ diff testMonthDayRef $ concat $ map (\isL -> unlines (leap isL : yearDays isL)) [False,True] where diff --git a/Test/TestParseDAT.hs b/Test/TestParseDAT.hs index 187d062..313758d 100644 --- a/Test/TestParseDAT.hs +++ b/Test/TestParseDAT.hs @@ -43,7 +43,7 @@ times = testParseDAT :: Test testParseDAT - = Test $ pure $ SimpleTest "testParseDAT" + = Test $ pure "testParseDAT" $ diff testParseDAT_Ref parseDAT where parseDAT = diff --git a/Test/TestTime.hs b/Test/TestTime.hs index c47712e..cfa476b 100644 --- a/Test/TestTime.hs +++ b/Test/TestTime.hs @@ -108,5 +108,5 @@ testTimeOfDayToDayFraction testTime :: Test testTime - = Test $ pure $ SimpleTest "testTime" + = Test $ pure "testTime" $ diff testTimeRef $ unlines [testCal, testUTC, testUT1, testTimeOfDayToDayFraction] diff --git a/Test/TestUtil.hs b/Test/TestUtil.hs index 776b859..88d95d2 100644 --- a/Test/TestUtil.hs +++ b/Test/TestUtil.hs @@ -6,19 +6,21 @@ module Test.TestUtil import Distribution.TestSuite -data SimpleTest = SimpleTest String Result - -pure :: SimpleTest -> TestInstance -pure (SimpleTest name result) = TestInstance (return (Finished result)) name [] [] (\_ _ -> Left "") - -data IO_SimpleTest = IO_SimpleTest String (IO Result) +impure :: String -> IO Result -> TestInstance +impure name mresult = TestInstance { + run = fmap Finished mresult, + name = name, + tags = [], + options = [], + setOption = \_ _ -> Left "unsupported" +} -impure :: IO_SimpleTest -> TestInstance -impure (IO_SimpleTest name mresult) = TestInstance (fmap Finished mresult) name [] [] (\_ _ -> Left "") +pure :: String -> Result -> TestInstance +pure name result = impure name (return result) diff :: String -> String -> Result -diff s t - = if s == t then Pass else Fail "" +diff s t | s == t = Pass +diff _ _ = Fail "" finish :: IO Progress -> IO Result finish iop = do @@ -27,24 +29,18 @@ finish iop = do Finished result -> return result Progress _ iop' -> finish iop' -concatRun :: [IO Progress] -> IO Progress -concatRun [] = return (Finished Pass) +concatRun :: [IO Progress] -> IO Result +concatRun [] = return Pass concatRun (iop:iops) = do result <- finish iop case result of Pass -> concatRun iops - _ -> return (Finished result) + _ -> return result concatTestInstance :: String -> [TestInstance] -> TestInstance -concatTestInstance tname tis = TestInstance { - run = concatRun (fmap run tis), - name = tname, - tags = [], - options = [], - setOption = \_ _ -> Left "unsupported" -} +concatTestInstance tname tis = impure tname (concatRun (fmap run tis)) fastTestInstanceGroup :: String -> [TestInstance] -> Test ---fastTestGroup tname tis = testGroup tname (fmap Test tis) +fastTestInstanceGroup tname tis | False = testGroup tname (fmap Test tis) fastTestInstanceGroup tname tis = Test (concatTestInstance tname tis) From git at git.haskell.org Fri Jan 23 23:00:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:00:59 +0000 (UTC) Subject: [commit: packages/time] master: %C not restricted to two characters in format (295c172) Message-ID: <20150123230059.1FED63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/295c172ffdfd981375485387e3c1963d2544095a >--------------------------------------------------------------- commit 295c172ffdfd981375485387e3c1963d2544095a Author: Ashley Yakeley Date: Sun Oct 28 22:29:37 2012 -0700 %C not restricted to two characters in format Ignore-this: dab171d022b83436dc3a0449525654e darcs-hash:20121029052937-ac6dd-916d8ce315605f9b428f32728e8da8007091ae27 >--------------------------------------------------------------- 295c172ffdfd981375485387e3c1963d2544095a Data/Time/Format.hs | 4 ++-- Test/TestFormat.hs | 5 ++++- 2 files changed, 6 insertions(+), 3 deletions(-) diff --git a/Data/Time/Format.hs b/Data/Time/Format.hs index 174bbea..926004b 100644 --- a/Data/Time/Format.hs +++ b/Data/Time/Format.hs @@ -113,7 +113,7 @@ formatChar c locale mpado t = case (formatCharacter c) of -- -- [@%y@] last two digits of year, @00@ - @99@ -- --- [@%C@] century (being the first two digits of the year), @00@ - @99@ +-- [@%C@] century -- -- [@%B@] month name, long form ('fst' from 'months' @locale@), @January@ - @December@ -- @@ -213,7 +213,7 @@ instance FormatTime Day where -- Year Count formatCharacter 'Y' = Just (\_ _ -> show . fst . toOrdinalDate) formatCharacter 'y' = Just (\_ opt -> (show2 (fromMaybe (Just '0') opt)) . mod100 . fst . toOrdinalDate) - formatCharacter 'C' = Just (\_ opt -> (show2 (fromMaybe (Just '0') opt)) . div100 . fst . toOrdinalDate) + formatCharacter 'C' = Just (\_ _ -> show . div100 . fst . toOrdinalDate) -- Month of Year formatCharacter 'B' = Just (\locale _ -> fst . (\(_,m,_) -> (months locale) !! (m - 1)) . toGregorian) formatCharacter 'b' = Just (\locale _ -> snd . (\(_,m,_) -> (months locale) !! (m - 1)) . toGregorian) diff --git a/Test/TestFormat.hs b/Test/TestFormat.hs index 001de68..3aae5e5 100644 --- a/Test/TestFormat.hs +++ b/Test/TestFormat.hs @@ -68,9 +68,12 @@ getYearP3 year = localTimeToUTC utc (LocalTime (fromGregorian year 03 04) midnig getYearP4 :: Integer -> UTCTime getYearP4 year = localTimeToUTC utc (LocalTime (fromGregorian year 12 31) midnight) +years :: [Integer] +years = [999,1000,1899,1900,1901] ++ [1980..2000] ++ [9999,10000] + times :: [UTCTime] times = [baseTime0] ++ (fmap getDay [0..23]) ++ (fmap getDay [0..100]) ++ - (fmap getYearP1 [1980..2000]) ++ (fmap getYearP2 [1980..2000]) ++ (fmap getYearP3 [1980..2000]) ++ (fmap getYearP4 [1980..2000]) + (fmap getYearP1 years) ++ (fmap getYearP2 years) ++ (fmap getYearP3 years) ++ (fmap getYearP4 years) compareFormat :: String -> (String -> String) -> String -> TimeZone -> UTCTime -> TestInstance compareFormat testname modUnix fmt zone time = From git at git.haskell.org Fri Jan 23 23:01:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:01 +0000 (UTC) Subject: [commit: packages/time] master: fix up test infrastructure (500ca20) Message-ID: <20150123230101.284AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/500ca2046c1f85279a4b2b95b71dadc5f4c22986 >--------------------------------------------------------------- commit 500ca2046c1f85279a4b2b95b71dadc5f4c22986 Author: Ashley Yakeley Date: Wed Nov 14 20:17:38 2012 -0800 fix up test infrastructure Ignore-this: 884e829c58ee215ab63a75114c0627ec darcs-hash:20121115041738-ac6dd-c747d085442d3b43b6c8f66bf7b78431ad2efd4b >--------------------------------------------------------------- 500ca2046c1f85279a4b2b95b71dadc5f4c22986 Makefile | 2 +- Test/AddDays.hs | 10 +--- Test/ClipDates.hs | 38 +++++--------- Test/ConvertBack.hs | 10 +--- Test/LongWeekYears.hs | 10 +--- Test/TestCalendars.hs | 17 ++---- Test/TestEaster.hs | 12 ++--- Test/TestFormat.hs | 49 +++++++----------- Test/TestMonthDay.hs | 29 ++++------- Test/TestParseDAT.hs | 35 +++++-------- Test/TestParseTime.hs | 127 +++++++++++++++++++++++---------------------- Test/TestTime.hs | 10 +--- Test/TestUtil.hs | 85 +++++++++++++++--------------- Test/Tests.hs | 8 +-- time.cabal | 140 +++++++++++++++++++++++++++++--------------------- 15 files changed, 271 insertions(+), 311 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 500ca2046c1f85279a4b2b95b71dadc5f4c22986 From git at git.haskell.org Fri Jan 23 23:01:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:03 +0000 (UTC) Subject: [commit: packages/time] master: more test infrastructure (b85fefa) Message-ID: <20150123230103.2FA363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b85fefa65a538c2e38bd688594c68fd0d16236db >--------------------------------------------------------------- commit b85fefa65a538c2e38bd688594c68fd0d16236db Author: Ashley Yakeley Date: Thu Nov 15 00:52:10 2012 -0800 more test infrastructure Ignore-this: 7e091ce926e7c054340ecdbc1779fb84 darcs-hash:20121115085210-ac6dd-a38387a32dbb5d33ce700fc5004aa8e73475831f >--------------------------------------------------------------- b85fefa65a538c2e38bd688594c68fd0d16236db Test.hs | 6 ++++++ Test/TestParseTime.hs | 35 ----------------------------------- 2 files changed, 6 insertions(+), 35 deletions(-) diff --git a/Test.hs b/Test.hs new file mode 100644 index 0000000..27e2bee --- /dev/null +++ b/Test.hs @@ -0,0 +1,6 @@ +module Main where +import Test.Framework +import Test.Tests + +main :: IO () +main = defaultMain tests diff --git a/Test/TestParseTime.hs b/Test/TestParseTime.hs index 823a3c1..fa7b241 100644 --- a/Test/TestParseTime.hs +++ b/Test/TestParseTime.hs @@ -12,13 +12,7 @@ import Data.Time.Calendar.WeekDate import Data.Time.Clock.POSIX import System.Locale import Test.QuickCheck hiding (Result) ---import qualified Test.QuickCheck import Test.TestUtil ---import qualified Test.TestUtil - - ---instance RunTest Property where --- runTest p = run p (TestOptions {no_of_tests = 10000,length_of_tests = 0,debug_tests = False}) ntest :: Int ntest = 1000 @@ -32,9 +26,6 @@ testParseTime = testGroup "testParseTime" testGroup "properties" (fmap (\(n,prop) -> testProperty n prop) properties) ] -{- -knownFailures --} yearDays :: Integer -> [Day] yearDays y = [(fromGregorian y 1 1) .. (fromGregorian y 12 31)] @@ -83,38 +74,12 @@ parseCYY c i = return $ diff (Just (fromGregorian ((c * 100) + i) 1 1)) (parse " parseCYY2 :: Integer -> Integer -> IO Result parseCYY2 c i = return $ diff (Just (fromGregorian ((c * 100) + i) 1 1)) (parse "%C %y" ((show2 c) ++ " " ++ (show2 i))) -{- -checkAll :: RunTest p => [(String,p)] -> IO Bool -checkAll ps = fmap and (mapM checkOne ps) - -trMessage :: TestResult -> String -trMessage (TestOk s _ _) = s -trMessage (TestExausted s i ss) = "Exhausted " ++ (show s) ++ " " ++ (show i) ++ " " ++ (show ss) -trMessage (TestFailed ss i) = "Failed " ++ (show ss) ++ " " ++ (show i) -trMessage (TestAborted ex) = "Aborted " ++ (show ex) - -trGood :: TestResult -> Bool -trGood (TestOk _ _ _) = True -trGood _ = False - -checkOne :: RunTest p => (String,p) -> IO Bool -checkOne (n,p) = - do - putStr (rpad 65 ' ' n) - tr <- runTest p - putStrLn (trMessage tr) - return (trGood tr) - where - rpad n' c xs = xs ++ replicate (n' - length xs) c --} - parse :: ParseTime t => String -> String -> Maybe t parse f t = parseTime defaultTimeLocale f t format :: (FormatTime t) => String -> t -> String format f t = formatTime defaultTimeLocale f t - instance Arbitrary Day where arbitrary = liftM ModifiedJulianDay $ choose (-313698, 2973483) -- 1000-01-1 to 9999-12-31 From git at git.haskell.org Fri Jan 23 23:01:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:05 +0000 (UTC) Subject: [commit: packages/time] master: fixed some parsing issues; more test sorting out (3d0480a) Message-ID: <20150123230105.396903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/3d0480ac7ea30169cc5b3f5e3d39aa45f9bd80b8 >--------------------------------------------------------------- commit 3d0480ac7ea30169cc5b3f5e3d39aa45f9bd80b8 Author: Ashley Yakeley Date: Sat Nov 24 03:47:35 2012 -0800 fixed some parsing issues; more test sorting out Ignore-this: d08009aa11f8a8919041b57651193763 darcs-hash:20121124114735-ac6dd-252292144b82f3ec98609cdc344de145d123a3a1 >--------------------------------------------------------------- 3d0480ac7ea30169cc5b3f5e3d39aa45f9bd80b8 Data/Time/Format/Parse.hs | 176 +++++++++++++++++++++++++++++----------------- Test/AddDaysRef.hs | 1 + Test/ClipDatesRef.hs | 1 + Test/LongWeekYearsRef.hs | 1 + Test/TAI_UTC_DAT.hs | 1 + Test/TestCalendarsRef.hs | 1 + Test/TestEasterRef.hs | 1 + Test/TestMonthDayRef.hs | 1 + Test/TestParseDAT_Ref.hs | 1 + Test/TestParseTime.hs | 82 +++++++++++++-------- Test/TestTimeRef.hs | 1 + Test/TestUtil.hs | 7 +- 12 files changed, 174 insertions(+), 100 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3d0480ac7ea30169cc5b3f5e3d39aa45f9bd80b8 From git at git.haskell.org Fri Jan 23 23:01:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:07 +0000 (UTC) Subject: [commit: packages/time] master: fix format modifiers for YCGf (fc49f3e) Message-ID: <20150123230107.405BB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/fc49f3e92d7ce4474d16a282784da6686ed8a180 >--------------------------------------------------------------- commit fc49f3e92d7ce4474d16a282784da6686ed8a180 Author: Ashley Yakeley Date: Sat Nov 24 18:23:58 2012 -0800 fix format modifiers for YCGf Ignore-this: 6fb972e177214f11f807e125d5e69da3 darcs-hash:20121125022358-ac6dd-901bbe054d6df17f3410480ba25140d6d0068879 >--------------------------------------------------------------- fc49f3e92d7ce4474d16a282784da6686ed8a180 Data/Time/Calendar/Private.hs | 32 ++++++++++++++------------------ Data/Time/Format.hs | 8 ++++---- Test/TestFormat.hs | 21 +++++++++++++++++++-- 3 files changed, 37 insertions(+), 24 deletions(-) diff --git a/Data/Time/Calendar/Private.hs b/Data/Time/Calendar/Private.hs index 6afe648..f241dc3 100644 --- a/Data/Time/Calendar/Private.hs +++ b/Data/Time/Calendar/Private.hs @@ -9,33 +9,29 @@ pad1 :: NumericPadOption -> String -> String pad1 (Just c) s = c:s pad1 _ s = s +padN :: Int -> Char -> String -> String +padN i _ s | i <= 0 = s +padN i c s = (replicate i c) ++ s + show2Fixed :: NumericPadOption -> Pico -> String show2Fixed opt x | x < 10 = pad1 opt (showFixed True x) show2Fixed _ x = showFixed True x +showPaddedMin :: (Num t,Ord t,Show t) => Int -> NumericPadOption -> t -> String +showPaddedMin _ Nothing i = show i +showPaddedMin pl opt i | i < 0 = '-':(showPaddedMin pl opt (negate i)) +showPaddedMin pl (Just c) i = + let s = show i in + padN (pl - (length s)) c s + show2 :: (Num t,Ord t,Show t) => NumericPadOption -> t -> String -show2 opt i | i < 0 = '-':(show2 opt (negate i)) -show2 opt i = let - s = show i in - case s of - [_] -> pad1 opt s - _ -> s +show2 = showPaddedMin 2 show3 :: (Num t,Ord t,Show t) => NumericPadOption -> t -> String -show3 opt i | i < 0 = '-':(show3 opt (negate i)) -show3 opt i = let - s = show2 opt i in - case s of - [_,_] -> pad1 opt s - _ -> s +show3 = showPaddedMin 3 show4 :: (Num t,Ord t,Show t) => NumericPadOption -> t -> String -show4 opt i | i < 0 = '-':(show4 opt (negate i)) -show4 opt i = let - s = show3 opt i in - case s of - [_,_,_] -> pad1 opt s - _ -> s +show4 = showPaddedMin 4 mod100 :: (Integral i) => i -> i mod100 x = mod x 100 diff --git a/Data/Time/Format.hs b/Data/Time/Format.hs index 926004b..f332f97 100644 --- a/Data/Time/Format.hs +++ b/Data/Time/Format.hs @@ -211,9 +211,9 @@ instance FormatTime Day where formatCharacter 'x' = Just (\locale _ -> formatTime locale (dateFmt locale)) -- Year Count - formatCharacter 'Y' = Just (\_ _ -> show . fst . toOrdinalDate) + formatCharacter 'Y' = Just (\_ opt -> (show4 (fromMaybe Nothing opt)) . fst . toOrdinalDate) formatCharacter 'y' = Just (\_ opt -> (show2 (fromMaybe (Just '0') opt)) . mod100 . fst . toOrdinalDate) - formatCharacter 'C' = Just (\_ _ -> show . div100 . fst . toOrdinalDate) + formatCharacter 'C' = Just (\_ opt -> (show2 (fromMaybe Nothing opt)) . div100 . fst . toOrdinalDate) -- Month of Year formatCharacter 'B' = Just (\locale _ -> fst . (\(_,m,_) -> (months locale) !! (m - 1)) . toGregorian) formatCharacter 'b' = Just (\locale _ -> snd . (\(_,m,_) -> (months locale) !! (m - 1)) . toGregorian) @@ -226,9 +226,9 @@ instance FormatTime Day where formatCharacter 'j' = Just (\_ opt -> (show3 (fromMaybe (Just '0') opt)) . snd . toOrdinalDate) -- ISO 8601 Week Date - formatCharacter 'G' = Just (\_ _ -> show . (\(y,_,_) -> y) . toWeekDate) + formatCharacter 'G' = Just (\_ opt -> (show4 (fromMaybe Nothing opt)) . (\(y,_,_) -> y) . toWeekDate) formatCharacter 'g' = Just (\_ opt -> (show2 (fromMaybe (Just '0') opt)) . mod100 . (\(y,_,_) -> y) . toWeekDate) - formatCharacter 'f' = Just (\_ opt -> (show2 (fromMaybe (Just '0') opt)) . div100 . (\(y,_,_) -> y) . toWeekDate) + formatCharacter 'f' = Just (\_ opt -> (show2 (fromMaybe Nothing opt)) . div100 . (\(y,_,_) -> y) . toWeekDate) formatCharacter 'V' = Just (\_ opt -> (show2 (fromMaybe (Just '0') opt)) . (\(_,w,_) -> w) . toWeekDate) formatCharacter 'u' = Just (\_ _ -> show . (\(_,_,d) -> d) . toWeekDate) diff --git a/Test/TestFormat.hs b/Test/TestFormat.hs index c063847..fe5f375 100644 --- a/Test/TestFormat.hs +++ b/Test/TestFormat.hs @@ -70,17 +70,34 @@ times :: [UTCTime] times = [baseTime0] ++ (fmap getDay [0..23]) ++ (fmap getDay [0..100]) ++ (fmap getYearP1 years) ++ (fmap getYearP2 years) ++ (fmap getYearP3 years) ++ (fmap getYearP4 years) +padN :: Int -> Char -> String -> String +padN n _ s | n <= (length s) = s +padN n c s = (replicate (n - length s) c) ++ s + +unixWorkarounds :: String -> String -> String +unixWorkarounds "%_Y" s = padN 4 ' ' s +unixWorkarounds "%0Y" s = padN 4 '0' s +unixWorkarounds "%_C" s = padN 2 ' ' s +unixWorkarounds "%0C" s = padN 2 '0' s +unixWorkarounds "%_G" s = padN 4 ' ' s +unixWorkarounds "%0G" s = padN 4 '0' s +unixWorkarounds "%_f" s = padN 2 ' ' s +unixWorkarounds "%0f" s = padN 2 '0' s +unixWorkarounds _ s = s + compareFormat :: String -> (String -> String) -> String -> TimeZone -> UTCTime -> Test compareFormat testname modUnix fmt zone time = let ctime = utcToZonedTime zone time haskellText = formatTime locale fmt ctime in ioTest (testname ++ ": " ++ (show fmt) ++ " of " ++ (show ctime)) $ do - unixText <- fmap modUnix (unixFormatTime fmt zone time) - return $ diff unixText haskellText + unixText <- unixFormatTime fmt zone time + let expectedText = unixWorkarounds fmt (modUnix unixText) + return $ diff expectedText haskellText -- as found in http://www.opengroup.org/onlinepubs/007908799/xsh/strftime.html -- plus FgGklz +-- f not supported -- P not always supported -- s time-zone dependent chars :: [Char] From git at git.haskell.org Fri Jan 23 23:01:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:09 +0000 (UTC) Subject: [commit: packages/time] master: test warning on 32-bit systems (63896a3) Message-ID: <20150123230109.46C413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/63896a3379e35c635487ecb0c8ca90fb0debb6f4 >--------------------------------------------------------------- commit 63896a3379e35c635487ecb0c8ca90fb0debb6f4 Author: Ashley Yakeley Date: Sun Nov 25 02:18:39 2012 -0800 test warning on 32-bit systems Ignore-this: 8b699d17f9112b170580414a8b4a2b2 darcs-hash:20121125101839-ac6dd-953b3b0c939f02e528a3a8fb3fce55365e8839c4 >--------------------------------------------------------------- 63896a3379e35c635487ecb0c8ca90fb0debb6f4 Test.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/Test.hs b/Test.hs index 27e2bee..855e73c 100644 --- a/Test.hs +++ b/Test.hs @@ -1,6 +1,11 @@ module Main where import Test.Framework import Test.Tests +import Foreign.C.Types main :: IO () -main = defaultMain tests +main = do + if (toRational (1000000000000 :: CTime)) /= (1000000000000 :: Rational) + then putStrLn "WARNING: Some tests will incorrectly fail due to a 32-bit time_t C type." + else return () + defaultMain tests From git at git.haskell.org Fri Jan 23 23:01:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:11 +0000 (UTC) Subject: [commit: packages/time] master: update haddock for format & parse (9b3c6c7) Message-ID: <20150123230111.4E7EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/9b3c6c7662ec88e8b2df1d43927027989668c6e3 >--------------------------------------------------------------- commit 9b3c6c7662ec88e8b2df1d43927027989668c6e3 Author: Ashley Yakeley Date: Sun Nov 25 02:54:34 2012 -0800 update haddock for format & parse Ignore-this: 5f710d4cf2071a3e93fe5b17729a72de darcs-hash:20121125105434-ac6dd-361778510fc0965617ec4b4f3316bc37adfb3ff7 >--------------------------------------------------------------- 9b3c6c7662ec88e8b2df1d43927027989668c6e3 Data/Time/Format.hs | 48 +++++++++++++++++++++++------------------------ Data/Time/Format/Parse.hs | 36 +++++++++++++++++++++-------------- 2 files changed, 46 insertions(+), 38 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9b3c6c7662ec88e8b2df1d43927027989668c6e3 From git at git.haskell.org Fri Jan 23 23:01:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:13 +0000 (UTC) Subject: [commit: packages/time] master: fix time.cabal (c5f3fdc) Message-ID: <20150123230113.54F943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c5f3fdc94e0724af6bc91be94487e939d2211da6 >--------------------------------------------------------------- commit c5f3fdc94e0724af6bc91be94487e939d2211da6 Author: Ashley Yakeley Date: Sun Nov 25 03:12:24 2012 -0800 fix time.cabal Ignore-this: bac91d44100c3aab03e4ef2440ec3a9c darcs-hash:20121125111224-ac6dd-c7db079938d2688d6803332b742e4e02ff9abaaf >--------------------------------------------------------------- c5f3fdc94e0724af6bc91be94487e939d2211da6 configure.ac | 2 +- time.cabal | 15 ++++++++------- 2 files changed, 9 insertions(+), 8 deletions(-) diff --git a/configure.ac b/configure.ac index 927625a..82a1173 100644 --- a/configure.ac +++ b/configure.ac @@ -1,4 +1,4 @@ -AC_INIT([Haskell time package], [1.3], [ashley at semantic.org], [time]) +AC_INIT([Haskell time package], [1.4.0.2], [ashley at semantic.org], [time]) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([include/HsTime.h]) diff --git a/time.cabal b/time.cabal index 7254d3b..0335d52 100644 --- a/time.cabal +++ b/time.cabal @@ -20,19 +20,20 @@ extra-source-files: include/HsConfigure.h include/HsTime.h include/HsTimeConfig.h.in - test/Makefile - test/*.hs - test/*.lhs - test/*.ref - test/*.dat - test/*.c - test/*.h + Test/*.hs + Test/*.lhs + Test/*.c + Test/*.h extra-tmp-files: config.log config.status autom4te.cache include/HsTimeConfig.h +source-repository head + type: darcs + location: http://code.haskell.org/time/ + library build-depends: base >= 4, From git at git.haskell.org Fri Jan 23 23:01:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:15 +0000 (UTC) Subject: [commit: packages/time] master: more fixing of time.cabal (d452222) Message-ID: <20150123230115.5BD063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/d4522223d762136234793dbdef5c21bbb000143e >--------------------------------------------------------------- commit d4522223d762136234793dbdef5c21bbb000143e Author: Ashley Yakeley Date: Sun Nov 25 03:22:49 2012 -0800 more fixing of time.cabal Ignore-this: 589eeb82bf6e1c7a8a4513c924c2299a darcs-hash:20121125112249-ac6dd-dc7003a0bcdf8530d63fee170344b4513490e119 >--------------------------------------------------------------- d4522223d762136234793dbdef5c21bbb000143e time.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/time.cabal b/time.cabal index 0335d52..873a06a 100644 --- a/time.cabal +++ b/time.cabal @@ -10,7 +10,7 @@ synopsis: A time library description: A time library category: System build-type: Configure -cabal-version: >=1.16 +cabal-version: >=1.14 x-follows-version-policy: extra-source-files: @@ -36,7 +36,7 @@ source-repository head library build-depends: - base >= 4, + base >= 4 && < 5, deepseq >= 1.1, old-locale ghc-options: -Wall From git at git.haskell.org Fri Jan 23 23:01:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:17 +0000 (UTC) Subject: [commit: packages/time] master: Derive Typeable instances (222f71c) Message-ID: <20150123230117.6380B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/222f71c3c2d97dfcb68e2db171d57835695c91b5 >--------------------------------------------------------------- commit 222f71c3c2d97dfcb68e2db171d57835695c91b5 Author: jpm Date: Wed Nov 28 06:58:44 2012 -0800 Derive Typeable instances Ignore-this: d301bb00a270f5c27cf9bffc27f85828 darcs-hash:20121128145844-ddd07-279620f99a395c40ffc649ee93d3c5bee3e4e7d9 >--------------------------------------------------------------- 222f71c3c2d97dfcb68e2db171d57835695c91b5 Data/Time/Calendar/Days.hs | 5 +---- Data/Time/Clock/Scale.hs | 10 ++-------- Data/Time/Clock/TAI.hs | 5 +---- Data/Time/Clock/UTC.hs | 10 ++-------- Data/Time/LocalTime/LocalTime.hs | 10 ++-------- Data/Time/LocalTime/TimeOfDay.hs | 5 +---- Data/Time/LocalTime/TimeZone.hs | 5 +---- 7 files changed, 10 insertions(+), 40 deletions(-) diff --git a/Data/Time/Calendar/Days.hs b/Data/Time/Calendar/Days.hs index 6911833..9b535c0 100644 --- a/Data/Time/Calendar/Days.hs +++ b/Data/Time/Calendar/Days.hs @@ -18,7 +18,7 @@ import Data.Data newtype Day = ModifiedJulianDay {toModifiedJulianDay :: Integer} deriving (Eq,Ord #if LANGUAGE_DeriveDataTypeable #if LANGUAGE_Rank2Types - ,Data + ,Data, Typeable #endif #endif ) @@ -26,9 +26,6 @@ newtype Day = ModifiedJulianDay {toModifiedJulianDay :: Integer} deriving (Eq,Or instance NFData Day where rnf (ModifiedJulianDay a) = rnf a -instance Typeable Day where - typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Calendar.Days" "Day") [] - -- necessary because H98 doesn't have "cunning newtype" derivation instance Enum Day where succ (ModifiedJulianDay a) = ModifiedJulianDay (succ a) diff --git a/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs index 237a77b..9e91795 100644 --- a/Data/Time/Clock/Scale.hs +++ b/Data/Time/Clock/Scale.hs @@ -25,7 +25,7 @@ import Data.Data newtype UniversalTime = ModJulianDate {getModJulianDate :: Rational} deriving (Eq,Ord #if LANGUAGE_DeriveDataTypeable #if LANGUAGE_Rank2Types - ,Data + ,Data, Typeable #endif #endif ) @@ -34,9 +34,6 @@ newtype UniversalTime = ModJulianDate {getModJulianDate :: Rational} deriving (E instance NFData UniversalTime where rnf (ModJulianDate a) = rnf a -instance Typeable UniversalTime where - typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.Scale" "UniversalTime") [] - -- | This is a length of time, as measured by a clock. -- Conversion functions will treat it as seconds. -- It has a precision of 10^-12 s. @@ -44,7 +41,7 @@ newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord #if LANGUAGE_DeriveDataTypeable #if LANGUAGE_Rank2Types #if HAS_DataPico - ,Data + ,Data, Typeable #else #endif #endif @@ -54,9 +51,6 @@ newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord -- necessary because H98 doesn't have "cunning newtype" derivation instance NFData DiffTime -- FIXME: Data.Fixed had no NFData instances yet at time of writing -instance Typeable DiffTime where - typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.Scale" "DiffTime") [] - -- necessary because H98 doesn't have "cunning newtype" derivation instance Enum DiffTime where succ (MkDiffTime a) = MkDiffTime (succ a) diff --git a/Data/Time/Clock/TAI.hs b/Data/Time/Clock/TAI.hs index 5e6bfef..271f750 100644 --- a/Data/Time/Clock/TAI.hs +++ b/Data/Time/Clock/TAI.hs @@ -30,7 +30,7 @@ newtype AbsoluteTime = MkAbsoluteTime {unAbsoluteTime :: DiffTime} deriving (Eq, #if LANGUAGE_DeriveDataTypeable #if LANGUAGE_Rank2Types #if HAS_DataPico - ,Data + ,Data, Typeable #endif #endif #endif @@ -39,9 +39,6 @@ newtype AbsoluteTime = MkAbsoluteTime {unAbsoluteTime :: DiffTime} deriving (Eq, instance NFData AbsoluteTime where rnf (MkAbsoluteTime a) = rnf a -instance Typeable AbsoluteTime where - typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.TAI" "AbsoluteTime") [] - instance Show AbsoluteTime where show t = show (utcToLocalTime utc (taiToUTCTime (const 0) t)) ++ " TAI" -- ugly, but standard apparently diff --git a/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs index da1ecc2..3ba3309 100644 --- a/Data/Time/Clock/UTC.hs +++ b/Data/Time/Clock/UTC.hs @@ -36,7 +36,7 @@ data UTCTime = UTCTime { #if LANGUAGE_DeriveDataTypeable #if LANGUAGE_Rank2Types #if HAS_DataPico - deriving (Data) + deriving (Data, Typeable) #endif #endif #endif @@ -44,9 +44,6 @@ data UTCTime = UTCTime { instance NFData UTCTime where rnf (UTCTime d t) = d `deepseq` t `deepseq` () -instance Typeable UTCTime where - typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.UTC" "UTCTime") [] - instance Eq UTCTime where (UTCTime da ta) == (UTCTime db tb) = (da == db) && (ta == tb) @@ -65,7 +62,7 @@ newtype NominalDiffTime = MkNominalDiffTime Pico deriving (Eq,Ord #if LANGUAGE_DeriveDataTypeable #if LANGUAGE_Rank2Types #if HAS_DataPico - ,Data + ,Data, Typeable #endif #endif #endif @@ -74,9 +71,6 @@ newtype NominalDiffTime = MkNominalDiffTime Pico deriving (Eq,Ord -- necessary because H98 doesn't have "cunning newtype" derivation instance NFData NominalDiffTime -- FIXME: Data.Fixed had no NFData instances yet at time of writing -instance Typeable NominalDiffTime where - typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.UTC" "NominalDiffTime") [] - instance Enum NominalDiffTime where succ (MkNominalDiffTime a) = MkNominalDiffTime (succ a) pred (MkNominalDiffTime a) = MkNominalDiffTime (pred a) diff --git a/Data/Time/LocalTime/LocalTime.hs b/Data/Time/LocalTime/LocalTime.hs index 02f06a4..b32af80 100644 --- a/Data/Time/LocalTime/LocalTime.hs +++ b/Data/Time/LocalTime/LocalTime.hs @@ -34,7 +34,7 @@ data LocalTime = LocalTime { #if LANGUAGE_DeriveDataTypeable #if LANGUAGE_Rank2Types #if HAS_DataPico - ,Data + ,Data, Typeable #endif #endif #endif @@ -43,9 +43,6 @@ data LocalTime = LocalTime { instance NFData LocalTime where rnf (LocalTime d t) = d `deepseq` t `deepseq` () -instance Typeable LocalTime where - typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.LocalTime" "LocalTime") [] - instance Show LocalTime where show (LocalTime d t) = (showGregorian d) ++ " " ++ (show t) @@ -78,7 +75,7 @@ data ZonedTime = ZonedTime { #if LANGUAGE_DeriveDataTypeable #if LANGUAGE_Rank2Types #if HAS_DataPico - deriving (Data) + deriving (Data, Typeable) #endif #endif #endif @@ -86,9 +83,6 @@ data ZonedTime = ZonedTime { instance NFData ZonedTime where rnf (ZonedTime lt z) = lt `deepseq` z `deepseq` () -instance Typeable ZonedTime where - typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.LocalTime" "ZonedTime") [] - utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime utcToZonedTime zone time = ZonedTime (utcToLocalTime zone time) zone diff --git a/Data/Time/LocalTime/TimeOfDay.hs b/Data/Time/LocalTime/TimeOfDay.hs index 8fdf539..93c0c70 100644 --- a/Data/Time/LocalTime/TimeOfDay.hs +++ b/Data/Time/LocalTime/TimeOfDay.hs @@ -33,7 +33,7 @@ data TimeOfDay = TimeOfDay { #if LANGUAGE_DeriveDataTypeable #if LANGUAGE_Rank2Types #if HAS_DataPico - ,Data + ,Data, Typeable #endif #endif #endif @@ -42,9 +42,6 @@ data TimeOfDay = TimeOfDay { instance NFData TimeOfDay where rnf (TimeOfDay h m s) = h `deepseq` m `deepseq` s `seq` () -- FIXME: Data.Fixed had no NFData instances yet at time of writing -instance Typeable TimeOfDay where - typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.TimeOfDay" "TimeOfDay") [] - -- | Hour zero midnight :: TimeOfDay midnight = TimeOfDay 0 0 0 diff --git a/Data/Time/LocalTime/TimeZone.hs b/Data/Time/LocalTime/TimeZone.hs index 689288f..fa70026 100644 --- a/Data/Time/LocalTime/TimeZone.hs +++ b/Data/Time/LocalTime/TimeZone.hs @@ -36,7 +36,7 @@ data TimeZone = TimeZone { } deriving (Eq,Ord #if LANGUAGE_DeriveDataTypeable #if LANGUAGE_Rank2Types - ,Data + ,Data, Typeable #endif #endif ) @@ -44,9 +44,6 @@ data TimeZone = TimeZone { instance NFData TimeZone where rnf (TimeZone m so n) = m `deepseq` so `deepseq` n `deepseq` () -instance Typeable TimeZone where - typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.TimeZone" "TimeZone") [] - -- | Create a nameless non-summer timezone for this number of minutes minutesToTimeZone :: Int -> TimeZone minutesToTimeZone m = TimeZone m False "" From git at git.haskell.org Fri Jan 23 23:01:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:19 +0000 (UTC) Subject: [commit: packages/time] master: use throwErrnoIfMinus1 gettimeofday for consistency in error handling (d575902) Message-ID: <20150123230119.6B49F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/d575902c77c2697cc03e28a0f3e81fffbae7c7b6 >--------------------------------------------------------------- commit d575902c77c2697cc03e28a0f3e81fffbae7c7b6 Author: Dylan Simon Date: Fri Jan 25 18:59:54 2013 -0800 use throwErrnoIfMinus1 gettimeofday for consistency in error handling Ignore-this: fc81b9dd998c4e7c01a58d3e3a104cb8 darcs-hash:20130126025954-56c21-c94b312b53512f2202f5012b2abab5b2b8f4c05d >--------------------------------------------------------------- d575902c77c2697cc03e28a0f3e81fffbae7c7b6 Data/Time/Clock/CTimeval.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/Data/Time/Clock/CTimeval.hs b/Data/Time/Clock/CTimeval.hs index 5e0ffdf..b0d8920 100644 --- a/Data/Time/Clock/CTimeval.hs +++ b/Data/Time/Clock/CTimeval.hs @@ -25,10 +25,8 @@ foreign import ccall unsafe "time.h gettimeofday" gettimeofday :: Ptr CTimeval - -- | Get the current POSIX time from the system clock. getCTimeval :: IO CTimeval getCTimeval = with (MkCTimeval 0 0) (\ptval -> do - result <- gettimeofday ptval nullPtr - if (result == 0) - then peek ptval - else fail ("error in gettimeofday: " ++ (show result)) + throwErrnoIfMinus1_ "gettimeofday" $ gettimeofday ptval nullPtr + peek ptval ) #endif From git at git.haskell.org Fri Jan 23 23:01:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:21 +0000 (UTC) Subject: [commit: packages/time] master: Make getTimeZone cross-platform consistent by always considering the TZ environment variable. (9926c4a) Message-ID: <20150123230121.715B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/9926c4aae23dc11afb018175a15e505da4e73e73 >--------------------------------------------------------------- commit 9926c4aae23dc11afb018175a15e505da4e73e73 Author: oconnorr Date: Mon Jun 10 15:22:54 2013 -0700 Make getTimeZone cross-platform consistent by always considering the TZ environment variable. Ignore-this: 98f02c84c56cc5f77aa96e3f9d9e90fc The current behaviour of getTimeZone is system dependent. On Linux, using glibc we get the following result: $ ghc -package time-1.4 -e 'System.Posix.Env.putEnv "TZ=EST5EDT" >> Data.Time.getCurrentTimeZone >>= print >> System.Posix.Env.putEnv "TZ=PST8PDT" >> Data.Time.getCurrentTimeZone >>= print' EDT EDT Under MacOS X we get a different result $ ghc -package time-1.4 -e 'System.Posix.Env.putEnv "TZ=EST5EDT" >> Data.Time.getCurrentTimeZone >>= print >> System.Posix.Env.putEnv "TZ=PST8PDT" >> Data.Time.getCurrentTimeZone >>= print' EDT PDT The underlying problem is that POSIX does not fully specify the behaviour of localtime_r, upon which getTimeZone relies. POSIX.1-2008 says: Unlike localtime(), the localtime_r() function is not required to set tzname. "not required" means that localtime_r may or may not set tzname. MacOS X's behaviour sets tzname on every call to localtime_r. On the other hand, Linux, using glibc, the behaviour of localtime_r is outstandingly complicated. Upon the first call to localtime_r (or more techincially upon the first call to tzset_internal) it will set tzname based upon the value in the TZ environment variable, but upon subsequent calls, localtime_r will *not* set the tzname. This leads to the bizzare behaviour under Linux whereby the value used by getTimeZone (and getCurrentTimeZone) will always use the value of the TZ environment variable during the first call, and it is impossible to change it again. The only workaround available to a Haskell programer is to call tzset, which is can only be found in another package. This patch calls tzset() before each call to localtime_r() which forces tzname to be set from the TZ enviroment call. The result is that on all platforms one gets the sane result of $ ghc -package time-1.4.1 -e 'System.Posix.Env.putEnv "TZ=EST5EDT" >> Data.Time.getCurrentTimeZone >>= print >> System.Posix.Env.putEnv "TZ=PST8PDT" >> Data.Time.getCurrentTimeZone >>= print' EDT PDT darcs-hash:20130610222254-a4c94-e18c93b079fcee2becc635ed32a2ce3c34f9276e >--------------------------------------------------------------- 9926c4aae23dc11afb018175a15e505da4e73e73 cbits/HsTime.c | 1 + time.cabal | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/cbits/HsTime.c b/cbits/HsTime.c index dacb1d4..e8a1155 100644 --- a/cbits/HsTime.c +++ b/cbits/HsTime.c @@ -5,6 +5,7 @@ long int get_current_timezone_seconds (time_t t,int* pdst,char const* * pname) { #if HAVE_LOCALTIME_R struct tm tmd; + tzset(); struct tm* ptm = localtime_r(&t,&tmd); #else struct tm* ptm = localtime(&t); diff --git a/time.cabal b/time.cabal index 873a06a..5e38d2a 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.4.0.2 +version: 1.4.1 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 23:01:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:23 +0000 (UTC) Subject: [commit: packages/time] master: Regression test for getTimeZone. (27173fc) Message-ID: <20150123230123.788543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/27173fcefbcaf8d699a3929585758597191ca313 >--------------------------------------------------------------- commit 27173fcefbcaf8d699a3929585758597191ca313 Author: oconnorr Date: Fri Jun 14 12:19:45 2013 -0700 Regression test for getTimeZone. Ignore-this: e113a43c80f89126aa12b2fdcd73ae9f The localtime_r call made from getTimeZone may or may not perform a tzset(). In particular, in glibc, a tzset() will only be performed the first time a process runs localtime_r. This added regression test will fail on implementations like glibc that only perform a tzset() on the first call to localtime_r. A fix to make getTimeZone always call tzset() can be found in patch: [Make getTimeZone cross-platform consistent by always considering the TZ environment variable. oconnorr at google.com**20130610222254 darcs-hash:20130614191945-a4c94-8b89e390a71d3b46bf56997ad103bec7a5144f13 >--------------------------------------------------------------- 27173fcefbcaf8d699a3929585758597191ca313 Test/TestTimeZone.hs | 17 +++++++++++++++++ Test/Tests.hs | 4 +++- time.cabal | 5 +++-- 3 files changed, 23 insertions(+), 3 deletions(-) diff --git a/Test/TestTimeZone.hs b/Test/TestTimeZone.hs new file mode 100644 index 0000000..8e79baa --- /dev/null +++ b/Test/TestTimeZone.hs @@ -0,0 +1,17 @@ +{-# OPTIONS -Wall -Werror #-} + +module Test.TestTimeZone where + +import Data.Time +import System.Posix.Env (putEnv) +import Test.TestUtil + +testTimeZone :: Test +testTimeZone = ioTest "getTimeZone respects TZ env var" $ do + putEnv "TZ=UTC+0" + zone1 <- getTimeZone epoch + putEnv "TZ=EST+5" + zone2 <- getTimeZone epoch + return $ diff False (zone1 == zone2) + where + epoch = UTCTime (ModifiedJulianDay 0) 0 diff --git a/Test/Tests.hs b/Test/Tests.hs index 512b64e..3900e45 100644 --- a/Test/Tests.hs +++ b/Test/Tests.hs @@ -13,6 +13,7 @@ import Test.TestMonthDay import Test.TestParseDAT import Test.TestParseTime import Test.TestTime +import Test.TestTimeZone tests :: [Test] tests = [ addDaysTest @@ -25,4 +26,5 @@ tests = [ addDaysTest , testMonthDay , testParseDAT , testParseTime - , testTime ] + , testTime + , testTimeZone ] diff --git a/time.cabal b/time.cabal index 5e38d2a..e1f7d79 100644 --- a/time.cabal +++ b/time.cabal @@ -114,8 +114,9 @@ test-suite tests old-locale, process, QuickCheck >= 2.5.1, - test-framework >= 0.6.1, - test-framework-quickcheck2 >= 0.2.12 + test-framework >= 0.6.1 && < 0.7, + test-framework-quickcheck2 >= 0.2.12, + unix main-is: Test.hs other-modules: Test.Tests From git at git.haskell.org Fri Jan 23 23:01:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:25 +0000 (UTC) Subject: [commit: packages/time] master: detabify cbits (a4fbbed) Message-ID: <20150123230125.7EC5C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/a4fbbedf1bb8190ed6ac57b0fc89750b581be31a >--------------------------------------------------------------- commit a4fbbedf1bb8190ed6ac57b0fc89750b581be31a Author: Ashley Yakeley Date: Sun Jun 23 17:35:10 2013 -0700 detabify cbits Ignore-this: bc6e127a254ec4e39b03ad5d601ee014 darcs-hash:20130624003510-ac6dd-f1537ad91adc4bd50fc1b222d6af0311ccde7a06 >--------------------------------------------------------------- a4fbbedf1bb8190ed6ac57b0fc89750b581be31a cbits/HsTime.c | 42 +++++++++++++++++++++--------------------- 1 file changed, 21 insertions(+), 21 deletions(-) diff --git a/cbits/HsTime.c b/cbits/HsTime.c index e8a1155..cfafb27 100644 --- a/cbits/HsTime.c +++ b/cbits/HsTime.c @@ -4,38 +4,38 @@ long int get_current_timezone_seconds (time_t t,int* pdst,char const* * pname) { #if HAVE_LOCALTIME_R - struct tm tmd; - tzset(); - struct tm* ptm = localtime_r(&t,&tmd); + struct tm tmd; + tzset(); + struct tm* ptm = localtime_r(&t,&tmd); #else - struct tm* ptm = localtime(&t); + struct tm* ptm = localtime(&t); #endif - if (ptm) - { - int dst = ptm -> tm_isdst; - *pdst = dst; + if (ptm) + { + int dst = ptm -> tm_isdst; + *pdst = dst; #if HAVE_TM_ZONE - *pname = ptm -> tm_zone; - return ptm -> tm_gmtoff; + *pname = ptm -> tm_zone; + return ptm -> tm_gmtoff; #elif defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32) - // We don't have a better API to use on Windows, the logic to - // decide whether a given date/time falls within DST is - // implemented as part of localtime() in the CRT. This is_dst - // flag is all we need here. - *pname = dst ? _tzname[1] : _tzname[0]; - return - (dst ? _timezone - 3600 : _timezone); + // We don't have a better API to use on Windows, the logic to + // decide whether a given date/time falls within DST is + // implemented as part of localtime() in the CRT. This is_dst + // flag is all we need here. + *pname = dst ? _tzname[1] : _tzname[0]; + return - (dst ? _timezone - 3600 : _timezone); #else # if HAVE_TZNAME - *pname = *tzname; + *pname = *tzname; # else # error "Don't know how to get timezone name on your OS" # endif # if HAVE_DECL_ALTZONE - return dst ? altzone : timezone; + return dst ? altzone : timezone; # else - return dst ? timezone - 3600 : timezone; + return dst ? timezone - 3600 : timezone; # endif #endif // HAVE_TM_ZONE - } - else return 0x80000000; + } + else return 0x80000000; } From git at git.haskell.org Fri Jan 23 23:01:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:27 +0000 (UTC) Subject: [commit: packages/time] master: Changes for Safe Haskell (7cc0d01) Message-ID: <20150123230127.874B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/7cc0d011e7a956c62d1c6a5d83b302cb938693e4 >--------------------------------------------------------------- commit 7cc0d011e7a956c62d1c6a5d83b302cb938693e4 Author: omari Date: Thu Feb 13 15:24:36 2014 -0800 Changes for Safe Haskell Ignore-this: c7c8f97541bd4ab2620613c51fad3b91 Makes minimal necessary changes so that modules will infer as Safe for Safe Haskell. Some modules are using rewrite rules, which are not Safe; to these I added Trustworthy pragmas. The rewrite rules will continue to fire as normal, according to GHC's documentation. Other modules import Foreign. I changed these to import Foreign.Safe instead. I changed the time.cabal file so that the minimum version of Base is 4.4; that was the first version of Base that has the Foreign.Safe module. (base 4.4 came with GHC 7.2, which is over two years old.) darcs-hash:20140213232436-6ee4c-27c941c537e6ab258befe3e38b9d9266334e9421 >--------------------------------------------------------------- 7cc0d011e7a956c62d1c6a5d83b302cb938693e4 Data/Time/Clock/CTimeval.hs | 2 +- Data/Time/Clock/Scale.hs | 1 + Data/Time/Clock/UTC.hs | 1 + Data/Time/LocalTime/TimeZone.hs | 2 +- time.cabal | 2 +- 5 files changed, 5 insertions(+), 3 deletions(-) diff --git a/Data/Time/Clock/CTimeval.hs b/Data/Time/Clock/CTimeval.hs index b0d8920..c8a692a 100644 --- a/Data/Time/Clock/CTimeval.hs +++ b/Data/Time/Clock/CTimeval.hs @@ -4,7 +4,7 @@ module Data.Time.Clock.CTimeval where #ifndef mingw32_HOST_OS -- All Unix-specific, this -import Foreign +import Foreign.Safe import Foreign.C data CTimeval = MkCTimeval CLong CLong diff --git a/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs index 9e91795..8ba7759 100644 --- a/Data/Time/Clock/Scale.hs +++ b/Data/Time/Clock/Scale.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Trustworthy #-} {-# OPTIONS -fno-warn-unused-imports #-} #include "HsConfigure.h" -- #hide diff --git a/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs index 3ba3309..d41b8f8 100644 --- a/Data/Time/Clock/UTC.hs +++ b/Data/Time/Clock/UTC.hs @@ -1,4 +1,5 @@ {-# OPTIONS -fno-warn-unused-imports #-} +{-# LANGUAGE Trustworthy #-} #include "HsConfigure.h" -- #hide module Data.Time.Clock.UTC diff --git a/Data/Time/LocalTime/TimeZone.hs b/Data/Time/LocalTime/TimeZone.hs index fa70026..e9e4f5f 100644 --- a/Data/Time/LocalTime/TimeZone.hs +++ b/Data/Time/LocalTime/TimeZone.hs @@ -17,7 +17,7 @@ import Data.Time.Calendar.Private import Data.Time.Clock import Data.Time.Clock.POSIX -import Foreign +import Foreign.Safe import Foreign.C import Control.DeepSeq import Data.Typeable diff --git a/time.cabal b/time.cabal index e1f7d79..334fa08 100644 --- a/time.cabal +++ b/time.cabal @@ -36,7 +36,7 @@ source-repository head library build-depends: - base >= 4 && < 5, + base >= 4.4 && < 5, deepseq >= 1.1, old-locale ghc-options: -Wall From git at git.haskell.org Fri Jan 23 23:01:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:29 +0000 (UTC) Subject: [commit: packages/time] master: version 1.4.2; improve Makefile (1e92867) Message-ID: <20150123230129.8DEF73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1e928677ff732d5355ef249faa4584caa2335bd9 >--------------------------------------------------------------- commit 1e928677ff732d5355ef249faa4584caa2335bd9 Author: Ashley Yakeley Date: Sun Mar 2 21:18:43 2014 -0800 version 1.4.2; improve Makefile Ignore-this: 9dcd1b4a4decdf6ea319f55849f97cbf darcs-hash:20140303051843-ac6dd-949729bef614ae9d022ba7a96419719ef92c2f0a >--------------------------------------------------------------- 1e928677ff732d5355ef249faa4584caa2335bd9 Makefile | 11 +++++++---- time.cabal | 2 +- 2 files changed, 8 insertions(+), 5 deletions(-) diff --git a/Makefile b/Makefile index 4fe6afb..73f55fd 100644 --- a/Makefile +++ b/Makefile @@ -1,4 +1,4 @@ -default: install +default: clean test install sdist # Building @@ -17,8 +17,11 @@ test: build haddock: configure cabal haddock -install: build test haddock - cabal install --user --enable-library-profiling --enable-executable-profiling +copy: build test haddock + cabal copy + +install: + cabal install --user --ghc-options=-Werror --enable-library-profiling --enable-executable-profiling sdist: clean configure cabal sdist @@ -26,4 +29,4 @@ sdist: clean configure # switch off intermediate file deletion .SECONDARY: -.PHONY: default clean configure build haddock install test sdist +.PHONY: default clean configure build haddock copy install test sdist diff --git a/time.cabal b/time.cabal index 334fa08..fad816c 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.4.1 +version: 1.4.2 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 23:01:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:31 +0000 (UTC) Subject: [commit: packages/time] master: tzset regardless of HAVE_LOCALTIME_R (a22e848) Message-ID: <20150123230131.945833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/a22e848dde29581cecb03a6cea70a73ee6a405cf >--------------------------------------------------------------- commit a22e848dde29581cecb03a6cea70a73ee6a405cf Author: Ashley Yakeley Date: Sat Jul 19 13:37:05 2014 -0700 tzset regardless of HAVE_LOCALTIME_R Ignore-this: a03b607f40ed91382348da78649d6f62 darcs-hash:20140719203705-ac6dd-dd66552eab0b730816f50cf4a30add39a633240b >--------------------------------------------------------------- a22e848dde29581cecb03a6cea70a73ee6a405cf cbits/HsTime.c | 2 +- time.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/cbits/HsTime.c b/cbits/HsTime.c index cfafb27..646fac6 100644 --- a/cbits/HsTime.c +++ b/cbits/HsTime.c @@ -3,9 +3,9 @@ long int get_current_timezone_seconds (time_t t,int* pdst,char const* * pname) { + tzset(); #if HAVE_LOCALTIME_R struct tm tmd; - tzset(); struct tm* ptm = localtime_r(&t,&tmd); #else struct tm* ptm = localtime(&t); diff --git a/time.cabal b/time.cabal index fad816c..b02f0e3 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.4.2 +version: 1.4.2.1 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 23:01:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:33 +0000 (UTC) Subject: [commit: packages/time] master: use latest test library (656b250) Message-ID: <20150123230133.9BFD33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/656b250ba24a60e15abb440ec302bd479270bae4 >--------------------------------------------------------------- commit 656b250ba24a60e15abb440ec302bd479270bae4 Author: Ashley Yakeley Date: Sat Jul 19 20:57:07 2014 -0700 use latest test library >--------------------------------------------------------------- 656b250ba24a60e15abb440ec302bd479270bae4 Test/TestUtil.hs | 3 ++- time.cabal | 4 ++-- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/Test/TestUtil.hs b/Test/TestUtil.hs index bb2b58e..b711f93 100644 --- a/Test/TestUtil.hs +++ b/Test/TestUtil.hs @@ -9,8 +9,9 @@ module Test.TestUtil import Test.Framework import Test.Framework.Providers.API import Test.Framework.Providers.QuickCheck2 +import Data.Typeable -data Result = Pass | Fail String +data Result = Pass | Fail String deriving Typeable instance Show Result where show Pass = "passed" diff --git a/time.cabal b/time.cabal index b02f0e3..34cdd78 100644 --- a/time.cabal +++ b/time.cabal @@ -114,8 +114,8 @@ test-suite tests old-locale, process, QuickCheck >= 2.5.1, - test-framework >= 0.6.1 && < 0.7, - test-framework-quickcheck2 >= 0.2.12, + test-framework >= 0.8, + test-framework-quickcheck2 >= 0.3, unix main-is: Test.hs other-modules: From git at git.haskell.org Fri Jan 23 23:01:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:35 +0000 (UTC) Subject: [commit: packages/time] master: .gitignore (08a0531) Message-ID: <20150123230135.A2ED83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/08a053130822da4933c8a289277a6dbd103e308b >--------------------------------------------------------------- commit 08a053130822da4933c8a289277a6dbd103e308b Author: Ashley Yakeley Date: Sat Jul 19 20:58:50 2014 -0700 .gitignore >--------------------------------------------------------------- 08a053130822da4933c8a289277a6dbd103e308b .darcs-boring | 70 ----------------------------------------------------------- .gitignore | 6 +++++ 2 files changed, 6 insertions(+), 70 deletions(-) diff --git a/.darcs-boring b/.darcs-boring deleted file mode 100644 index ca040f7..0000000 --- a/.darcs-boring +++ /dev/null @@ -1,70 +0,0 @@ -# Boring file regexps: -\.hi$ -\.o$ -\.p_hi$ -\.p_o$ -\.raw-hs$ -_split$ -\.a$ -(^|/)dist$ -(^|/)package.conf.inplace$ -(^|/)package.conf.installed$ -(^|/)\.depend$ -(^|/)\.setup-config$ -(^|/)\.installed-pkg-config$ -\.haddock$ -^build$ -\.xcodeproj/.*\.pbxuser$ -\.xcodeproj/.*\.mode1$ -\.o\.cmd$ -\.ko$ -\.ko\.cmd$ -\.mod\.c$ -(^|/)\.tmp_versions($|/) -(^|/)CVS($|/) -(^|/)RCS($|/) -~$ -#(^|/)\.[^/] -(^|/)_darcs($|/) -\.bak$ -\.BAK$ -\.orig$ -(^|/)vssver\.scc$ -\.swp$ -(^|/)MT($|/) -(^|/)\{arch\}($|/) -(^|/).arch-ids($|/) -(^|/), -\.class$ -\.prof$ -(^|/)\.DS_Store$ -(^|/)BitKeeper($|/) -(^|/)ChangeSet($|/) -(^|/)\.svn($|/) -\.py[co]$ -\# -\.cvsignore$ -^Private($|/) -(^|/)Thumbs\.db$ -^configure$ -^config\..*$ -^autom4te.cache($|/) -^include/HsTimeConfig\.h$ -^include/HsTimeConfig\.h.in$ -^test/.*\.out$ -^test/.*\.run$ -^test/AddDays$ -^test/ClipDates$ -^test/ConvertBack$ -^test/CurrentTime$ -^test/LongWeekYears$ -^test/ShowDST$ -^test/TestCalendars$ -^test/TestEaster$ -^test/TestFormat$ -^test/TestMonthDay$ -^test/TestParseDAT$ -^test/TestParseTime$ -^test/TestTime$ -^test/TimeZone$ -^test/TimeZone.ref$ diff --git a/.gitignore b/.gitignore new file mode 100644 index 0000000..dead619 --- /dev/null +++ b/.gitignore @@ -0,0 +1,6 @@ +dist/ +configure +autom4te.cache/ +config.* +include/HsTimeConfig.h +include/HsTimeConfig.h.in From git at git.haskell.org Fri Jan 23 23:01:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:37 +0000 (UTC) Subject: [commit: packages/time] master: time.cabal: note homepage and source-repository (dff2fcf) Message-ID: <20150123230137.A9BC23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/dff2fcfa89e87de2ea67b701ad2b6d3ad090aa3e >--------------------------------------------------------------- commit dff2fcfa89e87de2ea67b701ad2b6d3ad090aa3e Author: Ashley Yakeley Date: Sat Jul 19 21:54:57 2014 -0700 time.cabal: note homepage and source-repository >--------------------------------------------------------------- dff2fcfa89e87de2ea67b701ad2b6d3ad090aa3e time.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/time.cabal b/time.cabal index 34cdd78..1b71b00 100644 --- a/time.cabal +++ b/time.cabal @@ -5,7 +5,7 @@ license: BSD3 license-file: LICENSE author: Ashley Yakeley maintainer: -homepage: http://semantic.org/TimeLib/ +homepage: https://github.com/haskell/time synopsis: A time library description: A time library category: System @@ -31,8 +31,8 @@ extra-tmp-files: include/HsTimeConfig.h source-repository head - type: darcs - location: http://code.haskell.org/time/ + type: git + location: https://github.com/haskell/time library build-depends: From git at git.haskell.org Fri Jan 23 23:01:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:39 +0000 (UTC) Subject: [commit: packages/time] master: more parse tests (757c5c4) Message-ID: <20150123230139.B47843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/757c5c4e7293c01a2dee8e59b86bbccbe57c814b >--------------------------------------------------------------- commit 757c5c4e7293c01a2dee8e59b86bbccbe57c814b Author: Ashley Yakeley Date: Sun Jul 20 20:59:52 2014 -0700 more parse tests >--------------------------------------------------------------- 757c5c4e7293c01a2dee8e59b86bbccbe57c814b Test/TestParseTime.hs | 120 ++++++++++++++++++++++++++++++++------------------ 1 file changed, 76 insertions(+), 44 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 757c5c4e7293c01a2dee8e59b86bbccbe57c814b From git at git.haskell.org Fri Jan 23 23:01:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:41 +0000 (UTC) Subject: [commit: packages/time] master: Data.Time.Format.Parse re-exports System.Locale. Bump to 1.5 for this. (f1853e7) Message-ID: <20150123230141.BD1F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f1853e7ecb323df073606a028898fdfe0a5933e6 >--------------------------------------------------------------- commit f1853e7ecb323df073606a028898fdfe0a5933e6 Author: Ashley Yakeley Date: Sun Aug 10 02:46:16 2014 -0700 Data.Time.Format.Parse re-exports System.Locale. Bump to 1.5 for this. >--------------------------------------------------------------- f1853e7ecb323df073606a028898fdfe0a5933e6 Data/Time/Format.hs | 1 - Data/Time/Format/Parse.hs | 4 +++- Test/TestEaster.hs | 2 -- Test/TestFormat.hs | 1 - Test/TestParseTime.hs | 1 - time.cabal | 2 +- 6 files changed, 4 insertions(+), 7 deletions(-) diff --git a/Data/Time/Format.hs b/Data/Time/Format.hs index 21bce35..d071c30 100644 --- a/Data/Time/Format.hs +++ b/Data/Time/Format.hs @@ -14,7 +14,6 @@ import Data.Time.Calendar.Private import Data.Time.Clock import Data.Time.Clock.POSIX -import System.Locale import Data.Maybe import Data.Char import Data.Fixed diff --git a/Data/Time/Format/Parse.hs b/Data/Time/Format/Parse.hs index f9cc33d..c0569ee 100644 --- a/Data/Time/Format/Parse.hs +++ b/Data/Time/Format/Parse.hs @@ -8,7 +8,9 @@ module Data.Time.Format.Parse #if LANGUAGE_Rank2Types parseTime, readTime, readsTime, #endif - ParseTime(..) + ParseTime(..), + -- * Locale + module System.Locale ) where import Data.Time.Clock.POSIX diff --git a/Test/TestEaster.hs b/Test/TestEaster.hs index 20c8889..afba44c 100644 --- a/Test/TestEaster.hs +++ b/Test/TestEaster.hs @@ -6,8 +6,6 @@ import Data.Time.Calendar.Easter import Data.Time.Calendar import Data.Time.Format -import System.Locale - import Test.TestUtil import Test.TestEasterRef diff --git a/Test/TestFormat.hs b/Test/TestFormat.hs index fe5f375..68b8d2f 100644 --- a/Test/TestFormat.hs +++ b/Test/TestFormat.hs @@ -5,7 +5,6 @@ module Test.TestFormat where import Data.Time import Data.Time.Clock.POSIX import Data.Char -import System.Locale import Foreign import Foreign.C import Control.Exception; diff --git a/Test/TestParseTime.hs b/Test/TestParseTime.hs index 7ddf400..fcb7421 100644 --- a/Test/TestParseTime.hs +++ b/Test/TestParseTime.hs @@ -10,7 +10,6 @@ import Data.Time import Data.Time.Calendar.OrdinalDate import Data.Time.Calendar.WeekDate import Data.Time.Clock.POSIX -import System.Locale import Test.QuickCheck hiding (Result,reason) import Test.QuickCheck.Property hiding (result) import Test.TestUtil hiding (Result) diff --git a/time.cabal b/time.cabal index 1b71b00..d41b553 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.4.2.1 +version: 1.5 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Jan 23 23:01:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:43 +0000 (UTC) Subject: [commit: packages/time] master: .Format.Parse: add parseTimeM parseTimeOrError readSTime readPTime, deprecate parseTime readTime readsTime (1a633e6) Message-ID: <20150123230143.C66E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/1a633e6737ae45634619e2c9895c89848020bdec >--------------------------------------------------------------- commit 1a633e6737ae45634619e2c9895c89848020bdec Author: Ashley Yakeley Date: Sun Aug 10 03:19:27 2014 -0700 .Format.Parse: add parseTimeM parseTimeOrError readSTime readPTime, deprecate parseTime readTime readsTime >--------------------------------------------------------------- 1a633e6737ae45634619e2c9895c89848020bdec Data/Time/Format/Parse.hs | 95 +++++++++++++++++++++++++++++++++++------------ Test/TestFormat.hs | 10 ++--- Test/TestParseTime.hs | 89 +++++++++++++++++++++++++++++++------------- 3 files changed, 140 insertions(+), 54 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1a633e6737ae45634619e2c9895c89848020bdec From git at git.haskell.org Fri Jan 23 23:01:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:45 +0000 (UTC) Subject: [commit: packages/time] master: clean up source (50ddcf7) Message-ID: <20150123230145.CCE463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/50ddcf77f6ab8d6464e64422c0ac563c2b600423 >--------------------------------------------------------------- commit 50ddcf77f6ab8d6464e64422c0ac563c2b600423 Author: Ashley Yakeley Date: Sun Aug 17 19:21:51 2014 -0700 clean up source >--------------------------------------------------------------- 50ddcf77f6ab8d6464e64422c0ac563c2b600423 Data/Time/Format/Parse.hs | 0 Test/TestFormat.hs | 0 Test/TestParseTime.hs | 0 3 files changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Fri Jan 23 23:01:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:47 +0000 (UTC) Subject: [commit: packages/time] master: TestParseTime: more tests (c732e4d) Message-ID: <20150123230147.D81393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/c732e4d16d58ec1de790dc60afd7475c96641d89 >--------------------------------------------------------------- commit c732e4d16d58ec1de790dc60afd7475c96641d89 Author: Ashley Yakeley Date: Sun Aug 17 19:39:51 2014 -0700 TestParseTime: more tests >--------------------------------------------------------------- c732e4d16d58ec1de790dc60afd7475c96641d89 Test/TestParseTime.hs | 36 ++++++++++++++++++++++++------------ 1 file changed, 24 insertions(+), 12 deletions(-) diff --git a/Test/TestParseTime.hs b/Test/TestParseTime.hs index e53a016..97acfb6 100644 --- a/Test/TestParseTime.hs +++ b/Test/TestParseTime.hs @@ -63,25 +63,37 @@ readTest expected target = let name = show target in pureTest name result +readTestsParensSpaces :: forall a. (Eq a,Show a,Read a) => a -> String -> Test +readTestsParensSpaces expected target = testGroup target + [ + readTest [(expected,"")] $ target, + readTest [(expected,"")] $ "("++target++")", + readTest [(expected,"")] $ " ("++target++")", + readTest [(expected," ")] $ " ( "++target++" ) ", + readTest [(expected," ")] $ " (( "++target++" )) ", + readTest ([] :: [(a,String)]) $ "("++target, + readTest [(expected,")")] $ ""++target++")", + readTest [(expected,"")] $ "(("++target++"))", + readTest [(expected," ")] $ " ( ( "++target++" ) ) " + ] where + readOtherTypesTest :: Test readOtherTypesTest = testGroup "read other types" [ - readTest [(3,"")] "3", - readTest [(3,"")] "(3)", - readTest [(3,"")] " (3)", - readTest [(3," ")] " ( 3 ) ", - readTest [(3," ")] " (( 3 )) ", - readTest [("a","")] "(\"a\")", - readTest ([] :: [(String,String)]) "(\"a\"", - readTest [("a",")")] "\"a\")", - readTest [("a","")] "((\"a\"))", - readTest [("a"," ")] " ( ( \"a\" ) ) " - ] where + readTestsParensSpaces 3 "3", + readTestsParensSpaces "a" "\"a\"" + ] readTests :: Test readTests = testGroup "read times" [ - ] + readTestsParensSpaces testDay "1912-07-08", + readTestsParensSpaces testDay "1912-7-8", + readTestsParensSpaces testTimeOfDay "08:04:02", + readTestsParensSpaces testTimeOfDay "8:4:2" + ] where + testDay = fromGregorian 1912 7 8 + testTimeOfDay = TimeOfDay 8 4 2 simpleFormatTests :: Test simpleFormatTests = testGroup "simple" From git at git.haskell.org Fri Jan 23 23:01:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:49 +0000 (UTC) Subject: [commit: packages/time] master: move lib/test sources to separate directories (ad32d01) Message-ID: <20150123230149.E5D153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ad32d011138e7147236b0299cb0c2efb327e1f9d >--------------------------------------------------------------- commit ad32d011138e7147236b0299cb0c2efb327e1f9d Author: Ashley Yakeley Date: Sun Aug 17 20:00:05 2014 -0700 move lib/test sources to separate directories >--------------------------------------------------------------- ad32d011138e7147236b0299cb0c2efb327e1f9d Makefile | 2 +- {Data => lib/Data}/Time.hs | 0 {Data => lib/Data}/Time/Calendar.hs | 0 {Data => lib/Data}/Time/Calendar/Days.hs | 0 {Data => lib/Data}/Time/Calendar/Easter.hs | 0 {Data => lib/Data}/Time/Calendar/Gregorian.hs | 0 {Data => lib/Data}/Time/Calendar/Julian.hs | 0 {Data => lib/Data}/Time/Calendar/JulianYearDay.hs | 0 {Data => lib/Data}/Time/Calendar/MonthDay.hs | 0 {Data => lib/Data}/Time/Calendar/OrdinalDate.hs | 0 {Data => lib/Data}/Time/Calendar/Private.hs | 0 {Data => lib/Data}/Time/Calendar/WeekDate.hs | 0 {Data => lib/Data}/Time/Clock.hs | 0 {Data => lib/Data}/Time/Clock/CTimeval.hs | 0 {Data => lib/Data}/Time/Clock/POSIX.hs | 0 {Data => lib/Data}/Time/Clock/Scale.hs | 0 {Data => lib/Data}/Time/Clock/TAI.hs | 0 {Data => lib/Data}/Time/Clock/UTC.hs | 0 {Data => lib/Data}/Time/Clock/UTCDiff.hs | 0 {Data => lib/Data}/Time/Format.hs | 0 {Data => lib/Data}/Time/Format/Parse.hs | 0 {Data => lib/Data}/Time/LocalTime.hs | 0 {Data => lib/Data}/Time/LocalTime/LocalTime.hs | 0 {Data => lib/Data}/Time/LocalTime/TimeOfDay.hs | 0 {Data => lib/Data}/Time/LocalTime/TimeZone.hs | 0 Test.hs => test/Test.hs | 0 {Test => test/Test}/AddDays.hs | 0 {Test => test/Test}/AddDaysRef.hs | 0 {Test => test/Test}/ClipDates.hs | 0 {Test => test/Test}/ClipDatesRef.hs | 0 {Test => test/Test}/ConvertBack.hs | 0 {Test => test/Test}/CurrentTime.hs | 0 {Test => test/Test}/LongWeekYears.hs | 0 {Test => test/Test}/LongWeekYearsRef.hs | 0 {Test => test/Test}/RealToFracBenchmark.hs | 0 {Test => test/Test}/ShowDST.hs | 0 {Test => test/Test}/TAI_UTC_DAT.hs | 0 {Test => test/Test}/TestCalendars.hs | 0 {Test => test/Test}/TestCalendarsRef.hs | 0 {Test => test/Test}/TestEaster.hs | 0 {Test => test/Test}/TestEasterRef.hs | 0 {Test => test/Test}/TestFormat.hs | 0 {Test => test/Test}/TestFormatStuff.c | 0 {Test => test/Test}/TestFormatStuff.h | 0 {Test => test/Test}/TestMonthDay.hs | 0 {Test => test/Test}/TestMonthDayRef.hs | 0 {Test => test/Test}/TestParseDAT.hs | 0 {Test => test/Test}/TestParseDAT_Ref.hs | 0 {Test => test/Test}/TestParseTime.hs | 0 {Test => test/Test}/TestTime.hs | 0 {Test => test/Test}/TestTimeRef.hs | 0 {Test => test/Test}/TestTimeZone.hs | 0 {Test => test/Test}/TestUtil.hs | 0 {Test => test/Test}/Tests.hs | 0 {Test => test/Test}/TimeZone.hs | 0 {Test => test/Test}/UseCases.lhs | 0 time.cabal | 32 ++++------------------- 57 files changed, 6 insertions(+), 28 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ad32d011138e7147236b0299cb0c2efb327e1f9d From git at git.haskell.org Fri Jan 23 23:01:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:51 +0000 (UTC) Subject: [commit: packages/time] master: further file moves and .cabal fixes (0939180) Message-ID: <20150123230151.F1A0B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/093918017defa1bf5c56c6ca5f31c6bc03c52de5 >--------------------------------------------------------------- commit 093918017defa1bf5c56c6ca5f31c6bc03c52de5 Author: Ashley Yakeley Date: Sun Aug 17 20:09:24 2014 -0700 further file moves and .cabal fixes >--------------------------------------------------------------- 093918017defa1bf5c56c6ca5f31c6bc03c52de5 configure.ac | 4 +- {cbits => lib/cbits}/HsTime.c | 0 {include => lib/include}/HsConfigure.h | 0 {include => lib/include}/HsTime.h | 0 lib/include/HsTimeConfig.h | 87 ++++++++++++++++++++++++++++++++++ lib/include/HsTimeConfig.h.in | 86 +++++++++++++++++++++++++++++++++ lib/include/HsTimeConfig.h.in~ | 86 +++++++++++++++++++++++++++++++++ time.cabal | 23 ++++----- 8 files changed, 270 insertions(+), 16 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 093918017defa1bf5c56c6ca5f31c6bc03c52de5 From git at git.haskell.org Fri Jan 23 23:01:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:54 +0000 (UTC) Subject: [commit: packages/time] master: remove odd file (185cb99) Message-ID: <20150123230154.04F6F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/185cb993a5b2d0bda1d214d9d811ae68456440e6 >--------------------------------------------------------------- commit 185cb993a5b2d0bda1d214d9d811ae68456440e6 Author: Ashley Yakeley Date: Sun Aug 17 20:11:34 2014 -0700 remove odd file >--------------------------------------------------------------- 185cb993a5b2d0bda1d214d9d811ae68456440e6 lib/include/HsTimeConfig.h.in~ | 86 ------------------------------------------ 1 file changed, 86 deletions(-) diff --git a/lib/include/HsTimeConfig.h.in~ b/lib/include/HsTimeConfig.h.in~ deleted file mode 100644 index 618088e..0000000 --- a/lib/include/HsTimeConfig.h.in~ +++ /dev/null @@ -1,86 +0,0 @@ -/* include/HsTimeConfig.h.in. Generated from configure.ac by autoheader. */ - -/* Define to 1 if you have the declaration of `altzone', and to 0 if you - don't. */ -#undef HAVE_DECL_ALTZONE - -/* Define to 1 if you have the declaration of `tzname', and to 0 if you don't. - */ -#undef HAVE_DECL_TZNAME - -/* Define to 1 if you have the `gmtime_r' function. */ -#undef HAVE_GMTIME_R - -/* Define to 1 if you have the header file. */ -#undef HAVE_INTTYPES_H - -/* Define to 1 if you have the `localtime_r' function. */ -#undef HAVE_LOCALTIME_R - -/* Define to 1 if you have the header file. */ -#undef HAVE_MEMORY_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_STDINT_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_STDLIB_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_STRINGS_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_STRING_H - -/* Define to 1 if `tm_zone' is a member of `struct tm'. */ -#undef HAVE_STRUCT_TM_TM_ZONE - -/* Define to 1 if you have the header file. */ -#undef HAVE_SYS_STAT_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_SYS_TIME_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_SYS_TYPES_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_TIME_H - -/* Define to 1 if your `struct tm' has `tm_zone'. Deprecated, use - `HAVE_STRUCT_TM_TM_ZONE' instead. */ -#undef HAVE_TM_ZONE - -/* Define to 1 if you don't have `tm_zone' but do have the external array - `tzname'. */ -#undef HAVE_TZNAME - -/* Define to 1 if you have the header file. */ -#undef HAVE_UNISTD_H - -/* Define to the address where bug reports for this package should be sent. */ -#undef PACKAGE_BUGREPORT - -/* Define to the full name of this package. */ -#undef PACKAGE_NAME - -/* Define to the full name and version of this package. */ -#undef PACKAGE_STRING - -/* Define to the one symbol short name of this package. */ -#undef PACKAGE_TARNAME - -/* Define to the home page for this package. */ -#undef PACKAGE_URL - -/* Define to the version of this package. */ -#undef PACKAGE_VERSION - -/* Define to 1 if you have the ANSI C header files. */ -#undef STDC_HEADERS - -/* Define to 1 if you can safely include both and . */ -#undef TIME_WITH_SYS_TIME - -/* Define to 1 if your declares `struct tm'. */ -#undef TM_IN_SYS_TIME From git at git.haskell.org Fri Jan 23 23:01:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:56 +0000 (UTC) Subject: [commit: packages/time] master: Makefile: slight fix (077665f) Message-ID: <20150123230156.0BEED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/077665f054fb140b8e0ef8afbdf03eec1b627a30 >--------------------------------------------------------------- commit 077665f054fb140b8e0ef8afbdf03eec1b627a30 Author: Ashley Yakeley Date: Mon Aug 18 00:54:48 2014 -0700 Makefile: slight fix >--------------------------------------------------------------- 077665f054fb140b8e0ef8afbdf03eec1b627a30 Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Makefile b/Makefile index afe2b5b..7b37eb9 100644 --- a/Makefile +++ b/Makefile @@ -12,7 +12,7 @@ build: configure cabal build --ghc-options=-Werror test: configure - cabal test --test-option=--hide-successes --test-option=--color + cabal test --ghc-options=-Werror --test-option=--hide-successes --test-option=--color haddock: configure cabal haddock From git at git.haskell.org Fri Jan 23 23:01:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:01:58 +0000 (UTC) Subject: [commit: packages/time] master: .Format.Parse: be cleverer about skipping spaces (42afd39) Message-ID: <20150123230158.14E023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/42afd39fc919636b86c7b4764d0e610afce208ef >--------------------------------------------------------------- commit 42afd39fc919636b86c7b4764d0e610afce208ef Author: Ashley Yakeley Date: Mon Aug 18 01:48:59 2014 -0700 .Format.Parse: be cleverer about skipping spaces >--------------------------------------------------------------- 42afd39fc919636b86c7b4764d0e610afce208ef lib/Data/Time/Format/Parse.hs | 2 +- test/Test/TestParseTime.hs | 67 +++++++++++++++++++++++++++++-------------- 2 files changed, 47 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 42afd39fc919636b86c7b4764d0e610afce208ef From git at git.haskell.org Fri Jan 23 23:02:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:00 +0000 (UTC) Subject: [commit: packages/time] master: .Format.Parse: fix spaces parsing (f964074) Message-ID: <20150123230200.1C8613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f964074acda92566bc15e25f31bb5c752b17c002 >--------------------------------------------------------------- commit f964074acda92566bc15e25f31bb5c752b17c002 Author: Ashley Yakeley Date: Mon Aug 18 02:03:25 2014 -0700 .Format.Parse: fix spaces parsing >--------------------------------------------------------------- f964074acda92566bc15e25f31bb5c752b17c002 lib/Data/Time/Format/Parse.hs | 2 +- test/Test/TestParseTime.hs | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/lib/Data/Time/Format/Parse.hs b/lib/Data/Time/Format/Parse.hs index e750f9a..5b0b762 100644 --- a/lib/Data/Time/Format/Parse.hs +++ b/lib/Data/Time/Format/Parse.hs @@ -131,7 +131,7 @@ readPTime :: ParseTime t => -> String -- ^ Format string -> ReadP t readPTime False l f = readPOnlyTime l f -readPTime True l f = readPOnlyTime l f <++ (skipSpaces >> readPOnlyTime l f) +readPTime True l f = (skipSpaces >> readPOnlyTime l f) <++ readPOnlyTime l f -- | Parse a time value given a format string (without allowing leading whitespace). See 'parseTimeM' for details. readPOnlyTime :: ParseTime t => diff --git a/test/Test/TestParseTime.hs b/test/Test/TestParseTime.hs index 0fb9711..b0e9ef2 100644 --- a/test/Test/TestParseTime.hs +++ b/test/Test/TestParseTime.hs @@ -147,9 +147,13 @@ particularParseTests :: Test particularParseTests = testGroup "particular" [ spacingTests epoch "%Q" "", + spacingTests epoch "%Q" ".0", spacingTests epoch "%k" " 0", spacingTests epoch "%M" "00", - spacingTests (TimeZone 120 False "") "%Z" "+0200" + spacingTests epoch "%m" "01", + spacingTests (TimeZone 120 False "") "%z" "+0200", + spacingTests (TimeZone 120 False "") "%Z" "+0200", + spacingTests (TimeZone (-480) False "PST") "%Z" "PST" ] parseYMD :: Day -> Test From git at git.haskell.org Fri Jan 23 23:02:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:02 +0000 (UTC) Subject: [commit: packages/time] master: remove dependency on old-locale (907cbc2) Message-ID: <20150123230202.259943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/907cbc2c7c3fcecea255028fb895c3f5b144a6eb >--------------------------------------------------------------- commit 907cbc2c7c3fcecea255028fb895c3f5b144a6eb Author: Ashley Yakeley Date: Sat Aug 23 21:56:11 2014 -0700 remove dependency on old-locale >--------------------------------------------------------------- 907cbc2c7c3fcecea255028fb895c3f5b144a6eb lib/Data/Time/Format/Locale.hs | 78 ++++++++++++++++++++++++++++++++++++++++++ lib/Data/Time/Format/Parse.hs | 4 +-- lib/System/Locale.hs | 5 +++ time.cabal | 8 ++--- 4 files changed, 89 insertions(+), 6 deletions(-) diff --git a/lib/Data/Time/Format/Locale.hs b/lib/Data/Time/Format/Locale.hs new file mode 100644 index 0000000..11ec05a --- /dev/null +++ b/lib/Data/Time/Format/Locale.hs @@ -0,0 +1,78 @@ +-- Note: this file derives from old-locale:System.Locale.hs, which is copyright (c) The University of Glasgow 2001 + +module Data.Time.Format.Locale ( + + TimeLocale(..) + + , defaultTimeLocale + + , iso8601DateFormat + , rfc822DateFormat + ) +where + +import Prelude + +data TimeLocale = TimeLocale { + -- |full and abbreviated week days + wDays :: [(String, String)], + -- |full and abbreviated months + months :: [(String, String)], + intervals :: [(String, String)], + -- |AM\/PM symbols + amPm :: (String, String), + -- |formatting strings + dateTimeFmt, dateFmt, + timeFmt, time12Fmt :: String + } deriving (Eq, Ord, Show) + +defaultTimeLocale :: TimeLocale +defaultTimeLocale = TimeLocale { + wDays = [("Sunday", "Sun"), ("Monday", "Mon"), + ("Tuesday", "Tue"), ("Wednesday", "Wed"), + ("Thursday", "Thu"), ("Friday", "Fri"), + ("Saturday", "Sat")], + + months = [("January", "Jan"), ("February", "Feb"), + ("March", "Mar"), ("April", "Apr"), + ("May", "May"), ("June", "Jun"), + ("July", "Jul"), ("August", "Aug"), + ("September", "Sep"), ("October", "Oct"), + ("November", "Nov"), ("December", "Dec")], + + intervals = [ ("year","years") + , ("month", "months") + , ("day","days") + , ("hour","hours") + , ("min","mins") + , ("sec","secs") + , ("usec","usecs") + ], + + amPm = ("AM", "PM"), + dateTimeFmt = "%a %b %e %H:%M:%S %Z %Y", + dateFmt = "%m/%d/%y", + timeFmt = "%H:%M:%S", + time12Fmt = "%I:%M:%S %p" + } + + +{- | Construct format string according to . + +The @Maybe String@ argument allows to supply an optional time specification. E.g.: + +@ +'iso8601DateFormat' Nothing == "%Y-%m-%d" -- i.e. @/YYYY-MM-DD/@ +'iso8601DateFormat' (Just "%H:%M:%S") == "%Y-%m-%dT%H:%M:%S" -- i.e. @/YYYY-MM-DD/T/HH:MM:SS/@ +@ +-} + +iso8601DateFormat :: Maybe String -> String +iso8601DateFormat mTimeFmt = + "%Y-%m-%d" ++ case mTimeFmt of + Nothing -> "" + Just fmt -> 'T' : fmt + +-- | Format string according to . +rfc822DateFormat :: String +rfc822DateFormat = "%a, %_d %b %Y %H:%M:%S %Z" diff --git a/lib/Data/Time/Format/Parse.hs b/lib/Data/Time/Format/Parse.hs index 5b0b762..82c48df 100644 --- a/lib/Data/Time/Format/Parse.hs +++ b/lib/Data/Time/Format/Parse.hs @@ -11,7 +11,7 @@ module Data.Time.Format.Parse #endif ParseTime(..), -- * Locale - module System.Locale + module Data.Time.Format.Locale ) where import Data.Time.Clock.POSIX @@ -29,7 +29,7 @@ import Data.Fixed import Data.List import Data.Maybe import Data.Ratio -import System.Locale +import Data.Time.Format.Locale #if LANGUAGE_Rank2Types import Text.ParserCombinators.ReadP hiding (char, string) #endif diff --git a/lib/System/Locale.hs b/lib/System/Locale.hs new file mode 100644 index 0000000..88961cc --- /dev/null +++ b/lib/System/Locale.hs @@ -0,0 +1,5 @@ +module System.Locale +{-# DEPRECATED "Use Data.Time.Format instead" #-} +(module Data.Time.Format.Locale) +where +import Data.Time.Format.Locale diff --git a/time.cabal b/time.cabal index 881fd7d..23a388f 100644 --- a/time.cabal +++ b/time.cabal @@ -36,8 +36,7 @@ library hs-source-dirs: lib build-depends: base >= 4.4 && < 5, - deepseq >= 1.1, - old-locale + deepseq >= 1.1 ghc-options: -Wall default-language: Haskell2010 if impl(ghc) @@ -64,7 +63,8 @@ library Data.Time.Clock.TAI, Data.Time.LocalTime, Data.Time.Format, - Data.Time + Data.Time, + System.Locale default-extensions: CPP c-sources: lib/cbits/HsTime.c other-modules: @@ -80,6 +80,7 @@ library Data.Time.LocalTime.TimeOfDay, Data.Time.LocalTime.LocalTime, Data.Time.Format.Parse + Data.Time.Format.Locale include-dirs: lib/include if os(windows) install-includes: @@ -108,7 +109,6 @@ test-suite tests build-depends: base, deepseq, - old-locale, time == 1.5, QuickCheck >= 2.5.1, test-framework >= 0.8, From git at git.haskell.org Fri Jan 23 23:02:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:04 +0000 (UTC) Subject: [commit: packages/time] master: LICENSE: some code U. Glasgow (635917c) Message-ID: <20150123230204.2C97D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/635917c79260a6ddf890b2e2b5ff257bb029ff35 >--------------------------------------------------------------- commit 635917c79260a6ddf890b2e2b5ff257bb029ff35 Author: Ashley Yakeley Date: Sat Aug 23 22:10:18 2014 -0700 LICENSE: some code U. Glasgow >--------------------------------------------------------------- 635917c79260a6ddf890b2e2b5ff257bb029ff35 LICENSE | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/LICENSE b/LICENSE index 485d7f6..34a3712 100644 --- a/LICENSE +++ b/LICENSE @@ -1,5 +1,5 @@ -TimeLib is Copyright (c) Ashley Yakeley, 2004-2010. -All rights reserved. +TimeLib is Copyright (c) Ashley Yakeley, 2004-2014. All rights reserved. +Certain sections are Copyright 2004, The University Court of the University of Glasgow. All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: From git at git.haskell.org Fri Jan 23 23:02:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:06 +0000 (UTC) Subject: [commit: packages/time] master: remove System.Locale (e4ea1d9) Message-ID: <20150123230206.331783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e4ea1d9be7cb20339b1140937f2db01e5fe1d1a0 >--------------------------------------------------------------- commit e4ea1d9be7cb20339b1140937f2db01e5fe1d1a0 Author: Ashley Yakeley Date: Mon Aug 25 01:32:51 2014 -0700 remove System.Locale >--------------------------------------------------------------- e4ea1d9be7cb20339b1140937f2db01e5fe1d1a0 lib/System/Locale.hs | 5 ----- time.cabal | 3 +-- 2 files changed, 1 insertion(+), 7 deletions(-) diff --git a/lib/System/Locale.hs b/lib/System/Locale.hs deleted file mode 100644 index 88961cc..0000000 --- a/lib/System/Locale.hs +++ /dev/null @@ -1,5 +0,0 @@ -module System.Locale -{-# DEPRECATED "Use Data.Time.Format instead" #-} -(module Data.Time.Format.Locale) -where -import Data.Time.Format.Locale diff --git a/time.cabal b/time.cabal index 23a388f..383267f 100644 --- a/time.cabal +++ b/time.cabal @@ -63,8 +63,7 @@ library Data.Time.Clock.TAI, Data.Time.LocalTime, Data.Time.Format, - Data.Time, - System.Locale + Data.Time default-extensions: CPP c-sources: lib/cbits/HsTime.c other-modules: From git at git.haskell.org Fri Jan 23 23:02:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:08 +0000 (UTC) Subject: [commit: packages/time] master: allow user control of parsing of time-zone names (dc4157a) Message-ID: <20150123230208.3A22A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/dc4157a645c6a91803470a2e795008b680072586 >--------------------------------------------------------------- commit dc4157a645c6a91803470a2e795008b680072586 Author: Ashley Yakeley Date: Mon Aug 25 02:39:44 2014 -0700 allow user control of parsing of time-zone names >--------------------------------------------------------------- dc4157a645c6a91803470a2e795008b680072586 lib/Data/Time/Format/Locale.hs | 230 ++++++++++++++++++++++++++++++++++++++- lib/Data/Time/Format/Parse.hs | 238 +++-------------------------------------- 2 files changed, 241 insertions(+), 227 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dc4157a645c6a91803470a2e795008b680072586 From git at git.haskell.org Fri Jan 23 23:02:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:10 +0000 (UTC) Subject: [commit: packages/time] master: parse single-letter "military" time zones; test parsing of all defaultLocale time zones. Test failure: "EAST" is there twice. (2e0c3f8) Message-ID: <20150123230210.417733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2e0c3f84f91a22e6c7cf9ee77d3f823a3aeb9355 >--------------------------------------------------------------- commit 2e0c3f84f91a22e6c7cf9ee77d3f823a3aeb9355 Author: Ashley Yakeley Date: Mon Sep 1 20:34:22 2014 -0700 parse single-letter "military" time zones; test parsing of all defaultLocale time zones. Test failure: "EAST" is there twice. >--------------------------------------------------------------- 2e0c3f84f91a22e6c7cf9ee77d3f823a3aeb9355 lib/Data/Time/Format/Locale.hs | 2 -- lib/Data/Time/Format/Parse.hs | 16 +++++++++++++++- test/ShowDefaultTZAbbreviations.hs | 9 +++++++++ test/Test/TestParseTime.hs | 32 ++++++++++++++++++++++++++++++++ time.cabal | 8 ++++++++ 5 files changed, 64 insertions(+), 3 deletions(-) diff --git a/lib/Data/Time/Format/Locale.hs b/lib/Data/Time/Format/Locale.hs index 3708b8e..399cb25 100644 --- a/lib/Data/Time/Format/Locale.hs +++ b/lib/Data/Time/Format/Locale.hs @@ -210,8 +210,6 @@ _TIMEZONES_ = -- Universal Coordinated Time ,("UTC", (readTzOffset "+00:00", False)) -- Same as UTC - ,("Z", (readTzOffset "+00:00", False)) - -- Same as UTC ,("ZULU", (readTzOffset "+00:00", False)) -- Western European Time ,("WET", (readTzOffset "+00:00", False)) diff --git a/lib/Data/Time/Format/Parse.hs b/lib/Data/Time/Format/Parse.hs index 0064dda..07dc5b2 100644 --- a/lib/Data/Time/Format/Parse.hs +++ b/lib/Data/Time/Format/Parse.hs @@ -410,6 +410,18 @@ mkPico i f = fromInteger i + fromRational (f % 1000000000000) instance ParseTime LocalTime where buildTime l xs = LocalTime (buildTime l xs) (buildTime l xs) +enumDiff :: (Enum a) => a -> a -> Int +enumDiff a b = (fromEnum a) - (fromEnum b) + +getMilZoneHours :: Char -> Maybe Int +getMilZoneHours c | c < 'A' = Nothing +getMilZoneHours c | c <= 'I' = Just $ 1 + enumDiff c 'A' +getMilZoneHours 'J' = Nothing +getMilZoneHours c | c <= 'M' = Just $ 10 + enumDiff c 'K' +getMilZoneHours c | c <= 'Y' = Just $ (enumDiff 'N' c) - 1 +getMilZoneHours 'Z' = Just 0 +getMilZoneHours _ = Nothing + instance ParseTime TimeZone where buildTime l = foldl f (minutesToTimeZone 0) where @@ -420,7 +432,9 @@ instance ParseTime TimeZone where | isAlpha (head x) -> let y = up x in case find (\tz -> y == timeZoneName tz) (knownTimeZones l) of Just tz -> tz - Nothing -> TimeZone offset dst y + Nothing -> case y of + [yc] | Just hours <- getMilZoneHours yc -> TimeZone (hours * 60) False y + _ -> TimeZone offset dst y | otherwise -> zone _ -> t where zone = TimeZone (readTzOffset x) dst name diff --git a/test/ShowDefaultTZAbbreviations.hs b/test/ShowDefaultTZAbbreviations.hs new file mode 100644 index 0000000..fc24783 --- /dev/null +++ b/test/ShowDefaultTZAbbreviations.hs @@ -0,0 +1,9 @@ +module Main where + +import Data.Time + +showTZ :: TimeZone -> String +showTZ tz = (formatTime defaultTimeLocale "%Z %z " tz) ++ show (timeZoneSummerOnly tz) + +main :: IO () +main = mapM_ (\tz -> putStrLn (showTZ tz)) (knownTimeZones defaultTimeLocale) diff --git a/test/Test/TestParseTime.hs b/test/Test/TestParseTime.hs index b0e9ef2..26ee67d 100644 --- a/test/Test/TestParseTime.hs +++ b/test/Test/TestParseTime.hs @@ -27,6 +27,9 @@ testParseTime = testGroup "testParseTime" simpleFormatTests, extests, particularParseTests, + badParseTests, + defaultTimeZoneTests, + militaryTimeZoneTests, testGroup "properties" (fmap (\(n,prop) -> testProperty n prop) properties) ] @@ -156,6 +159,12 @@ particularParseTests = testGroup "particular" spacingTests (TimeZone (-480) False "PST") "%Z" "PST" ] +badParseTests :: Test +badParseTests = testGroup "bad" + [ + parseTest False (Nothing :: Maybe Day) "%Y" "" + ] + parseYMD :: Day -> Test parseYMD day = case toGregorian day of (y,m,d) -> parseTest False (Just day) "%Y%m%d" ((show y) ++ (show2 m) ++ (show2 d)) @@ -200,6 +209,29 @@ readsTest :: forall t. (Show t, Eq t, ParseTime t) => Maybe t -> String -> Strin readsTest (Just e) = readsTest' [(e,"")] readsTest Nothing = readsTest' ([] :: [(t,String)]) -} + +enumAdd :: (Enum a) => Int -> a -> a +enumAdd i a = toEnum (i + fromEnum a) + +getMilZoneLetter :: Int -> Char +getMilZoneLetter 0 = 'Z' +getMilZoneLetter h | h < 0 = enumAdd (negate h) 'M' +getMilZoneLetter h | h < 10 = enumAdd (h - 1) 'A' +getMilZoneLetter h = enumAdd (h - 10) 'K' + +getMilZone :: Int -> TimeZone +getMilZone hour = TimeZone (hour * 60) False [getMilZoneLetter hour] + +testParseTimeZone :: TimeZone -> Test +testParseTimeZone tz = parseTest False (Just tz) "%Z" (timeZoneName tz) + +defaultTimeZoneTests :: Test +defaultTimeZoneTests = testGroup "default time zones" (fmap testParseTimeZone (knownTimeZones defaultTimeLocale)) + +militaryTimeZoneTests :: Test +militaryTimeZoneTests = testGroup "military time zones" (fmap (testParseTimeZone . getMilZone) [-12 .. 12]) + + parse :: ParseTime t => Bool -> String -> String -> Maybe t parse sp f t = parseTimeM sp defaultTimeLocale f t diff --git a/time.cabal b/time.cabal index 383267f..b5c1638 100644 --- a/time.cabal +++ b/time.cabal @@ -89,6 +89,14 @@ library HsTime.h HsTimeConfig.h +test-suite ShowDefaultTZAbbreviations + hs-source-dirs: test + type: exitcode-stdio-1.0 + build-depends: + base, + time == 1.5 + main-is: ShowDefaultTZAbbreviations.hs + test-suite tests hs-source-dirs: test type: exitcode-stdio-1.0 From git at git.haskell.org Fri Jan 23 23:02:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:12 +0000 (UTC) Subject: [commit: packages/time] master: We're not in the time-zone business. defaultTimeLocale only has the time-zones mentioned in RFC 822. (f5ed156) Message-ID: <20150123230212.489F13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/f5ed15614b8950c1c31b031a50ce18755b652f0e >--------------------------------------------------------------- commit f5ed15614b8950c1c31b031a50ce18755b652f0e Author: Ashley Yakeley Date: Mon Sep 1 20:53:59 2014 -0700 We're not in the time-zone business. defaultTimeLocale only has the time-zones mentioned in RFC 822. >--------------------------------------------------------------- f5ed15614b8950c1c31b031a50ce18755b652f0e lib/Data/Time/Format/Locale.hs | 239 +++---------------------------------- test/ShowDefaultTZAbbreviations.hs | 2 +- 2 files changed, 19 insertions(+), 222 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f5ed15614b8950c1c31b031a50ce18755b652f0e From git at git.haskell.org Fri Jan 23 23:02:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:14 +0000 (UTC) Subject: [commit: packages/time] master: remove "intervals" from TimeLocale (2be4631) Message-ID: <20150123230214.4FAB93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2be46316b8ae4849fb38555c36722116b71edd74 >--------------------------------------------------------------- commit 2be46316b8ae4849fb38555c36722116b71edd74 Author: Ashley Yakeley Date: Mon Sep 1 21:22:44 2014 -0700 remove "intervals" from TimeLocale >--------------------------------------------------------------- 2be46316b8ae4849fb38555c36722116b71edd74 lib/Data/Time/Format/Locale.hs | 10 ---------- 1 file changed, 10 deletions(-) diff --git a/lib/Data/Time/Format/Locale.hs b/lib/Data/Time/Format/Locale.hs index e613fb9..ce0598a 100644 --- a/lib/Data/Time/Format/Locale.hs +++ b/lib/Data/Time/Format/Locale.hs @@ -18,7 +18,6 @@ data TimeLocale = TimeLocale { wDays :: [(String, String)], -- |full and abbreviated months months :: [(String, String)], - intervals :: [(String, String)], -- |AM\/PM symbols amPm :: (String, String), -- |formatting strings @@ -47,15 +46,6 @@ defaultTimeLocale = TimeLocale { ("September", "Sep"), ("October", "Oct"), ("November", "Nov"), ("December", "Dec")], - intervals = [ ("year","years") - , ("month", "months") - , ("day","days") - , ("hour","hours") - , ("min","mins") - , ("sec","secs") - , ("usec","usecs") - ], - amPm = ("AM", "PM"), dateTimeFmt = "%a %b %e %H:%M:%S %Z %Y", dateFmt = "%m/%d/%y", From git at git.haskell.org Fri Jan 23 23:02:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:16 +0000 (UTC) Subject: [commit: packages/time] master: doc quote cleanup (2a14cb0) Message-ID: <20150123230216.56E913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/2a14cb05a1685d6f8ddc3725f811cbfd48a34915 >--------------------------------------------------------------- commit 2a14cb05a1685d6f8ddc3725f811cbfd48a34915 Author: Ashley Yakeley Date: Sun Sep 7 20:26:16 2014 -0700 doc quote cleanup >--------------------------------------------------------------- 2a14cb05a1685d6f8ddc3725f811cbfd48a34915 lib/Data/Time/Format/Locale.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/Data/Time/Format/Locale.hs b/lib/Data/Time/Format/Locale.hs index ce0598a..2ce510f 100644 --- a/lib/Data/Time/Format/Locale.hs +++ b/lib/Data/Time/Format/Locale.hs @@ -30,7 +30,7 @@ data TimeLocale = TimeLocale { -- | Locale representing American usage. -- -- 'knownTimeZones' contains only the ten time-zones mentioned in RFC 822 sec. 5: --- "UT", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", "PDT". +-- \"UT\", \"GMT\", \"EST\", \"EDT\", \"CST\", \"CDT\", \"MST\", \"MDT\", \"PST\", \"PDT\". -- Note that the parsing functions will regardless parse single-letter military time-zones and +HHMM format. defaultTimeLocale :: TimeLocale defaultTimeLocale = TimeLocale { From git at git.haskell.org Fri Jan 23 23:02:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:18 +0000 (UTC) Subject: [commit: packages/time] master: Added bug-reports line to time.cabal (892717c) Message-ID: <20150123230218.5D6C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/892717c506ebbeadf8b9f1f8eecf5e145cfed47e >--------------------------------------------------------------- commit 892717c506ebbeadf8b9f1f8eecf5e145cfed47e Author: Ashley Yakeley Date: Sun Sep 7 23:13:08 2014 -0700 Added bug-reports line to time.cabal >--------------------------------------------------------------- 892717c506ebbeadf8b9f1f8eecf5e145cfed47e time.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/time.cabal b/time.cabal index b5c1638..068219a 100644 --- a/time.cabal +++ b/time.cabal @@ -6,6 +6,7 @@ license-file: LICENSE author: Ashley Yakeley maintainer: homepage: https://github.com/haskell/time +bug-reports: https://github.com/haskell/time/issues synopsis: A time library description: A time library category: System From git at git.haskell.org Fri Jan 23 23:02:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:20 +0000 (UTC) Subject: [commit: packages/time] master: Removed autogenerated HsTimeConfig.h* from repository, updated .gitignore. (82e0256) Message-ID: <20150123230220.641BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/82e0256223e94b21dbffb0dc60d196fc54cb41a4 >--------------------------------------------------------------- commit 82e0256223e94b21dbffb0dc60d196fc54cb41a4 Author: Gintautas Miliauskas Date: Sun Oct 12 02:29:04 2014 +0200 Removed autogenerated HsTimeConfig.h* from repository, updated .gitignore. >--------------------------------------------------------------- 82e0256223e94b21dbffb0dc60d196fc54cb41a4 .gitignore | 11 ++++-- lib/include/HsTimeConfig.h | 87 ------------------------------------------- lib/include/HsTimeConfig.h.in | 86 ------------------------------------------ 3 files changed, 7 insertions(+), 177 deletions(-) diff --git a/.gitignore b/.gitignore index dead619..5880242 100644 --- a/.gitignore +++ b/.gitignore @@ -1,6 +1,9 @@ -dist/ -configure +GNUmakefile autom4te.cache/ config.* -include/HsTimeConfig.h -include/HsTimeConfig.h.in +configure +dist/ +dist-install +ghc.mk +lib/include/HsTimeConfig.h +lib/include/HsTimeConfig.h.in diff --git a/lib/include/HsTimeConfig.h b/lib/include/HsTimeConfig.h deleted file mode 100644 index 769d94e..0000000 --- a/lib/include/HsTimeConfig.h +++ /dev/null @@ -1,87 +0,0 @@ -/* lib/include/HsTimeConfig.h. Generated from HsTimeConfig.h.in by configure. */ -/* lib/include/HsTimeConfig.h.in. Generated from configure.ac by autoheader. */ - -/* Define to 1 if you have the declaration of `altzone', and to 0 if you - don't. */ -#define HAVE_DECL_ALTZONE 0 - -/* Define to 1 if you have the declaration of `tzname', and to 0 if you don't. - */ -/* #undef HAVE_DECL_TZNAME */ - -/* Define to 1 if you have the `gmtime_r' function. */ -#define HAVE_GMTIME_R 1 - -/* Define to 1 if you have the header file. */ -#define HAVE_INTTYPES_H 1 - -/* Define to 1 if you have the `localtime_r' function. */ -#define HAVE_LOCALTIME_R 1 - -/* Define to 1 if you have the header file. */ -#define HAVE_MEMORY_H 1 - -/* Define to 1 if you have the header file. */ -#define HAVE_STDINT_H 1 - -/* Define to 1 if you have the header file. */ -#define HAVE_STDLIB_H 1 - -/* Define to 1 if you have the header file. */ -#define HAVE_STRINGS_H 1 - -/* Define to 1 if you have the header file. */ -#define HAVE_STRING_H 1 - -/* Define to 1 if `tm_zone' is a member of `struct tm'. */ -#define HAVE_STRUCT_TM_TM_ZONE 1 - -/* Define to 1 if you have the header file. */ -#define HAVE_SYS_STAT_H 1 - -/* Define to 1 if you have the header file. */ -#define HAVE_SYS_TIME_H 1 - -/* Define to 1 if you have the header file. */ -#define HAVE_SYS_TYPES_H 1 - -/* Define to 1 if you have the header file. */ -#define HAVE_TIME_H 1 - -/* Define to 1 if your `struct tm' has `tm_zone'. Deprecated, use - `HAVE_STRUCT_TM_TM_ZONE' instead. */ -#define HAVE_TM_ZONE 1 - -/* Define to 1 if you don't have `tm_zone' but do have the external array - `tzname'. */ -/* #undef HAVE_TZNAME */ - -/* Define to 1 if you have the header file. */ -#define HAVE_UNISTD_H 1 - -/* Define to the address where bug reports for this package should be sent. */ -#define PACKAGE_BUGREPORT "ashley at semantic.org" - -/* Define to the full name of this package. */ -#define PACKAGE_NAME "Haskell time package" - -/* Define to the full name and version of this package. */ -#define PACKAGE_STRING "Haskell time package 1.4.0.2" - -/* Define to the one symbol short name of this package. */ -#define PACKAGE_TARNAME "time" - -/* Define to the home page for this package. */ -#define PACKAGE_URL "" - -/* Define to the version of this package. */ -#define PACKAGE_VERSION "1.4.0.2" - -/* Define to 1 if you have the ANSI C header files. */ -#define STDC_HEADERS 1 - -/* Define to 1 if you can safely include both and . */ -#define TIME_WITH_SYS_TIME 1 - -/* Define to 1 if your declares `struct tm'. */ -/* #undef TM_IN_SYS_TIME */ diff --git a/lib/include/HsTimeConfig.h.in b/lib/include/HsTimeConfig.h.in deleted file mode 100644 index b6da5d3..0000000 --- a/lib/include/HsTimeConfig.h.in +++ /dev/null @@ -1,86 +0,0 @@ -/* lib/include/HsTimeConfig.h.in. Generated from configure.ac by autoheader. */ - -/* Define to 1 if you have the declaration of `altzone', and to 0 if you - don't. */ -#undef HAVE_DECL_ALTZONE - -/* Define to 1 if you have the declaration of `tzname', and to 0 if you don't. - */ -#undef HAVE_DECL_TZNAME - -/* Define to 1 if you have the `gmtime_r' function. */ -#undef HAVE_GMTIME_R - -/* Define to 1 if you have the header file. */ -#undef HAVE_INTTYPES_H - -/* Define to 1 if you have the `localtime_r' function. */ -#undef HAVE_LOCALTIME_R - -/* Define to 1 if you have the header file. */ -#undef HAVE_MEMORY_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_STDINT_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_STDLIB_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_STRINGS_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_STRING_H - -/* Define to 1 if `tm_zone' is a member of `struct tm'. */ -#undef HAVE_STRUCT_TM_TM_ZONE - -/* Define to 1 if you have the header file. */ -#undef HAVE_SYS_STAT_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_SYS_TIME_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_SYS_TYPES_H - -/* Define to 1 if you have the header file. */ -#undef HAVE_TIME_H - -/* Define to 1 if your `struct tm' has `tm_zone'. Deprecated, use - `HAVE_STRUCT_TM_TM_ZONE' instead. */ -#undef HAVE_TM_ZONE - -/* Define to 1 if you don't have `tm_zone' but do have the external array - `tzname'. */ -#undef HAVE_TZNAME - -/* Define to 1 if you have the header file. */ -#undef HAVE_UNISTD_H - -/* Define to the address where bug reports for this package should be sent. */ -#undef PACKAGE_BUGREPORT - -/* Define to the full name of this package. */ -#undef PACKAGE_NAME - -/* Define to the full name and version of this package. */ -#undef PACKAGE_STRING - -/* Define to the one symbol short name of this package. */ -#undef PACKAGE_TARNAME - -/* Define to the home page for this package. */ -#undef PACKAGE_URL - -/* Define to the version of this package. */ -#undef PACKAGE_VERSION - -/* Define to 1 if you have the ANSI C header files. */ -#undef STDC_HEADERS - -/* Define to 1 if you can safely include both and . */ -#undef TIME_WITH_SYS_TIME - -/* Define to 1 if your declares `struct tm'. */ -#undef TM_IN_SYS_TIME From git at git.haskell.org Fri Jan 23 23:02:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:22 +0000 (UTC) Subject: [commit: packages/time] master: Use `_tzset()` for non-POSIX Windows environments (9f12261) Message-ID: <20150123230222.6B2B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/9f12261f5e81f70a50f29f0a43d487070cfa1ab4 >--------------------------------------------------------------- commit 9f12261f5e81f70a50f29f0a43d487070cfa1ab4 Author: Herbert Valerio Riedel Date: Sun Oct 12 10:26:50 2014 +0200 Use `_tzset()` for non-POSIX Windows environments When compiling with MinGW (which does not provide a full POSIX layer as opposed to CygWin) it's better to use the CRT's underscore-prefixed `_tzset()` variant to avoid linker issues as Microsoft considers the POSIX named `tzset()` function deprecated Further reading - http://msdn.microsoft.com/en-us/library/ms235384.aspx - http://stackoverflow.com/questions/23477746/what-are-the-posix-like-functions-in-msvcs-c-runtime This hopefully addresses #2 >--------------------------------------------------------------- 9f12261f5e81f70a50f29f0a43d487070cfa1ab4 lib/cbits/HsTime.c | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/lib/cbits/HsTime.c b/lib/cbits/HsTime.c index 646fac6..e2be98a 100644 --- a/lib/cbits/HsTime.c +++ b/lib/cbits/HsTime.c @@ -3,7 +3,17 @@ long int get_current_timezone_seconds (time_t t,int* pdst,char const* * pname) { +#if defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32) + // When compiling with MinGW (which does not provide a full POSIX + // layer as opposed to CygWin) it's better to use the CRT's + // underscore-prefixed `_tzset()` variant to avoid linker issues + // as Microsoft considers the POSIX named `tzset()` function + // deprecated (see http://msdn.microsoft.com/en-us/library/ms235384.aspx) + _tzset(); +#else tzset(); +#endif + #if HAVE_LOCALTIME_R struct tm tmd; struct tm* ptm = localtime_r(&t,&tmd); From git at git.haskell.org Fri Jan 23 23:02:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:24 +0000 (UTC) Subject: [commit: packages/time] master: Merge pull request #4 from hvr/pr-tzset (7633c67) Message-ID: <20150123230224.72A8A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/7633c6731670fe757ccdf66ccd889e8e12ded56d >--------------------------------------------------------------- commit 7633c6731670fe757ccdf66ccd889e8e12ded56d Merge: 892717c 9f12261 Author: Ashley Yakeley Date: Sun Oct 12 22:18:16 2014 -0700 Merge pull request #4 from hvr/pr-tzset Use `_tzset()` for non-POSIX Windows environments >--------------------------------------------------------------- 7633c6731670fe757ccdf66ccd889e8e12ded56d lib/cbits/HsTime.c | 10 ++++++++++ 1 file changed, 10 insertions(+) From git at git.haskell.org Fri Jan 23 23:02:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:26 +0000 (UTC) Subject: [commit: packages/time] master: Merge pull request #3 from gintas/master (991e6be) Message-ID: <20150123230226.7923B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/991e6be84974b02d7f968601ab02d2e2b3e14190 >--------------------------------------------------------------- commit 991e6be84974b02d7f968601ab02d2e2b3e14190 Merge: 7633c67 82e0256 Author: Ashley Yakeley Date: Sun Oct 12 22:19:57 2014 -0700 Merge pull request #3 from gintas/master Removed autogenerated HsTimeConfig.h* from repository, updated .gitignore >--------------------------------------------------------------- 991e6be84974b02d7f968601ab02d2e2b3e14190 .gitignore | 11 ++++-- lib/include/HsTimeConfig.h | 87 ------------------------------------------- lib/include/HsTimeConfig.h.in | 86 ------------------------------------------ 3 files changed, 7 insertions(+), 177 deletions(-) From git at git.haskell.org Fri Jan 23 23:02:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:28 +0000 (UTC) Subject: [commit: packages/time] master: Add `Setup.hs` file (5511b80) Message-ID: <20150123230228.804C93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/5511b80a884ec945fabfa3ca7ae0107713e5000e >--------------------------------------------------------------- commit 5511b80a884ec945fabfa3ca7ae0107713e5000e Author: Herbert Valerio Riedel Date: Tue Oct 14 17:40:36 2014 +0200 Add `Setup.hs` file This adds a `Setup.hs` appropriate for `build-type: configure` and makes `cabal check` happy. >--------------------------------------------------------------- 5511b80a884ec945fabfa3ca7ae0107713e5000e Setup.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/Setup.hs b/Setup.hs new file mode 100644 index 0000000..54f57d6 --- /dev/null +++ b/Setup.hs @@ -0,0 +1,6 @@ +module Main (main) where + +import Distribution.Simple + +main :: IO () +main = defaultMainWithHooks autoconfUserHooks From git at git.haskell.org Fri Jan 23 23:02:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:30 +0000 (UTC) Subject: [commit: packages/time] master: Remove an extra division (52523fb) Message-ID: <20150123230230.8737F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/52523fbc2deebeb7137b76d66e68eea1c8c030c0 >--------------------------------------------------------------- commit 52523fbc2deebeb7137b76d66e68eea1c8c030c0 Author: treeowl Date: Fri Nov 7 00:14:37 2014 -0500 Remove an extra division Currently, GHC does not merge `div` with `mod` by itself; `divMod` saves time. Turn nested `if`s into `case`. >--------------------------------------------------------------- 52523fbc2deebeb7137b76d66e68eea1c8c030c0 lib/Data/Time/Calendar/WeekDate.hs | 19 +++++++++---------- 1 file changed, 9 insertions(+), 10 deletions(-) diff --git a/lib/Data/Time/Calendar/WeekDate.hs b/lib/Data/Time/Calendar/WeekDate.hs index 1c76977..c7046b4 100644 --- a/lib/Data/Time/Calendar/WeekDate.hs +++ b/lib/Data/Time/Calendar/WeekDate.hs @@ -9,20 +9,19 @@ import Data.Time.Calendar.Private -- Note that \"Week\" years are not quite the same as Gregorian years, as the first day of the year is always a Monday. -- The first week of a year is the first week to contain at least four days in the corresponding Gregorian year. toWeekDate :: Day -> (Integer,Int,Int) -toWeekDate date@(ModifiedJulianDay mjd) = (y1,fromInteger (w1 + 1),fromInteger (mod d 7) + 1) where +toWeekDate date@(ModifiedJulianDay mjd) = (y1,fromInteger (w1 + 1),fromInteger d_mod_7 + 1) where + (d_div_7, d_mod_7) = d `divMod` 7 (y0,yd) = toOrdinalDate date d = mjd + 2 foo :: Integer -> Integer foo y = bar (toModifiedJulianDay (fromOrdinalDate y 6)) - bar k = (div d 7) - (div k 7) - w0 = bar (d - (toInteger yd) + 4) - (y1,w1) = if w0 == -1 - then (y0 - 1,foo (y0 - 1)) - else if w0 == 52 - then if (foo (y0 + 1)) == 0 - then (y0 + 1,0) - else (y0,w0) - else (y0,w0) + bar k = d_div_7 - k `div` 7 + (y1,w1) = case bar (d - toInteger yd + 4) of + -1 -> (y0 - 1, foo (y0 - 1)) + 52 -> if foo (y0 + 1) == 0 + then (y0 + 1, 0) + else (y0, 52) + w0 -> (y0, w0) -- | convert from ISO 8601 Week Date format. First argument is year, second week number (1-52 or 53), third day of week (1 for Monday to 7 for Sunday). -- Invalid week and day values will be clipped to the correct range. From git at git.haskell.org Fri Jan 23 23:02:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:32 +0000 (UTC) Subject: [commit: packages/time] master: Merge pull request #10 from treeowl/master (b55b3c2) Message-ID: <20150123230232.8E1873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b55b3c260f042791d4c833d454cc576db9ddf574 >--------------------------------------------------------------- commit b55b3c260f042791d4c833d454cc576db9ddf574 Merge: 991e6be 52523fb Author: Ashley Yakeley Date: Fri Nov 7 02:14:54 2014 -0800 Merge pull request #10 from treeowl/master Remove an extra division >--------------------------------------------------------------- b55b3c260f042791d4c833d454cc576db9ddf574 lib/Data/Time/Calendar/WeekDate.hs | 19 +++++++++---------- 1 file changed, 9 insertions(+), 10 deletions(-) From git at git.haskell.org Fri Jan 23 23:02:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:34 +0000 (UTC) Subject: [commit: packages/time] master: Add support for `deepseq-1.4.0.0` (e6d887a) Message-ID: <20150123230234.93CDB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/e6d887a4eb63a9971ba86d84222e809f3c20373c >--------------------------------------------------------------- commit e6d887a4eb63a9971ba86d84222e809f3c20373c Author: Herbert Valerio Riedel Date: Fri Nov 14 18:19:36 2014 +0100 Add support for `deepseq-1.4.0.0` `deepseq-1.4.0.0`'s major change is the default `rnf` method implementation (see haskell/deepseq#1 for details). This commit changes `time` not to rely on the default implementation and instead explicitly make use of `seq` like the old default implementation did. >--------------------------------------------------------------- e6d887a4eb63a9971ba86d84222e809f3c20373c lib/Data/Time/Clock/Scale.hs | 3 ++- lib/Data/Time/Clock/UTC.hs | 3 ++- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/lib/Data/Time/Clock/Scale.hs b/lib/Data/Time/Clock/Scale.hs index 8ba7759..def28ce 100644 --- a/lib/Data/Time/Clock/Scale.hs +++ b/lib/Data/Time/Clock/Scale.hs @@ -50,7 +50,8 @@ newtype DiffTime = MkDiffTime Pico deriving (Eq,Ord ) -- necessary because H98 doesn't have "cunning newtype" derivation -instance NFData DiffTime -- FIXME: Data.Fixed had no NFData instances yet at time of writing +instance NFData DiffTime where -- FIXME: Data.Fixed had no NFData instances yet at time of writing + rnf dt = seq dt () -- necessary because H98 doesn't have "cunning newtype" derivation instance Enum DiffTime where diff --git a/lib/Data/Time/Clock/UTC.hs b/lib/Data/Time/Clock/UTC.hs index d41b8f8..4cb9447 100644 --- a/lib/Data/Time/Clock/UTC.hs +++ b/lib/Data/Time/Clock/UTC.hs @@ -70,7 +70,8 @@ newtype NominalDiffTime = MkNominalDiffTime Pico deriving (Eq,Ord ) -- necessary because H98 doesn't have "cunning newtype" derivation -instance NFData NominalDiffTime -- FIXME: Data.Fixed had no NFData instances yet at time of writing +instance NFData NominalDiffTime where -- FIXME: Data.Fixed had no NFData instances yet at time of writing + rnf ndt = seq ndt () instance Enum NominalDiffTime where succ (MkNominalDiffTime a) = MkNominalDiffTime (succ a) From git at git.haskell.org Fri Jan 23 23:02:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:36 +0000 (UTC) Subject: [commit: packages/time] master: Merge pull request #11 from hvr/pr-deepseq14 (982ea8f) Message-ID: <20150123230236.9B82B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/982ea8f68740a93399c78b0275d2a685d79c15cf >--------------------------------------------------------------- commit 982ea8f68740a93399c78b0275d2a685d79c15cf Merge: b55b3c2 e6d887a Author: Ashley Yakeley Date: Fri Nov 14 14:27:46 2014 -0800 Merge pull request #11 from hvr/pr-deepseq14 Add support for `deepseq-1.4.0.0` >--------------------------------------------------------------- 982ea8f68740a93399c78b0275d2a685d79c15cf lib/Data/Time/Clock/Scale.hs | 3 ++- lib/Data/Time/Clock/UTC.hs | 3 ++- 2 files changed, 4 insertions(+), 2 deletions(-) From git at git.haskell.org Fri Jan 23 23:02:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:38 +0000 (UTC) Subject: [commit: packages/time] master: Merge pull request #5 from hvr/pr-setuphs (ab6475c) Message-ID: <20150123230238.A3D403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ab6475cb94260f4303afbbd4b770cbd14ec2f57e >--------------------------------------------------------------- commit ab6475cb94260f4303afbbd4b770cbd14ec2f57e Merge: 982ea8f 5511b80 Author: Ashley Yakeley Date: Fri Nov 14 14:28:19 2014 -0800 Merge pull request #5 from hvr/pr-setuphs Add `Setup.hs` file >--------------------------------------------------------------- ab6475cb94260f4303afbbd4b770cbd14ec2f57e Setup.hs | 6 ++++++ 1 file changed, 6 insertions(+) From git at git.haskell.org Fri Jan 23 23:02:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:40 +0000 (UTC) Subject: [commit: packages/time] master: fix deprecation of base 4.8 (7513fad) Message-ID: <20150123230240.ACBC43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/7513fad1f1f7a4c48fa20582dfe407427484f367 >--------------------------------------------------------------- commit 7513fad1f1f7a4c48fa20582dfe407427484f367 Author: David Terei Date: Fri Nov 21 11:32:55 2014 -0800 fix deprecation of base 4.8 >--------------------------------------------------------------- 7513fad1f1f7a4c48fa20582dfe407427484f367 lib/Data/Time/Clock/CTimeval.hs | 4 ++++ lib/Data/Time/LocalTime/TimeZone.hs | 4 ++++ 2 files changed, 8 insertions(+) diff --git a/lib/Data/Time/Clock/CTimeval.hs b/lib/Data/Time/Clock/CTimeval.hs index c8a692a..012501a 100644 --- a/lib/Data/Time/Clock/CTimeval.hs +++ b/lib/Data/Time/Clock/CTimeval.hs @@ -4,7 +4,11 @@ module Data.Time.Clock.CTimeval where #ifndef mingw32_HOST_OS -- All Unix-specific, this +#if __GLASGOW_HASKELL__ >= 709 +import Foreign +#else import Foreign.Safe +#endif import Foreign.C data CTimeval = MkCTimeval CLong CLong diff --git a/lib/Data/Time/LocalTime/TimeZone.hs b/lib/Data/Time/LocalTime/TimeZone.hs index e9e4f5f..2efaebb 100644 --- a/lib/Data/Time/LocalTime/TimeZone.hs +++ b/lib/Data/Time/LocalTime/TimeZone.hs @@ -17,7 +17,11 @@ import Data.Time.Calendar.Private import Data.Time.Clock import Data.Time.Clock.POSIX +#if __GLASGOW_HASKELL__ >= 709 +import Foreign +#else import Foreign.Safe +#endif import Foreign.C import Control.DeepSeq import Data.Typeable From git at git.haskell.org Fri Jan 23 23:02:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:42 +0000 (UTC) Subject: [commit: packages/time] master: Merge pull request #12 from dterei/base48-foreign-fix (8c7c106) Message-ID: <20150123230242.B40B23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/8c7c106e890141b0452fefdc1bc03191a2f70893 >--------------------------------------------------------------- commit 8c7c106e890141b0452fefdc1bc03191a2f70893 Merge: ab6475c 7513fad Author: Ashley Yakeley Date: Fri Nov 21 12:54:26 2014 -0800 Merge pull request #12 from dterei/base48-foreign-fix Fix deprecation of Foreign.Safe in base 4.8 >--------------------------------------------------------------- 8c7c106e890141b0452fefdc1bc03191a2f70893 lib/Data/Time/Clock/CTimeval.hs | 4 ++++ lib/Data/Time/LocalTime/TimeZone.hs | 4 ++++ 2 files changed, 8 insertions(+) From git at git.haskell.org Fri Jan 23 23:02:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:44 +0000 (UTC) Subject: [commit: packages/time] master: Improve documentation of wdays in TimeLocale (9366adb) Message-ID: <20150123230244.BC3513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/9366adb2d12ff3ad4be7a40a160e231b5c650af7 >--------------------------------------------------------------- commit 9366adb2d12ff3ad4be7a40a160e231b5c650af7 Author: Lubom?r Sedl?? Date: Sat Dec 13 14:46:50 2014 +0100 Improve documentation of wdays in TimeLocale >--------------------------------------------------------------- 9366adb2d12ff3ad4be7a40a160e231b5c650af7 lib/Data/Time/Format/Locale.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/Data/Time/Format/Locale.hs b/lib/Data/Time/Format/Locale.hs index 2ce510f..80ead81 100644 --- a/lib/Data/Time/Format/Locale.hs +++ b/lib/Data/Time/Format/Locale.hs @@ -14,7 +14,7 @@ where import Data.Time.LocalTime data TimeLocale = TimeLocale { - -- |full and abbreviated week days + -- |full and abbreviated week days, starting with Sunday wDays :: [(String, String)], -- |full and abbreviated months months :: [(String, String)], From git at git.haskell.org Fri Jan 23 23:02:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:46 +0000 (UTC) Subject: [commit: packages/time] master: Merge pull request #14 from lubomir/document-locale (968ec05) Message-ID: <20150123230246.C21F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/968ec057a457c970a3b1bb6e5a612f392f29734e >--------------------------------------------------------------- commit 968ec057a457c970a3b1bb6e5a612f392f29734e Merge: 8c7c106 9366adb Author: Gregory Collins Date: Sat Dec 13 22:01:27 2014 +0100 Merge pull request #14 from lubomir/document-locale Improve documentation of wdays in TimeLocale >--------------------------------------------------------------- 968ec057a457c970a3b1bb6e5a612f392f29734e lib/Data/Time/Format/Locale.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 23:02:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:48 +0000 (UTC) Subject: [commit: packages/time] master: version 1.5.0.1 (8d3c90a) Message-ID: <20150123230248.CA4B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/8d3c90a420c8985dcc439766c028821cea7dc848 >--------------------------------------------------------------- commit 8d3c90a420c8985dcc439766c028821cea7dc848 Author: Ashley Yakeley Date: Sat Dec 13 14:32:01 2014 -0800 version 1.5.0.1 >--------------------------------------------------------------- 8d3c90a420c8985dcc439766c028821cea7dc848 time.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/time.cabal b/time.cabal index 068219a..c1a82be 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.5 +version: 1.5.0.1 stability: stable license: BSD3 license-file: LICENSE @@ -95,7 +95,7 @@ test-suite ShowDefaultTZAbbreviations type: exitcode-stdio-1.0 build-depends: base, - time == 1.5 + time == 1.5.0.1 main-is: ShowDefaultTZAbbreviations.hs test-suite tests @@ -117,7 +117,7 @@ test-suite tests build-depends: base, deepseq, - time == 1.5, + time == 1.5.0.1, QuickCheck >= 2.5.1, test-framework >= 0.8, test-framework-quickcheck2 >= 0.3, From git at git.haskell.org Fri Jan 23 23:02:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:50 +0000 (UTC) Subject: [commit: packages/time] master: Fix note about `%Y` padding. (a52561a) Message-ID: <20150123230250.D18743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/a52561acc09a942995f74bb8a0a2cd89f955c941 >--------------------------------------------------------------- commit a52561acc09a942995f74bb8a0a2cd89f955c941 Author: Bj?rn Buckwalter Date: Sun Dec 14 22:16:52 2014 +0100 Fix note about `%Y` padding. >--------------------------------------------------------------- a52561acc09a942995f74bb8a0a2cd89f955c941 lib/Data/Time/Format.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/Data/Time/Format.hs b/lib/Data/Time/Format.hs index d071c30..91dc93d 100644 --- a/lib/Data/Time/Format.hs +++ b/lib/Data/Time/Format.hs @@ -108,7 +108,7 @@ formatChar c locale mpado t = case (formatCharacter c) of -- -- [@%x@] as 'dateFmt' @locale@ (e.g. @%m\/%d\/%y@) -- --- [@%Y@] year, no padding. Note @%0y@ and @%_y@ pad to four chars +-- [@%Y@] year, no padding. Note @%0Y@ and @%_Y@ pad to four chars -- -- [@%y@] year of century, 0-padded to two chars, @00@ - @99@ -- From git at git.haskell.org Fri Jan 23 23:02:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:52 +0000 (UTC) Subject: [commit: packages/time] master: Merge pull request #17 from bjornbm/patch-1 (ba160e5) Message-ID: <20150123230252.E0AE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/ba160e582fc02a9d9b19b3235926c91cc390240f >--------------------------------------------------------------- commit ba160e582fc02a9d9b19b3235926c91cc390240f Merge: 8d3c90a a52561a Author: Ashley Yakeley Date: Sun Dec 14 13:47:10 2014 -0800 Merge pull request #17 from bjornbm/patch-1 Fix note about `%Y` padding. >--------------------------------------------------------------- ba160e582fc02a9d9b19b3235926c91cc390240f lib/Data/Time/Format.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Jan 23 23:02:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:54 +0000 (UTC) Subject: [commit: packages/time] master: De-tabify all Haskell source files. (63d2c82) Message-ID: <20150123230254.F0B9E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/63d2c8270de4ce32ae39e4d98ca1749ebb10ad94 >--------------------------------------------------------------- commit 63d2c8270de4ce32ae39e4d98ca1749ebb10ad94 Author: Erik de Castro Lopo Date: Tue Dec 23 14:43:30 2014 +1100 De-tabify all Haskell source files. This library is a GHC core library and GHC is now built using the -fwarn-tabs flag by default. De-tabifying this brings it into line with GHC standard practice. Also add -fwarn-tabs to the cabal file. Closes: https://github.com/haskell/time/issues/18 >--------------------------------------------------------------- 63d2c8270de4ce32ae39e4d98ca1749ebb10ad94 lib/Data/Time.hs | 8 +- lib/Data/Time/Calendar.hs | 4 +- lib/Data/Time/Calendar/Days.hs | 54 +++++----- lib/Data/Time/Calendar/Easter.hs | 20 ++-- lib/Data/Time/Calendar/Gregorian.hs | 34 +++---- lib/Data/Time/Calendar/Julian.hs | 28 +++--- lib/Data/Time/Calendar/JulianYearDay.hs | 36 +++---- lib/Data/Time/Calendar/MonthDay.hs | 32 +++--- lib/Data/Time/Calendar/OrdinalDate.hs | 80 +++++++-------- lib/Data/Time/Calendar/WeekDate.hs | 52 +++++----- lib/Data/Time/Clock.hs | 8 +- lib/Data/Time/Clock/CTimeval.hs | 24 ++--- lib/Data/Time/Clock/POSIX.hs | 6 +- lib/Data/Time/Clock/Scale.hs | 52 +++++----- lib/Data/Time/Clock/TAI.hs | 142 +++++++++++++-------------- lib/Data/Time/Clock/UTC.hs | 90 ++++++++--------- lib/Data/Time/Format.hs | 168 ++++++++++++++++---------------- lib/Data/Time/LocalTime.hs | 6 +- lib/Data/Time/LocalTime/LocalTime.hs | 48 ++++----- lib/Data/Time/LocalTime/TimeOfDay.hs | 50 +++++----- lib/Data/Time/LocalTime/TimeZone.hs | 44 ++++----- time.cabal | 2 +- 22 files changed, 494 insertions(+), 494 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 63d2c8270de4ce32ae39e4d98ca1749ebb10ad94 From git at git.haskell.org Fri Jan 23 23:02:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:57 +0000 (UTC) Subject: [commit: packages/time] master: Merge pull request #19 from erikd/master (b0c04d9) Message-ID: <20150123230257.05ECA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/b0c04d9e15ecfe7c629212280bb790d383a3f784 >--------------------------------------------------------------- commit b0c04d9e15ecfe7c629212280bb790d383a3f784 Merge: ba160e5 63d2c82 Author: Ashley Yakeley Date: Mon Dec 22 20:10:45 2014 -0800 Merge pull request #19 from erikd/master De-tabify all Haskell source files. >--------------------------------------------------------------- b0c04d9e15ecfe7c629212280bb790d383a3f784 lib/Data/Time.hs | 8 +- lib/Data/Time/Calendar.hs | 4 +- lib/Data/Time/Calendar/Days.hs | 54 +++++----- lib/Data/Time/Calendar/Easter.hs | 20 ++-- lib/Data/Time/Calendar/Gregorian.hs | 34 +++---- lib/Data/Time/Calendar/Julian.hs | 28 +++--- lib/Data/Time/Calendar/JulianYearDay.hs | 36 +++---- lib/Data/Time/Calendar/MonthDay.hs | 32 +++--- lib/Data/Time/Calendar/OrdinalDate.hs | 80 +++++++-------- lib/Data/Time/Calendar/WeekDate.hs | 52 +++++----- lib/Data/Time/Clock.hs | 8 +- lib/Data/Time/Clock/CTimeval.hs | 24 ++--- lib/Data/Time/Clock/POSIX.hs | 6 +- lib/Data/Time/Clock/Scale.hs | 52 +++++----- lib/Data/Time/Clock/TAI.hs | 142 +++++++++++++-------------- lib/Data/Time/Clock/UTC.hs | 90 ++++++++--------- lib/Data/Time/Format.hs | 168 ++++++++++++++++---------------- lib/Data/Time/LocalTime.hs | 6 +- lib/Data/Time/LocalTime/LocalTime.hs | 48 ++++----- lib/Data/Time/LocalTime/TimeOfDay.hs | 50 +++++----- lib/Data/Time/LocalTime/TimeZone.hs | 44 ++++----- time.cabal | 2 +- 22 files changed, 494 insertions(+), 494 deletions(-) From git at git.haskell.org Fri Jan 23 23:02:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:02:59 +0000 (UTC) Subject: [commit: packages/time] master: Document that the show instance for UTCTime is elsewhere. (5bcf96f) Message-ID: <20150123230259.0E8853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/5bcf96f4c0f5755a110e7ef6ae3ab54b42a1e96e >--------------------------------------------------------------- commit 5bcf96f4c0f5755a110e7ef6ae3ab54b42a1e96e Author: Tom Ellis Date: Wed Dec 31 13:05:27 2014 +0000 Document that the show instance for UTCTime is elsewhere. >--------------------------------------------------------------- 5bcf96f4c0f5755a110e7ef6ae3ab54b42a1e96e lib/Data/Time/Clock/UTC.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/lib/Data/Time/Clock/UTC.hs b/lib/Data/Time/Clock/UTC.hs index eff7f4d..0c0a7d3 100644 --- a/lib/Data/Time/Clock/UTC.hs +++ b/lib/Data/Time/Clock/UTC.hs @@ -28,6 +28,9 @@ import Data.Data -- | This is the simplest representation of UTC. -- It consists of the day number, and a time offset from midnight. -- Note that if a day has a leap second added to it, it will have 86401 seconds. +-- +-- For the 'Show' instance of 'UTCTime' import @Data.Time@ or +-- @Data.Time.LocalTime at . data UTCTime = UTCTime { -- | the day utctDay :: Day, From git at git.haskell.org Fri Jan 23 23:03:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:03:01 +0000 (UTC) Subject: [commit: packages/time] master: Merge pull request #21 from tomjaguarpaw/master (acc5478) Message-ID: <20150123230301.165003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : master Link : http://git.haskell.org/packages/time.git/commitdiff/acc5478a3aa6c2e33f4fb3f644a2239490e7447f >--------------------------------------------------------------- commit acc5478a3aa6c2e33f4fb3f644a2239490e7447f Merge: b0c04d9 5bcf96f Author: Ashley Yakeley Date: Mon Jan 5 16:43:51 2015 -0800 Merge pull request #21 from tomjaguarpaw/master Document that the show instance for UTCTime is elsewhere. >--------------------------------------------------------------- acc5478a3aa6c2e33f4fb3f644a2239490e7447f lib/Data/Time/Clock/UTC.hs | 3 +++ 1 file changed, 3 insertions(+) From git at git.haskell.org Fri Jan 23 23:04:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:04:33 +0000 (UTC) Subject: [commit: packages/haskeline] master: [ .gitignore ] Added dist/ (abaf5a2) Message-ID: <20150123230433.31C233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/abaf5a28fdf557d960bd2da4b6d8819e633cf18f >--------------------------------------------------------------- commit abaf5a28fdf557d960bd2da4b6d8819e633cf18f Author: Andr?s Sicard-Ram?rez Date: Tue Nov 4 08:31:57 2014 -0500 [ .gitignore ] Added dist/ >--------------------------------------------------------------- abaf5a28fdf557d960bd2da4b6d8819e633cf18f .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 8f4d267..b19cb2b 100644 --- a/.gitignore +++ b/.gitignore @@ -1,3 +1,4 @@ GNUmakefile +dist/ dist-install ghc.mk From git at git.haskell.org Fri Jan 23 23:04:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:04:35 +0000 (UTC) Subject: [commit: packages/haskeline] master: Removed unnecessary dependency on Cabal >= 1.16 (bcc1b81) Message-ID: <20150123230435.38E5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/bcc1b8181d529fd75acbfbef589c2856416e70c9 >--------------------------------------------------------------- commit bcc1b8181d529fd75acbfbef589c2856416e70c9 Author: Andr?s Sicard-Ram?rez Date: Tue Nov 4 08:32:25 2014 -0500 Removed unnecessary dependency on Cabal >= 1.16 This simplies the installation with GHC < 7.6. >--------------------------------------------------------------- bcc1b8181d529fd75acbfbef589c2856416e70c9 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haskeline.cabal b/haskeline.cabal index 404bf65..541ac8c 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -1,5 +1,5 @@ Name: haskeline -Cabal-Version: >=1.16 +Cabal-Version: >=1.10 Version: 0.7.1.3 Category: User Interfaces License: BSD3 From git at git.haskell.org Fri Jan 23 23:04:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:04:37 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge branch 'asr-master' (87a01d2) Message-ID: <20150123230437.3E9833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/87a01d222ef13f89a68204602e3fe9273eeed3ca >--------------------------------------------------------------- commit 87a01d222ef13f89a68204602e3fe9273eeed3ca Merge: 9d032a3 bcc1b81 Author: Judah Jacobson Date: Tue Jan 20 10:36:40 2015 -0800 Merge branch 'asr-master' Conflicts: haskeline.cabal >--------------------------------------------------------------- 87a01d222ef13f89a68204602e3fe9273eeed3ca .gitignore | 1 + haskeline.cabal | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --cc haskeline.cabal index f8ab65c,541ac8c..d1fe65a --- a/haskeline.cabal +++ b/haskeline.cabal @@@ -1,6 -1,6 +1,6 @@@ Name: haskeline - Cabal-Version: >=1.16 + Cabal-Version: >=1.10 -Version: 0.7.1.3 +Version: 0.7.2.0 Category: User Interfaces License: BSD3 License-File: LICENSE From git at git.haskell.org Fri Jan 23 23:04:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Jan 2015 23:04:50 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update haskeline submodule to upstream master tip (62d716e) Message-ID: <20150123230450.32ED63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/62d716e85aab992f8b1860da962c95d786ba44d7/ghc >--------------------------------------------------------------- commit 62d716e85aab992f8b1860da962c95d786ba44d7 Author: Herbert Valerio Riedel Date: Sat Jan 24 00:04:17 2015 +0100 Update haskeline submodule to upstream master tip this should have no visible effects as only the .cabal file was modified. >--------------------------------------------------------------- 62d716e85aab992f8b1860da962c95d786ba44d7 libraries/haskeline | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/haskeline b/libraries/haskeline index 9d032a3..87a01d2 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 9d032a3ad4e652357212dda1e02c4baa3579f111 +Subproject commit 87a01d222ef13f89a68204602e3fe9273eeed3ca From git at git.haskell.org Mon Jan 26 23:11:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Jan 2015 23:11:12 +0000 (UTC) Subject: [commit: ghc] master: RTS : Fix StgRun for aarch64-linux (#9935). (b906370) Message-ID: <20150126231112.5CF493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b9063703301f0d902b4bb2eb28ac27e9bc050ea0/ghc >--------------------------------------------------------------- commit b9063703301f0d902b4bb2eb28ac27e9bc050ea0 Author: Erik de Castro Lopo Date: Tue Jan 27 10:12:49 2015 +1100 RTS : Fix StgRun for aarch64-linux (#9935). Summary: The GCC assembler doesn't seem to recognise the 'fp' and 'lr' register names which are aliases for 'x29' and 'x30' respectively. Depends on D598. Test Plan: validate Reviewers: lukexi, bgamari, austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D599 GHC Trac Issues: #9935 >--------------------------------------------------------------- b9063703301f0d902b4bb2eb28ac27e9bc050ea0 rts/StgCRun.c | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/rts/StgCRun.c b/rts/StgCRun.c index 55e0a48..f8a3f0f 100644 --- a/rts/StgCRun.c +++ b/rts/StgCRun.c @@ -755,12 +755,14 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { StgRegTable * r; __asm__ volatile ( /* - * save callee-saves registers on behalf of the STG code. - * floating point registers only need the bottom 64 bits preserved. - * x16 and x17 are ip0 and ip1, but we can't refer to them by that name with clang. + * Save callee-saves registers on behalf of the STG code. + * Floating point registers only need the bottom 64 bits preserved. + * We need to use the the names x16, x17, x29 and x30 instead of ip0 + * ip1, fp and lp because one of either clang or gcc doesn't understand + * the later names. */ - "stp fp, lr, [sp, #-16]!\n\t" - "mov fp, sp\n\t" + "stp x29, x30, [sp, #-16]!\n\t" + "mov x29, sp\n\t" "stp x16, x17, [sp, #-16]!\n\t" "stp x19, x20, [sp, #-16]!\n\t" "stp x21, x22, [sp, #-16]!\n\t" @@ -814,12 +816,12 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { "ldp x21, x22, [sp], #16\n\t" "ldp x19, x20, [sp], #16\n\t" "ldp x16, x17, [sp], #16\n\t" - "ldp fp, lr, [sp], #16\n\t" + "ldp x29, x30, [sp], #16\n\t" : "=r" (r) : "r" (f), "r" (basereg), "i" (RESERVED_C_STACK_BYTES) : "%x19", "%x20", "%x21", "%x22", "%x23", "%x24", "%x25", "%x26", "%x27", "%x28", - "%x16", "%x17", "%lr" + "%x16", "%x17", "%x30" ); return r; } From git at git.haskell.org Mon Jan 26 23:17:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Jan 2015 23:17:18 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update release notes (25e416d) Message-ID: <20150126231718.B21BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/25e416dfba7ea6007f9c74699e1d6a9efd65db9b/ghc >--------------------------------------------------------------- commit 25e416dfba7ea6007f9c74699e1d6a9efd65db9b Author: Austin Seipp Date: Mon Jan 26 17:18:25 2015 -0600 Update release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 25e416dfba7ea6007f9c74699e1d6a9efd65db9b docs/users_guide/7.10.1-notes.xml | 212 ++++++++++++++++++++++++++------------ 1 file changed, 147 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 25e416dfba7ea6007f9c74699e1d6a9efd65db9b From git at git.haskell.org Tue Jan 27 19:01:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jan 2015 19:01:24 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-july' created Message-ID: <20150127190124.781823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : ghc-july Referencing: 0af1b73e10ccb232af568cda5acf59e5ab1eaa85 From git at git.haskell.org Tue Jan 27 19:01:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jan 2015 19:01:28 +0000 (UTC) Subject: [commit: ghc] ghc-july: Add cost semantics for STG profiling. (0af1b73) Message-ID: <20150127190128.7AAF33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-july Link : http://ghc.haskell.org/trac/ghc/changeset/0af1b73e10ccb232af568cda5acf59e5ab1eaa85/ghc >--------------------------------------------------------------- commit 0af1b73e10ccb232af568cda5acf59e5ab1eaa85 Author: Edward Z. Yang Date: Tue Jan 27 10:43:57 2015 -0800 Add cost semantics for STG profiling. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 0af1b73e10ccb232af568cda5acf59e5ab1eaa85 docs/stg-spec/.gitignore | 5 + docs/stg-spec/CostSem.ott | 122 +++++++++++++++++++++ docs/{core-spec => stg-spec}/Makefile | 6 +- docs/stg-spec/StgSyn.ott | 105 ++++++++++++++++++ docs/stg-spec/stg-spec.mng | 200 ++++++++++++++++++++++++++++++++++ 5 files changed, 435 insertions(+), 3 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0af1b73e10ccb232af568cda5acf59e5ab1eaa85 From git at git.haskell.org Tue Jan 27 19:01:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jan 2015 19:01:45 +0000 (UTC) Subject: [commit: ghc] master's head updated: Add cost semantics for STG profiling. (0af1b73) Message-ID: <20150127190145.0A3FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 0af1b73 Add cost semantics for STG profiling. From git at git.haskell.org Tue Jan 27 19:16:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Jan 2015 19:16:55 +0000 (UTC) Subject: [commit: ghc] master: Fix #10031 by inverting a critical test in kick_out. (cecf036) Message-ID: <20150127191655.B38753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cecf036fa10830a5e9861d1e6a2f8c22059fb4bb/ghc >--------------------------------------------------------------- commit cecf036fa10830a5e9861d1e6a2f8c22059fb4bb Author: Richard Eisenberg Date: Tue Jan 27 11:40:26 2015 -0500 Fix #10031 by inverting a critical test in kick_out. Summary: The documentation (Note [The flattening story] in TcFlatten) was correct; it's just the implementation that was not. Test in typecheck/should_compile/T10031 Test Plan: validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D630 GHC Trac Issues: #10031 >--------------------------------------------------------------- cecf036fa10830a5e9861d1e6a2f8c22059fb4bb compiler/typecheck/TcInteract.hs | 2 +- testsuite/tests/typecheck/should_compile/T10031.hs | 5 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 7 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 18ca270..aef934c 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1126,7 +1126,7 @@ kick_out new_flavour new_eq_rel new_tv (IC { inert_eqs = tv_eqs | can_rewrite ev = case eq_rel of NomEq -> not (rhs_ty `eqType` mkTyVarTy new_tv) - ReprEq -> isTyVarExposed new_tv rhs_ty + ReprEq -> not (isTyVarExposed new_tv rhs_ty) | otherwise = True diff --git a/testsuite/tests/typecheck/should_compile/T10031.hs b/testsuite/tests/typecheck/should_compile/T10031.hs new file mode 100644 index 0000000..4ed45d3 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10031.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE ScopedTypeVariables #-} +module T10031 where +import Data.Coerce +coerce' :: Coercible b a => a -> b +coerce' = coerce (\x -> x :: b) :: forall a b. Coercible b a => a -> b diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index c292eaf..4348ea3 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -441,3 +441,4 @@ test('T9939', normal, compile, ['']) test('T9973', normal, compile, ['']) test('T9971', normal, compile, ['']) test('T9999', normal, compile, ['']) +test('T10031', normal, compile, ['']) From git at git.haskell.org Wed Jan 28 11:32:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jan 2015 11:32:19 +0000 (UTC) Subject: [commit: nofib] master: Update output (random changes?) (85d10a4) Message-ID: <20150128113219.7D3173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/85d10a442ccc36b953cabe300ae7c2cd0dae9a97/nofib >--------------------------------------------------------------- commit 85d10a442ccc36b953cabe300ae7c2cd0dae9a97 Author: Simon Marlow Date: Wed Jan 28 11:30:00 2015 +0000 Update output (random changes?) >--------------------------------------------------------------- 85d10a442ccc36b953cabe300ae7c2cd0dae9a97 parallel/minimax/minimax.stdout | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/parallel/minimax/minimax.stdout b/parallel/minimax/minimax.stdout index 0407528..3e41691 100644 --- a/parallel/minimax/minimax.stdout +++ b/parallel/minimax/minimax.stdout @@ -1,18 +1,18 @@ - |X| | + | | |O -------- - | | | + |X|O| -------- - |O| | + | | |X -------- -O| | |X + | | | Score 2 -X|X| | +X| | |O -------- - | | | + |X|O| -------- - |O| | + | | |X -------- -O| | |X + | | | From git at git.haskell.org Wed Jan 28 11:41:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jan 2015 11:41:09 +0000 (UTC) Subject: [commit: ghc] master: update submodule (cf3e340) Message-ID: <20150128114109.449243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cf3e3406a0b66f1831decd88f8deda5e297f4395/ghc >--------------------------------------------------------------- commit cf3e3406a0b66f1831decd88f8deda5e297f4395 Author: Simon Marlow Date: Wed Jan 28 11:34:26 2015 +0000 update submodule >--------------------------------------------------------------- cf3e3406a0b66f1831decd88f8deda5e297f4395 nofib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nofib b/nofib index e8f5d80..85d10a4 160000 --- a/nofib +++ b/nofib @@ -1 +1 @@ -Subproject commit e8f5d80cb41b5267f23835909d06b4317cafd32f +Subproject commit 85d10a442ccc36b953cabe300ae7c2cd0dae9a97 From git at git.haskell.org Wed Jan 28 14:32:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jan 2015 14:32:46 +0000 (UTC) Subject: [commit: ghc] master: Improve error message on typed holes, and user manual (Tradc #10040) (276da79) Message-ID: <20150128143246.759163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/276da7929c187f007c198a38e88bdad91866e500/ghc >--------------------------------------------------------------- commit 276da7929c187f007c198a38e88bdad91866e500 Author: Simon Peyton Jones Date: Wed Jan 28 14:31:52 2015 +0000 Improve error message on typed holes, and user manual (Tradc #10040) >--------------------------------------------------------------- 276da7929c187f007c198a38e88bdad91866e500 compiler/typecheck/TcErrors.hs | 12 +++- docs/users_guide/glasgow_exts.xml | 73 +++++++++++----------- .../tests/typecheck/should_compile/T9497a.stderr | 1 + .../tests/typecheck/should_compile/holes3.stderr | 3 + .../tests/typecheck/should_fail/T9497d.stderr | 1 + 5 files changed, 51 insertions(+), 39 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 276da7929c187f007c198a38e88bdad91866e500 From git at git.haskell.org Wed Jan 28 18:46:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jan 2015 18:46:44 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: RTS : Fix StgRun for aarch64-linux (#9935). (5f2af66) Message-ID: <20150128184644.7953F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/5f2af6646067a6a66afa450c42482b5723172593/ghc >--------------------------------------------------------------- commit 5f2af6646067a6a66afa450c42482b5723172593 Author: Erik de Castro Lopo Date: Tue Jan 27 10:12:49 2015 +1100 RTS : Fix StgRun for aarch64-linux (#9935). Summary: The GCC assembler doesn't seem to recognise the 'fp' and 'lr' register names which are aliases for 'x29' and 'x30' respectively. Depends on D598. Test Plan: validate Reviewers: lukexi, bgamari, austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D599 GHC Trac Issues: #9935 (cherry picked from commit b9063703301f0d902b4bb2eb28ac27e9bc050ea0) >--------------------------------------------------------------- 5f2af6646067a6a66afa450c42482b5723172593 rts/StgCRun.c | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/rts/StgCRun.c b/rts/StgCRun.c index 55e0a48..f8a3f0f 100644 --- a/rts/StgCRun.c +++ b/rts/StgCRun.c @@ -755,12 +755,14 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { StgRegTable * r; __asm__ volatile ( /* - * save callee-saves registers on behalf of the STG code. - * floating point registers only need the bottom 64 bits preserved. - * x16 and x17 are ip0 and ip1, but we can't refer to them by that name with clang. + * Save callee-saves registers on behalf of the STG code. + * Floating point registers only need the bottom 64 bits preserved. + * We need to use the the names x16, x17, x29 and x30 instead of ip0 + * ip1, fp and lp because one of either clang or gcc doesn't understand + * the later names. */ - "stp fp, lr, [sp, #-16]!\n\t" - "mov fp, sp\n\t" + "stp x29, x30, [sp, #-16]!\n\t" + "mov x29, sp\n\t" "stp x16, x17, [sp, #-16]!\n\t" "stp x19, x20, [sp, #-16]!\n\t" "stp x21, x22, [sp, #-16]!\n\t" @@ -814,12 +816,12 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { "ldp x21, x22, [sp], #16\n\t" "ldp x19, x20, [sp], #16\n\t" "ldp x16, x17, [sp], #16\n\t" - "ldp fp, lr, [sp], #16\n\t" + "ldp x29, x30, [sp], #16\n\t" : "=r" (r) : "r" (f), "r" (basereg), "i" (RESERVED_C_STACK_BYTES) : "%x19", "%x20", "%x21", "%x22", "%x23", "%x24", "%x25", "%x26", "%x27", "%x28", - "%x16", "%x17", "%lr" + "%x16", "%x17", "%x30" ); return r; } From git at git.haskell.org Wed Jan 28 18:46:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jan 2015 18:46:47 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix #10031 by inverting a critical test in kick_out. (2387369) Message-ID: <20150128184647.BDE673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/2387369c498f631bd3f4be2d6efe71773353acc5/ghc >--------------------------------------------------------------- commit 2387369c498f631bd3f4be2d6efe71773353acc5 Author: Richard Eisenberg Date: Tue Jan 27 11:40:26 2015 -0500 Fix #10031 by inverting a critical test in kick_out. Summary: The documentation (Note [The flattening story] in TcFlatten) was correct; it's just the implementation that was not. Test in typecheck/should_compile/T10031 Test Plan: validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D630 GHC Trac Issues: #10031 (cherry picked from commit cecf036fa10830a5e9861d1e6a2f8c22059fb4bb) >--------------------------------------------------------------- 2387369c498f631bd3f4be2d6efe71773353acc5 compiler/typecheck/TcInteract.hs | 2 +- testsuite/tests/typecheck/should_compile/T10031.hs | 5 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 7 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index c67e437..1d0d8e4 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1033,7 +1033,7 @@ kick_out new_flavour new_eq_rel new_tv (IC { inert_eqs = tv_eqs | can_rewrite ev = case eq_rel of NomEq -> not (rhs_ty `eqType` mkTyVarTy new_tv) - ReprEq -> isTyVarExposed new_tv rhs_ty + ReprEq -> not (isTyVarExposed new_tv rhs_ty) | otherwise = True diff --git a/testsuite/tests/typecheck/should_compile/T10031.hs b/testsuite/tests/typecheck/should_compile/T10031.hs new file mode 100644 index 0000000..4ed45d3 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10031.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE ScopedTypeVariables #-} +module T10031 where +import Data.Coerce +coerce' :: Coercible b a => a -> b +coerce' = coerce (\x -> x :: b) :: forall a b. Coercible b a => a -> b diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index df07a3e..cce92d0 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -439,3 +439,4 @@ test('T9834', normal, compile, ['']) test('T9892', normal, compile, ['']) test('T9971', normal, compile, ['']) test('T9999', normal, compile, ['']) +test('T10031', normal, compile, ['']) From git at git.haskell.org Wed Jan 28 18:57:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jan 2015 18:57:49 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: docs: Fix #9928 (wrong version info) (e25e78f) Message-ID: <20150128185749.874283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/e25e78f6731248873f7aa899e6f3d69c1078727d/ghc >--------------------------------------------------------------- commit e25e78f6731248873f7aa899e6f3d69c1078727d Author: Austin Seipp Date: Wed Jan 28 12:59:25 2015 -0600 docs: Fix #9928 (wrong version info) Signed-off-by: Austin Seipp >--------------------------------------------------------------- e25e78f6731248873f7aa899e6f3d69c1078727d docs/users_guide/7.10.1-notes.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index b48efb9..16f113f 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -753,7 +753,7 @@ echo "[]" > package.conf - Version number 1.5.0.1 (was 1.4.1) + Version number 1.5.0.1 (was 1.4.2) From git at git.haskell.org Wed Jan 28 21:53:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Jan 2015 21:53:22 +0000 (UTC) Subject: [commit: ghc] master: Use strict atomicModifyIORef' (added in GHC 7.6). (07ee96f) Message-ID: <20150128215322.E3FA73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/07ee96faac4996cde0ab82789eec0b70d1a35af0/ghc >--------------------------------------------------------------- commit 07ee96faac4996cde0ab82789eec0b70d1a35af0 Author: Edward Z. Yang Date: Tue Jan 27 16:20:54 2015 -0800 Use strict atomicModifyIORef' (added in GHC 7.6). Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin, hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D635 >--------------------------------------------------------------- 07ee96faac4996cde0ab82789eec0b70d1a35af0 compiler/deSugar/DsExpr.hs | 4 ++-- compiler/ghci/Debugger.hs | 2 +- compiler/iface/IfaceEnv.hs | 7 ++----- compiler/main/Finder.hs | 14 ++++++-------- compiler/main/GhcMake.hs | 6 +++--- compiler/main/SysTools.hs | 12 ++++++------ compiler/main/TidyPgm.hs | 6 +++--- compiler/typecheck/TcEnv.hs | 2 +- compiler/utils/FastString.hs | 8 ++++---- compiler/utils/IOEnv.hs | 7 ++----- compiler/utils/Util.hs | 4 ++-- 11 files changed, 32 insertions(+), 40 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 07ee96faac4996cde0ab82789eec0b70d1a35af0 From git at git.haskell.org Thu Jan 29 12:33:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jan 2015 12:33:01 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T4879' created Message-ID: <20150129123301.47BC73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T4879 Referencing: 348df976743964ab838714e01f4bcac752c5dfc4 From git at git.haskell.org Thu Jan 29 12:33:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Jan 2015 12:33:04 +0000 (UTC) Subject: [commit: ghc] wip/T4879: Support re-export deprecations (re #4879) (348df97) Message-ID: <20150129123304.05AE33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T4879 Link : http://ghc.haskell.org/trac/ghc/changeset/348df976743964ab838714e01f4bcac752c5dfc4/ghc >--------------------------------------------------------------- commit 348df976743964ab838714e01f4bcac752c5dfc4 Author: Herbert Valerio Riedel Date: Thu Jan 29 13:32:58 2015 +0100 Support re-export deprecations (re #4879) This is basically the patch originally implemented by Ian Lynagh forward-ported to GHC 7.10/11 >--------------------------------------------------------------- 348df976743964ab838714e01f4bcac752c5dfc4 compiler/basicTypes/Avail.hs | 63 +++++++++++++---- compiler/basicTypes/BasicTypes.hs | 2 +- compiler/basicTypes/RdrName.hs | 27 +++++--- compiler/deSugar/DsMonad.hs | 2 +- compiler/hsSyn/HsDecls.hs | 2 +- compiler/hsSyn/HsImpExp.hs | 4 ++ compiler/iface/MkIface.hs | 4 +- compiler/main/DynamicLoading.hs | 2 +- compiler/main/HscTypes.hs | 26 ++++--- compiler/main/InteractiveEval.hs | 2 +- compiler/parser/Parser.y | 1 + compiler/prelude/PrelInfo.hs | 10 +-- compiler/rename/RnEnv.hs | 4 +- compiler/rename/RnNames.hs | 139 ++++++++++++++++++++++++-------------- compiler/rename/RnSource.hs | 3 +- compiler/typecheck/TcDeriv.hs | 3 +- compiler/typecheck/TcRnDriver.hs | 2 +- 17 files changed, 197 insertions(+), 99 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 348df976743964ab838714e01f4bcac752c5dfc4 From git at git.haskell.org Fri Jan 30 08:58:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Jan 2015 08:58:55 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Event Manager: Make one-shot a per-registration property (7bf4793) Message-ID: <20150130085855.D7A4C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/7bf4793b76080de15937b30b5bee5f62cc23d176/ghc >--------------------------------------------------------------- commit 7bf4793b76080de15937b30b5bee5f62cc23d176 Author: Ben Gamari Date: Mon Jan 12 18:36:23 2015 -0500 Event Manager: Make one-shot a per-registration property Currently the event manager has a global flag for whether to create epoll-like notifications as one-shot (e.g. EPOLLONESHOT, where an fd will be deactivated after its first event) or standard multi-shot notifications. Unfortunately this means that the event manager may export either one-shot or multi-shot semantics to the user. Even worse, the user has no way of knowing which semantics are being delivered. This resulted in breakage in the usb[1] library which deadlocks after notifications on its fd are disabled after the first event is delivered. This patch reworks one-shot event support to allow the user to choose whether one-shot or multi-shot semantics are desired on a per-registration basis. The event manager can then decide whether to use a one-shot or multi-shot epoll. A registration is now defined by a set of Events (as before) as well as a Lifetime (either one-shot or multi-shot). We lend monoidal structure to Lifetime choosing OneShot as the identity. This allows us to combine Lifetime/Event pairs of an fd to give the longest desired lifetime of the registration and the full set of Events for which we want notification. [1] https://github.com/basvandijk/usb/issues/7 (cherry picked from commit 023439980f6ef6ec051f676279ed2be5f031efe6) >--------------------------------------------------------------- 7bf4793b76080de15937b30b5bee5f62cc23d176 libraries/base/GHC/Event.hs | 1 - libraries/base/GHC/Event/IntTable.hs | 4 + libraries/base/GHC/Event/Internal.hs | 48 ++++++++ libraries/base/GHC/Event/Manager.hs | 224 +++++++++++++++++++---------------- libraries/base/GHC/Event/Thread.hs | 6 +- 5 files changed, 175 insertions(+), 108 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7bf4793b76080de15937b30b5bee5f62cc23d176