[darcs-users] darcs patch: Info.lhs, OldDate.lhs: push bytestring d... (and 3 more)

David Roundy droundy at darcs.net
Sat Apr 26 11:11:42 UTC 2008


On Sat, Apr 26, 2008 at 12:24:53AM -0400, gwern0 at gmail.com wrote:
> Thu Apr 24 20:27:39 EDT 2008  gwern0 at gmail.com
>   * Info.lhs, OldDate.lhs: push bytestring down the hierarchy
>   We don't want unpackPS/packString high up in the call hierarchy; we want those functions being called only at the very site or definition they are needed.

I'd prefer to have long comments on patches word-wrapped.

>   Unfortunately, we can't completely ByteString'ify OldDate.lhs, although I've given a sketch how to make it more bytestringy.
> 
> Sat Apr 26 00:04:47 EDT 2008  gwern0 at gmail.com
>   * FastPackedString, OldFastPackedString.hs: add in 'allPS' definition
>   This is a missing list utility function; for FPS.hs, it's the usual wrapping, while I copy the Bytestring version (swapping 'unsafePeformIO' for 'inplacePerformIO') into OldFPS. This will be a useful function for the next patch.
> 
> Sat Apr 26 00:07:57 EDT 2008  gwern0 at gmail.com
>   * OldDate.lhs: with allPS defined, we can define parseDate as more bytestringy
> 
> Sat Apr 26 00:23:24 EDT 2008  gwern0 at gmail.com
>   * refactor some of parseDate in OldDate.lhs

Content-Description: A darcs patch for your repository!
> -----BEGIN PGP SIGNED MESSAGE-----
> Hash: SHA512
> 
> 
> New patches:
> 
> [Info.lhs, OldDate.lhs: push bytestring down the hierarchy
> gwern0 at gmail.com**20080425002739
>  We don't want unpackPS/packString high up in the call hierarchy; we want those functions being called only at the very site or definition they are needed.
>  
>  Unfortunately, we can't completely ByteString'ify OldDate.lhs, although I've given a sketch how to make it more bytestringy.
> ] hunk ./src/Darcs/Patch/Info.lhs 108

This patch has way too many white-space changes.  Please resend without
them.  I don't care to read through page after page of non-changes, in
order to seek out what (according to the patch description) should be a
very simple change.

>  --   before 1.0.  Fortunately, newer patch dates are written in
>  --   UTC, so this timezone truncation is harmless for them.
>  readPatchDate :: PackedString -> CalendarTime
> - -readPatchDate = ignoreTz . readUTCDate . unpackPS
> +readPatchDate = ignoreTz . readUTCDate
>    where ignoreTz ct = ct { ctTZ = 0 }
>  
>  pi_date :: PatchInfo -> CalendarTime
> hunk ./src/OldDate.lhs 30
>  import System.Time
>  import Data.Char ( toUpper, isDigit )
>  import Control.Monad ( liftM, liftM2 )
> +import FastPackedString
>  
>  -- | Read/interpret a date string, assuming UTC if timezone
>  --   is not specified in the string
> hunk ./src/OldDate.lhs 34
> - -readUTCDate :: String -> CalendarTime
> +readUTCDate :: PackedString -> CalendarTime
>  readUTCDate = readDate 0
>  
> hunk ./src/OldDate.lhs 37
> - -readDate :: Int -> String -> CalendarTime
> +readDate :: Int -> PackedString -> CalendarTime
>  readDate tz d =
> hunk ./src/OldDate.lhs 39
> - -             case parseDate tz d of
> +             case parseDate tz (unpackPS d) of
>               Left e -> error e
>               Right ct -> ct
>  
> hunk ./src/OldDate.lhs 43
> +-- This is hard to convert to ByteString because Parsec's 'parse' needs String
> +-- and because the only 'read' for ByteString is in the separate Data.Binary package.
>  parseDate :: Int -> String -> Either String CalendarTime
>  parseDate tz d =
>                if length d >= 14 && and (map isDigit $ take 14 d)
> hunk ./src/OldDate.lhs 117
>  cvs_date_time tz =
>                  do y <- year
>                     char '/'
> - -                   mon <- month_num 
> +                   mon <- month_num
>                     char '/'
>                     d <- day
>                     my_spaces

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 147
>                        y <- year
>                        return (CalendarTime y mon d h m s 0 wd 0 "" z False)
>  
> - -{- FIXME: In case you ever want to use this outside of darcs, you should note 
> - -   that this implementation of ISO 8601 is not complete.  
> +{- FIXME: In case you ever want to use this outside of darcs, you should note
> +   that this implementation of ISO 8601 is not complete.
>  

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 150
> - -   reluctant to implement (ambiguous!): 
> - -     * years > 9999  
> - -     * truncated representations with implied century (89 for 1989) 
> - -   unimplemented: 
> +   reluctant to implement (ambiguous!):
> +     * years > 9999
> +     * truncated representations with implied century (89 for 1989)
> +   unimplemented:
>       * repeated durations (not relevant)
>       * lowest order component fractions in intervals

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 156
> - -     * negative dates (BC)                    
> +     * negative dates (BC)
>     unverified or too relaxed:
>       * the difference between 24h and 0h

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 159
> - -     * allows stuff like 2005-1212; either you use the hyphen all the way 
> +     * allows stuff like 2005-1212; either you use the hyphen all the way
>         (2005-12-12) or you don't use it at all (20051212), but you don't use

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 161
> - -       it halfway, likewise with time 
> - -     * No bounds checking whatsoever on intervals! 
> +       it halfway, likewise with time
> +     * No bounds checking whatsoever on intervals!
>         (next action: read iso doc to see if bounds-checking required?) -}
>  iso8601_date_time   :: Int -> CharParser a CalendarTime

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 165
> - -iso8601_date_time localTz = try $ 
> +iso8601_date_time localTz = try $
>    do d <- iso8601_date

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 167
> - -     t <- option id $ try $ do optional $ oneOf " T" 
> - -                               iso8601_time  
> +     t <- option id $ try $ do optional $ oneOf " T"
> +                               iso8601_time
>       return $ t $ d { ctTZ = localTz }
>  
>  iso8601_date :: CharParser a CalendarTime

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 172
> - -iso8601_date = 
> +iso8601_date =
>    do d <- calendar_date <|> week_date <|> ordinal_date
>       return $ foldr ($) nullCalendar d

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 175
> - -  where 
> +  where
>      calendar_date = -- yyyy-mm-dd
>        try $ do d <- optchain year_ [ (dash, month_), (dash, day_) ]

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 178
> - -               -- allow other variants to be parsed correctly 
> +               -- allow other variants to be parsed correctly
>                 notFollowedBy (digit <|> char 'W')
>                 return d

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 181
> - -    week_date = --yyyy-Www-dd 
> +    week_date = --yyyy-Www-dd
>        try $ do yfn <- year_
>                 optional dash
>                 char 'W'

This is not a change, as far as I can see.

> hunk ./src/OldDate.lhs 219
>  iso8601_time = try $
>    do ts <- optchain hour_ [ (colon     , min_)
>                            , (colon     , sec_)
> - -                          , (oneOf ",.", pico_) ] 
> +                          , (oneOf ",.", pico_) ]
>       z  <- option id $ choice [ zulu , offset ]
>       return $ foldr (.) id (z:ts)

This is not a change, as far as I can see.

And that's as far as I'm going to read.  Please, either don't make these
changes, or record interactively and pay attention to what changes you
accept.

David

> hunk ./src/OldDate.lhs 222
> - -  where 
> +  where
>      hour_ = do h <- two_digits
>                 return $ \c -> c { ctHour = h }
>      min_  = do m <- two_digits
> hunk ./src/OldDate.lhs 245
>      colon = char ':'
>  
>  optchain :: CharParser a b -> [(CharParser a c, CharParser a b)] -> CharParser a [b]
> - -optchain p next = try $ 
> +optchain p next = try $
>    do r1 <- p
> hunk ./src/OldDate.lhs 247
> - -     r2 <- case next of 
> +     r2 <- case next of
>             [] -> return []
>             ((sep,p2):next2) -> option [] $ do { optional sep; optchain p2 next2 }
>       return (r1:r2)
> hunk ./src/OldDate.lhs 252
>  
> - -n_digits :: Int -> CharParser a Int 
> +n_digits :: Int -> CharParser a Int
>  n_digits n = read `liftM` count n digit
>  
>  two_digits, four_digits :: CharParser a Int
> hunk ./src/OldDate.lhs 277
>  year             = four_digits
>  
>  month_num       :: CharParser a Month
> - -month_num = do mn <- manyNtoM 1 2 digit 
> +month_num = do mn <- manyNtoM 1 2 digit
>                 return $ intToMonth $ (read mn :: Int)
>  
>  intToMonth :: Int -> Month
> hunk ./src/OldDate.lhs 349
>       where mkZone n o  = try $ do { caseString n; return (o*60*60) }
>             space_digit = try $ do { char ' '; oneOf ['0'..'9'] }
>  
> - -nullCalendar :: CalendarTime 
> +nullCalendar :: CalendarTime
>  nullCalendar = CalendarTime 0 January 0 0 0 0 1 Sunday 0 "" 0 False
> hunk ./src/OldDate.lhs 351
> +
> +{- -- TODO: At some point we should convert parseDate to use ByteString; here's
> +   -- a sketch of how to do it.
> +
> +import qualified Data.ByteString.Char8 as B
> +import qualified Data.ByteString as C
> +import Data.Word
> +
> +-- ....
> +
> +isDigitWord8 :: Word8 -> Bool
> +isDigitWord8 p = p >= 0x30 && p <= 0x39
> +
> +readint :: B.ByteString -> Int
> +readint a = case (B.readInt a) of
> +              Just (b,_) -> b
> +              Nothing -> error "Bad parse of data"
> +
> +parseDate :: Int -> PackedString -> Either PackedString CalendarTime
> +parseDate tz d =
> +              if lengthPS d >= 14 && (C.all isDigitWord8 $ takePS 14 d)
> +              then Right $
> +                   CalendarTime (readint $ takePS 4 d)
> +                                (toEnum $ (+ (-1)) $ readint $ takePS 2 $ dropPS 4 d)
> +                                (readint $ takePS 2 $ dropPS 6 d) -- Day
> +                                (readint $ takePS 2 $ dropPS 8 d) -- Hour
> +                                (readint $ takePS 2 $ dropPS 10 d) -- Minute
> +                                (readint $ takePS 2 $ dropPS 12 d) -- Second
> +                                0 Sunday 0 -- Picosecond, weekday and day of year unknown
> +                                "GMT" 0 False
> +              else let dt = do { x <- date_time tz; eof; return x }
> +                   in case parse dt "" (unpackPS d) of
> +                      Left e -> Left $ concatPS [packString "bad date: ", d, packString " - ", packString $ show e]
> +                      Right ct -> Right ct
> +-}
>  \end{code}
> [FastPackedString, OldFastPackedString.hs: add in 'allPS' definition
> gwern0 at gmail.com**20080426040447
>  This is a missing list utility function; for FPS.hs, it's the usual wrapping, while I copy the Bytestring version (swapping 'unsafePeformIO' for 'inplacePerformIO') into OldFPS. This will be a useful function for the next patch.
> ] hunk ./src/FastPackedString.hs 65
>          dropPS,      -- :: Int -> PackedString -> PackedString
>          splitAtPS,   -- :: Int -> PackedString -> (PackedString, PackedString)
>  
> - -        anyPS,
> +        anyPS,       -- :: (Char -> Bool) -> PackedString -> Bool
> +        allPS,       -- :: (Char -> Bool) -> PackedString -> Bool
>          takeWhilePS, -- :: (Char -> Bool) -> PackedString -> PackedString
>          dropWhilePS, -- :: (Char -> Bool) -> PackedString -> PackedString
>          dropWhitePS, -- :: PackedString -> PackedString
> hunk ./src/FastPackedString.hs 293
>  anyPS :: (Char -> Bool) -> PackedString -> Bool
>  anyPS = B.any
>  
> +allPS :: (Char -> Bool) -> PackedString -> Bool
> +allPS = B.all
> +
>  {-# INLINE takeWhilePS #-}
>  takeWhilePS :: (Char -> Bool) -> PackedString -> PackedString
>  takeWhilePS = B.takeWhile
> hunk ./src/OldFastPackedString.hs 65
>          dropPS,      -- :: Int -> PackedString -> PackedString
>          splitAtPS,   -- :: Int -> PackedString -> (PackedString, PackedString)
>  
> - -        anyPS,
> +        anyPS,       -- :: (Char -> Bool) -> PackedString -> Bool
> +        allPS,       -- :: (Char -> Bool) -> PackedString -> Bool
>          takeWhilePS, -- :: (Char -> Bool) -> PackedString -> PackedString
>          dropWhilePS, -- :: (Char -> Bool) -> PackedString -> PackedString
>          dropWhitePS, -- :: PackedString -> PackedString
> hunk ./src/OldFastPackedString.hs 219
>  -- | 'comparePS' provides an 'Ordering' for 'PackedStrings' supporting slices.
>  comparePS :: PackedString -> PackedString -> Ordering
>  comparePS (PS _ _ 0) (PS _ _ 0) = EQ    -- short cut for empty strings
> - -comparePS (PS x1 s1 l1) (PS x2 s2 l2) = unsafePerformIO $ 
> - -    withForeignPtr x1 $ \p1 -> 
> - -        withForeignPtr x2 $ \p2 -> do 
> +comparePS (PS x1 s1 l1) (PS x2 s2 l2) = unsafePerformIO $
> +    withForeignPtr x1 $ \p1 ->
> +        withForeignPtr x2 $ \p2 -> do
>              i <- c_memcmp (p1 `plusPtr` s1) (p2 `plusPtr` s2)
>                   (fromIntegral $ min l1 l2)
>              return $ case i `compare` 0 of
> hunk ./src/OldFastPackedString.hs 344
>  -- | Extract the elements after the head of a packed string, which must be non-empty.
>  {-# INLINE tailPS #-}
>  tailPS :: PackedString -> PackedString
> - -tailPS (PS p s l) 
> +tailPS (PS p s l)
>      | l <= 0    = error ("FastPackedString.tailPS: empty list")
> hunk ./src/OldFastPackedString.hs 346
> - -    | l == 1    = nilPS                                                                    
> +    | l == 1    = nilPS
>      | otherwise = PS p (s+1) (l-1)
>  
>  -- | Return all the elements of a packed string except the last one.
> hunk ./src/OldFastPackedString.hs 353
>  -- The string must be finite and non-empty.
>  {-# INLINE initPS #-}
>  initPS :: PackedString -> PackedString
> - -initPS (PS p s l) 
> +initPS (PS p s l)
>      | l <= 0    = error ("FastPackedString.initPS: empty list")
> hunk ./src/OldFastPackedString.hs 355
> - -    | l == 1    = nilPS                                                                    
> - -    | otherwise = PS p s (l-1)                                                          
> +    | l == 1    = nilPS
> +    | otherwise = PS p s (l-1)
>  
>  {-# INLINE unsafeTailPS #-}
>  unsafeTailPS :: PackedString -> PackedString
> hunk ./src/OldFastPackedString.hs 401
>                                            then return True
>                                            else lookat (p `plusPtr` 1) st
>  
> +allPS :: (Char -> Bool) -> PackedString -> Bool
> +allPS _ (PS _ _ 0) = True
> +allPS f (PS x s l) = unsafePerformIO $ withForeignPtr x $ \ptr ->
> +        go (ptr `plusPtr` s) (ptr `plusPtr` (s+l))
> +    where
> +        go p q | p == q     = return True  -- end of list
> +               | otherwise  = do c <- peek p
> +                                 if f c
> +                                    then go (p `plusPtr` 1) q
> +                                    else return False
> +
> +
>  findWhenPS :: (Char -> Bool) -> PackedString -> Int
>  findWhenPS f ps = seq f $
>      if nullPS ps then 0
> [OldDate.lhs: with allPS defined, we can define parseDate as more bytestringy
> gwern0 at gmail.com**20080426040757] hunk ./src/OldDate.lhs 39
>  
>  readDate :: Int -> PackedString -> CalendarTime
>  readDate tz d =
> - -             case parseDate tz (unpackPS d) of
> +             case parseDate tz d of
>               Left e -> error e
>               Right ct -> ct
>  
> hunk ./src/OldDate.lhs 45
>  -- This is hard to convert to ByteString because Parsec's 'parse' needs String
>  -- and because the only 'read' for ByteString is in the separate Data.Binary package.
> - -parseDate :: Int -> String -> Either String CalendarTime
> +parseDate :: Int -> PackedString -> Either String CalendarTime
>  parseDate tz d =
> hunk ./src/OldDate.lhs 47
> - -              if length d >= 14 && and (map isDigit $ take 14 d)
> - -              then Right $
> - -                   CalendarTime (read $ take 4 d)
> - -                                (toEnum $ (+ (-1)) $ read $ take 2 $ drop 4 d)
> - -                                (read $ take 2 $ drop 6 d) -- Day
> - -                                (read $ take 2 $ drop 8 d) -- Hour
> - -                                (read $ take 2 $ drop 10 d) -- Minute
> - -                                (read $ take 2 $ drop 12 d) -- Second
> +              let d' = unpackPS d in
> +              if lengthPS d >= 14 && (allPS isDigit $ takePS 14 d)
> +              then
> +                   Right $
> +                   CalendarTime (read $ take 4 d')
> +                                (toEnum $ (+ (-1)) $ read $ take 2 $ drop 4 d')
> +                                (read $ take 2 $ drop 6 d') -- Day
> +                                (read $ take 2 $ drop 8 d') -- Hour
> +                                (read $ take 2 $ drop 10 d') -- Minute
> +                                (read $ take 2 $ drop 12 d') -- Second
>                                  0 Sunday 0 -- Picosecond, weekday and day of year unknown
>                                  "GMT" 0 False
>                else let dt = do { x <- date_time tz; eof; return x }
> hunk ./src/OldDate.lhs 60
> - -                   in case parse dt "" d of
> - -                      Left e -> Left $ "bad date: "++d++" - "++show e
> +                   in case parse dt "" d' of
> +                      Left e -> Left $ "bad date: " ++ d' ++ " - " ++ show e
>                        Right ct -> Right ct
>  
>  showIsoDateTime :: CalendarTime -> String
> hunk ./src/OldDate.lhs 353
>  
>  nullCalendar :: CalendarTime
>  nullCalendar = CalendarTime 0 January 0 0 0 0 1 Sunday 0 "" 0 False
> - -
> - -{- -- TODO: At some point we should convert parseDate to use ByteString; here's
> - -   -- a sketch of how to do it.
> - -
> - -import qualified Data.ByteString.Char8 as B
> - -import qualified Data.ByteString as C
> - -import Data.Word
> - -
> - --- ....
> - -
> - -isDigitWord8 :: Word8 -> Bool
> - -isDigitWord8 p = p >= 0x30 && p <= 0x39
> - -
> - -readint :: B.ByteString -> Int
> - -readint a = case (B.readInt a) of
> - -              Just (b,_) -> b
> - -              Nothing -> error "Bad parse of data"
> - -
> - -parseDate :: Int -> PackedString -> Either PackedString CalendarTime
> - -parseDate tz d =
> - -              if lengthPS d >= 14 && (C.all isDigitWord8 $ takePS 14 d)
> - -              then Right $
> - -                   CalendarTime (readint $ takePS 4 d)
> - -                                (toEnum $ (+ (-1)) $ readint $ takePS 2 $ dropPS 4 d)
> - -                                (readint $ takePS 2 $ dropPS 6 d) -- Day
> - -                                (readint $ takePS 2 $ dropPS 8 d) -- Hour
> - -                                (readint $ takePS 2 $ dropPS 10 d) -- Minute
> - -                                (readint $ takePS 2 $ dropPS 12 d) -- Second
> - -                                0 Sunday 0 -- Picosecond, weekday and day of year unknown
> - -                                "GMT" 0 False
> - -              else let dt = do { x <- date_time tz; eof; return x }
> - -                   in case parse dt "" (unpackPS d) of
> - -                      Left e -> Left $ concatPS [packString "bad date: ", d, packString " - ", packString $ show e]
> - -                      Right ct -> Right ct
> - --}
>  \end{code}
> [refactor some of parseDate in OldDate.lhs
> gwern0 at gmail.com**20080426042324] hunk ./src/OldDate.lhs 26
>  \begin{code}
>  module OldDate ( readUTCDate, showIsoDateTime ) where
>  
> +import Control.Arrow ((***))
>  import Text.ParserCombinators.Parsec
>  import System.Time
>  import Data.Char ( toUpper, isDigit )
> hunk ./src/OldDate.lhs 31
>  import Control.Monad ( liftM, liftM2 )
> - -import FastPackedString
> +import FastPackedString (PackedString, allPS, lengthPS, splitAtPS, takePS, unpackPS)
>  
>  -- | Read/interpret a date string, assuming UTC if timezone
>  --   is not specified in the string
> hunk ./src/OldDate.lhs 48
>  -- and because the only 'read' for ByteString is in the separate Data.Binary package.
>  parseDate :: Int -> PackedString -> Either String CalendarTime
>  parseDate tz d =
> - -              let d' = unpackPS d in
> - -              if lengthPS d >= 14 && (allPS isDigit $ takePS 14 d)
> - -              then
> - -                   Right $
> - -                   CalendarTime (read $ take 4 d')
> - -                                (toEnum $ (+ (-1)) $ read $ take 2 $ drop 4 d')
> - -                                (read $ take 2 $ drop 6 d') -- Day
> - -                                (read $ take 2 $ drop 8 d') -- Hour
> - -                                (read $ take 2 $ drop 10 d') -- Minute
> - -                                (read $ take 2 $ drop 12 d') -- Second
> - -                                0 Sunday 0 -- Picosecond, weekday and day of year unknown
> - -                                "GMT" 0 False
> - -              else let dt = do { x <- date_time tz; eof; return x }
> - -                   in case parse dt "" d' of
> - -                      Left e -> Left $ "bad date: " ++ d' ++ " - " ++ show e
> - -                      Right ct -> Right ct
> +              let read2 = read . take 2
> +                  (d', d'') = unpackPS *** unpackPS $ splitAtPS 4 d
> +              in
> +               if lengthPS d >= 14 && (allPS isDigit $ takePS 14 d)
> +               then Right $
> +                    CalendarTime (read d')
> +                                 (toEnum $ (+ (-1)) $ read2 d'')
> +                                 (read2 $ drop 2 d'') -- Day
> +                                 (read2 $ drop 4 d'') -- Hour
> +                                 (read2 $ drop 6 d'') -- Minute
> +                                 (read2 $ drop 8 d'') -- Second
> +                                 0 Sunday 0 -- Picosecond, weekday, and day of year unknown
> +                                 "GMT" 0 False
> +               else let dt = do { x <- date_time tz; eof; return x }
> +                    in case parse dt "" (d'++d'') of
> +                       Left   e -> Left $ "bad date: " ++ (d'++d'') ++ " - " ++ show e
> +                       Right ct -> Right ct
>  
>  showIsoDateTime :: CalendarTime -> String
>  showIsoDateTime ct = concat [ show $ ctYear ct
> 
> Context:
> 
> [remove git section from building_darcs.tex
> David Roundy <droundy at darcs.net>**20080424134245
>  Thanks to Nicolas Pouillard for pointing this out.
> ] 
> [clean up genslurp_helper a tad.
> David Roundy <droundy at darcs.net>**20080423214457
>  I'm removing an unneeded unsafeInterleaveIO and am reformatting some of the
>  indentation to make it clearer which else goes with which if.
> ] 
> [remove unneeded redundant adding of -lcurses (done by AC_SEARCH_LIBS).
> David Roundy <droundy at darcs.net>**20080423214404] 
> [Give a clear error message when no suitable haddock is installed
> tux_rocker at reinier.de**20080423172834] 
> [simplify configure a bit: if we're defining CPP symbols, no need to also use AC_SUBST.
> David Roundy <droundy at darcs.net>**20080423152121] 
> [simplify makefile a bit.
> David Roundy <droundy at darcs.net>**20080423150529] 
> [give proper error message when slurping fails to identify a file or directory.
> David Roundy <droundy at darcs.net>**20080423141737] 
> [default to not coloring hunks.
> David Roundy <droundy at darcs.net>**20080423141725] 
> [Use the lineColoring to prettify hunks with colors.
> Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080420135252] 
> [Add line coloring support in Printer and ColourPrinter.
> Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080420135238] 
> [Export Printer.(<?>).
> Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080420135208] 
> [Add two colors (cyan and magenta), but not use them yet.
> Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080420122811] 
> [Refactor a little the color handling.
> Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080420122500] 
> [slim down the makefile based on Gwern's changes to the configure script.
> David Roundy <droundy at darcs.net>**20080423131854] 
> [configure.ac: export -lcurses for cabal
> gwern0 at gmail.com**20080420221056] 
> [configure.ac: export Curses as well
> gwern0 at gmail.com**20080420214353] 
> [Little style change.
> Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080420122143] 
> [Define unDoc as field of Doc.
> Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080416075954] 
> [Replace colour by color to uniformise a bit.
> Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080416074742] 
> [Canonize G. Branwen, P. Rockai, L. Komolodin and R. Lamers.
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080422152346
>  All anonymous patches get assigned to Gwern. 
> ] 
> [doc tweak
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080422151420] 
> [resolve issue809: doc: darcs get is not lazy by default.
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080422150809] 
> [doc: darcs-2 is no longer experimental.
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080422150736] 
> [Rename ColourPrinter to ColorPrinter.
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080421154043
>  We might as well standardize on American spelling in the code.
> ] 
> [eliminate duplicate get_remote_repo in favor of list comprehensions.
> David Roundy <droundy at darcs.net>**20080421145642] 
> [resolve issue792: Account for --remote-repo in defaultrepo code
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080421144023] 
> [Extend command_argdefaults to accept [DarcsFlag].
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080421143950] 
> [Add a --remote-repodir flag (yet unused).
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080421134352] 
> [Account for pre-existing api-doc.
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080421135155] 
> [Create the api-doc dir if it does not exist.
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080421134800] 
> [replace '{-# OPTIONS' with '{-# OPTIONS_GHC'
> gwern0 at gmail.com**20080419024027
>  These OPTIONS pragmas use GHC-isms; best practice is to make them GHC specific if they are GHC specific.
>  Specifically: -fglasgow-exts is obviously GHC only. -cpp is used only by GHC AFAIK - hugs uses some hugscpp, YHC uses '--cpp' as does presumably NHC, JHC doesn't support cpp, and no idea about the others.
>  However, this patch omits modifying "src/Darcs/ColourPrinter.lhs", "src/Workaround.hs", and "src/win32/CtrlC.hs" because I was uncertain whether '-fno-warn-orphans', '-w', and '-ffi' are actually GHC-only.
> ] 
> [configure.ac: export -DHAVE_LIBWWW for CPP
> gwern0 at gmail.com**20080420213108] 
> [resolve issue795: Make 'darcs changes -i' behave more like other jobs.
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080421105247
>  
>  Old behaviour:
>   Shall I continue to view changes?
>     y - do not view this patch; keep going [DEFAULT]
>     n - quit
>     v - view this patch; keep going
>     q - quit
>  
>  New behaviour:
>    Shall I view this patch?
>     y - view this patch; keep going
>     n - do not view this patch; keep going [DEFAULT]
>     v - view this patch; keep going
>     q - quit
> ] 
> [Undo a false refactor in SelectChanges.
> Eric Kow <E.Y.Kow at brighton.ac.uk>**20080421104106
>  
>  The new old code makes it clearer that text_view is only used by
>  'view changes'
> ] 
> [Fix pluralization of patches using English module.
> David Roundy <droundy at darcs.net>**20080421121716] 
> [configure.ac: move HAVE_CURL around
> gwern0 at gmail.com**20080420220800
>  The dependency was inverted; we want to set HAVE_CURL before we test for Curl pipelining.
> ] 
> [optimized get --to-match handling for darcs 1 repositories
> tux_rocker at reinier.de**20080420152608] 
> [stringify.hs: rw to avoid multi-line string literal
> gwern0 at gmail.com**20080419025648
>  The reason we want to avoid multi-line string literals is because GHC and CPP can break them quite badly if accidentally applied.
>  In addition, no one is going to read Context.hs - it exists solely to be compiled. So removing the multi-line business in favor of one long string which will look exactly the same in the compiled binary causes no problems. And it can fix a big one - if Context.hs can't be compiled, obviously Darcs cannot.
> ] 
> [configure.ac: restructure curl
> gwern0 at gmail.com**20080419020619
>  We want to make sure HAVE_CURL shows up in CPP flags.
> ] 
> [configure.ac: +mention why threaded is not default/doc
> gwern0 at gmail.com**20080420023752] 
> [rearrange bytestring tests so if it's not present we're quieter.
> David Roundy <droundy at darcs.net>**20080418212319] 
> [configure.ac: fix bytestring checking
> gwern0 at gmail.com**20080418205704
>  This changes bytestring to be default. However it checks twice: if either --disable-bytestring is set or bytestring can't be found, it won't pass on CPP -DHAVE_BYTESTRING. So this should work for Dr. Roundy's lack of bytestring.
> ] 
> [remove unneeded check for termio.h.
> David Roundy <droundy at darcs.net>**20080417172427] 
> [configure.ac: rm line
> gwern0 at gmail.com**20080416184604
>  I can't even figure out how long ago Control.Monad was in a 'util' package.
> ] 
> [we don't need Darcs.Patch.Check for darcs itself.
> David Roundy <droundy at darcs.net>**20080417150720] 
> [remove hackish attempt to set GC parameters based on available memory.
> David Roundy <droundy at darcs.net>**20080416164105] 
> [define forM_ since it is absent on GHC 6.4.1
> zooko at zooko.com**20080409234512] 
> [make darcs build on win32 by conditionally compiling out a few bits that are unused or meaningless on win32
> zooko at zooko.com**20080410204830] 
> [Don't let other configure flags change the type witnesses
> Lennart Kolmodin <kolmodin at gentoo.org>**20080415210614
>  For example, when using --with-docs the type witnesses would be turned on,
>  while with --without-docs they would not. This patch adresses this issue.
> ] 
> [eliminate use of Haskell 98 library modules.
> David Roundy <droundy at darcs.net>**20080415214217] 
> [add type witness declarations to Resolution
> David Roundy <droundy at darcs.net>**20080415165457] 
> [move -cpp option into source files.
> David Roundy <droundy at darcs.net>**20080415144719] 
> [Issue a warning when using --old-fashioned-inventory with a darcs-2 repository.
> Nicolas Pouillard <nicolas.pouillard at gmail.com>**20080414232715] 
> [FastPackedString.hs: FastPackedString.hs: redefine linePS/unlinesPS
> gwern0 at gmail.com**20080414150839
>  Turns out that my definitions were wrong - they differed and added a newline where the old FPS versions didn't. So I've rewritten the wrapper versions around ByteString, and checked them against the old ones with QuickCheck. With these fixes, a bytestring darcs seems to pass all the tests as a fps darcs.
> ] 
> [remove unused Setup.lhs.
> David Roundy <droundy at darcs.net>**20080414190738] 
> [roll back implementation of joke oops command.
> David Roundy <droundy at darcs.net>**20080414133342
>  Apparently it didn't actually work...
>  
>  rolling back:
>  
>  Tue Apr  8 07:58:56 PDT 2008  David Roundy <droundy at darcs.net>
>    * resolve issue786:  implement oops command.
>  
>      M ./src/Darcs/Commands/Tag.lhs -5 +47
>      M ./src/Darcs/TheCommands.lhs -1 +2
> ] 
> [just remove concatLenPS
> David Roundy <droundy at darcs.net>**20080411205303
>  It is never used in a performance-critical situation, so I'm voting to just
>  trash it.  I'd rather have fewer unsafe operations.
> ] 
> [FastPackedString.hs: simplify concatLenPS, although this removes its strictness properties
> **20080411035327] 
> [FastPackedString.hs: remove wfindPS
> **20080411035046
>  With better imports from bytestring, I believe it to be superfluous, and dangerous to leave around.
> ] 
> [FastPackedString.hs: grmmr/sp
> **20080411034730] 
> [FastPackedString.hs: rw linesPS using ByteString split
> **20080411032229] 
> [doc updates
> gwern0 at gmail.com**20080409170824
>  Convert all uses of 'http://darcs.net/repos/stable' to just darcs.net, since unstable and stable were merged together, and the old URL is a 404 for darcs getting. This is a real problem, see for example <http://reddit.com/info/6ewbq/comments/c03o6d5>.
> ] 
> [fix typo in show_bug_help
> Matyas Janos <mjanos5 at gmail.com>**20080408232600] 
> [Raise a configure error when no Text.Regex module can be found.
> nicolas.pouillard at gmail.com**20080409085522] 
> [update README url links
> gwern0 at gmail.com**20080407201333] 
> [add a bit more debugging info to repository identification.
> David Roundy <droundy at darcs.net>**20080408151912] 
> [resolve issue385: don't worry if we can't get local changes.
> David Roundy <droundy at darcs.net>**20080408151823] 
> [add test for issue385.
> David Roundy <droundy at darcs.net>**20080408151808] 
> [resolve issue786:  implement oops command.
> David Roundy <droundy at darcs.net>**20080408145856] 
> [fix URL in network test.
> David Roundy <droundy at darcs.net>**20080408145407] 
> [fix manual bug.
> David Roundy <droundy at darcs.net>**20080407191736] 
> [add new show bug command (hidden) to see what darcs will report if we encounter a bug.
> David Roundy <droundy at darcs.net>**20080407175410] 
> [automatically work out the version of the stable release.
> David Roundy <droundy at darcs.net>**20080407171850] 
> [set prefs again (they got lost on convert).
> David Roundy <droundy at darcs.net>**20080407171559] 
> [update darcs repository URL.
> David Roundy <droundy at darcs.net>**20080407164601] 
> [fix up website for new release.
> David Roundy <droundy at darcs.net>**20080407164010] 
> [simplify determine_release_state.pl.
> David Roundy <droundy at darcs.net>**20080407153000] 
> [make determine_release_state.pl use changes --count.
> David Roundy <droundy at darcs.net>**20080407152347] 
> [add --count output option to changes.
> David Roundy <droundy at darcs.net>**20080407151825] 
> [TAG 2.0.0
> David Roundy <droundy at darcs.net>**20080407150638] 
> Patch bundle hash:
> 4b7825afde75b8959044e5014aa2ea96171ad35a
> -----BEGIN PGP SIGNATURE-----
> Version: GnuPG v2.0.7 (GNU/Linux)
> 
> iD8DBQFIEq5yvpDo5Pfl1oIRCjw7AJ9urgYccrWUNpoEQnf3VGz9b3CTDACfSQyf
> XQvkVf9B5Y6aJ+2B+vE7Uko=
> =YJGG
> -----END PGP SIGNATURE-----


-- 
David Roundy
Department of Physics
Oregon State University


More information about the darcs-users mailing list