darcs

Patch 479 Tighten up type in Darcs.Rollback (and 14 more)

Title Tighten up type in Darcs.Rollback (and 14 more)
Superseder Nosy List ganesh, kowey
Related Issues
Status accepted Assigned To kowey
Milestone

Created on 2010-11-23.22:55:02 by ganesh, last changed 2011-05-10.17:16:02 by darcswatch. Tracked on DarcsWatch.

Files
File name Status Uploaded Type Edit Remove
tighten-up-type-in-darcs_rollback.dpatch ganesh, 2010-11-23.22:55:01 text/x-darcs-patch
unnamed ganesh, 2010-11-23.22:55:01
See mailing list archives for discussion on individual patches.
Messages
msg13231 (view) Author: ganesh Date: 2010-11-23.22:55:01
Some simple refactorings. I think all of these should be
fairly obviously behaviour preserving given that they
compile.

15 patches for repository http://darcs.net/screened:

Sun Nov 21 15:31:25 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * Tighten up type in Darcs.Rollback

Sun Nov 21 15:31:26 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * Tighten up type of applyToWorking

Mon Nov 22 06:08:46 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * tighten up type of handlePendForAdd

Mon Nov 22 06:10:31 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * generalise type of xmlSummary
  conflictedEffect for Named has the same behaviour as for the underlying
  patch, so this should have no effect on behaviour

Mon Nov 22 06:10:49 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * Remove an unnecessary call to effect in setTentativePending

Mon Nov 22 06:10:49 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * Get rid of pointless call to effect in Darcs.Resolution

Mon Nov 22 06:18:06 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * Darcs.Patch.Apply doesn't have orphans any more

Mon Nov 22 06:18:06 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * improve name

Mon Nov 22 06:19:26 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * move pending.new reading/writing into Repository.LowLevel

Mon Nov 22 06:21:05 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * rename Darcs.Hopefully to Darcs.Patch.PatchInfoAnd
  The new name much better reflects the role of this module.
  The Hopefully type could in principle be split out back
  into a new Darcs.Hopefully module, but it's unlikely it would
  have any independent value.

Mon Nov 22 06:29:05 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * get rid of useless instance

Mon Nov 22 06:29:05 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * get rid of some spurious arguments to impossible

Mon Nov 22 06:32:09 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * simplify readPatch' for Braced

Mon Nov 22 06:42:45 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * move writePatch and gzWritePatch outside ShowPatch

Mon Nov 22 06:42:50 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
  * split a basic class out of ShowPatch that requires fewer deps
  This allows a bunch of unreachable and duplicated code to be removed
Attachments
msg13238 (view) Author: darcswatch Date: 2010-11-23.23:13:48
This patch bundle (with 15 patches) was just applied to the repository http://darcs.net/screened.
This message was brought to you by DarcsWatch
http://darcswatch.nomeata.de/repo_http:__darcs.net_screened.html#bundle-ed00940b03fcc73b2acae23eba0b4e2220b659f8
msg13312 (view) Author: kowey Date: 2010-12-10.19:08:18
I'm trying to chip away at the backlog, unfortunately only tackling the
most obvious-looking stuff for now.

On Tue, Nov 23, 2010 at 22:55:02 +0000, Ganesh Sittampalam wrote:
>   * Tighten up type in Darcs.Rollback
>   * Tighten up type of applyToWorking
>   * tighten up type of handlePendForAdd
>   * generalise type of xmlSummary
>   * Remove an unnecessary call to effect in setTentativePending
>   * Get rid of pointless call to effect in Darcs.Resolution
>   * Darcs.Patch.Apply doesn't have orphans any more
>   * improve name
>   * get rid of some spurious arguments to impossible
>   * move writePatch and gzWritePatch outside ShowPatch

I've applied these as they seem fairly straightforward

>   * simplify readPatch' for Braced
>   * move pending.new reading/writing into Repository.LowLevel
>   * rename Darcs.Hopefully to Darcs.Patch.PatchInfoAnd
>   * get rid of useless instance
>   * split a basic class out of ShowPatch that requires fewer deps

I'll hopefully work on this Saturday afternoon or if I'm too tired
Wednesday


Tighten up type in Darcs.Rollback
---------------------------------
> -rollItBackNow :: (RepoPatch p1, RepoPatch p) =>
> -                [DarcsFlag] -> Repository p1 C(r u t) ->  FL (PatchInfoAnd p) C(x y)
> +rollItBackNow :: (RepoPatch p) =>
> +                [DarcsFlag] -> Repository p C(r u t) ->  FL (PatchInfoAnd p) C(x y)

Is this just a matter of principle, not making types more general than
we have evidence that they need to be?

Or are we actively asserting that they have the same type here?

Tighten up type of applyToWorking
---------------------------------
> Ganesh Sittampalam <ganesh@earth.li>**20101121153126
> -applyToWorking :: Patchy p => Repository p1 C(r u t) -> [DarcsFlag] -> p C(u y) -> IO (Repository p1 C(r y t))
> +applyToWorking :: Repository p C(r u t) -> [DarcsFlag] -> FL Prim C(u y) -> IO (Repository p C(r y t))

tighten up type of handlePendForAdd
-----------------------------------
> -handlePendForAdd :: forall p q C(r u t x y). (RepoPatch p, Effect q)
> -                    => Repository p C(r u t) -> q C(x y) -> IO ()
> +handlePendForAdd :: forall p C(r u t x y). (RepoPatch p)
> +                    => Repository p C(r u t) -> PatchInfoAnd p C(x y) -> IO ()

Similar questions for the patches above?

generalise type of xmlSummary
-----------------------------
> -import Darcs.Patch.Named ( Named(..), patchcontents )
> +import Darcs.Patch.Named ( Named(..) )

> -xmlSummary :: (Effect p, Conflict p) => Named p C(x y) -> Doc
> +xmlSummary :: (Effect p, Conflict p) => p C(x y) -> Doc
>  xmlSummary p = text "<summary>"
> hunk ./src/Darcs/Patch/Viewing.hs 131
> -             $$ (vcat . map summChunkToXML . genSummary . conflictedEffect . patchcontents $ p)
> +             $$ (vcat . map summChunkToXML . genSummary . conflictedEffect $ p)

I'm trusting the patch summary that conflictedEffect on Named
grabs the patchcontent

Remove an unnecessary call to effect in setTentativePending
-----------------------------------------------------------
> ] hunk ./src/Darcs/Repository/Internal.hs 637
> -       setTentativePending r $ effect x
> +       setTentativePending r x

Seems like this needed a bit more studying to see that it's
unnecessary so I postponed.

Get rid of pointless call to effect in Darcs.Resolution
-------------------------------------------------------
> Ganesh Sittampalam <ganesh@earth.li>**20101122061049
> hunk ./src/Darcs/Resolution.lhs 70
>                case commute (invert p :> mp) of
> -              Just (mp' :> _) -> doml (effect p +>+ effect mp') ps
> +              Just (mp' :> _) -> doml (p +>+ mp') ps

Likewise, though I'm guessing that's because Prims are their own
effects.

Darcs.Patch.Apply doesn't have orphans any more
-----------------------------------------------
> Ganesh Sittampalam <ganesh@earth.li>**20101122061806
>  Ignore-this: 1f16110aa0724103970b586885e4bba6
> ] hunk ./src/Darcs/Patch/Apply.lhs 20
>  
>  
>  \begin{code}
> -{-# OPTIONS_GHC -fno-warn-orphans #-}


improve name
------------
> -applyToPop'
> +applyToPopPrim

Yes

---------------------------------------------------------
move pending.new reading/writing into Repository.LowLevel
rename Darcs.Hopefully to Darcs.Patch.PatchInfoAnd
get rid of useless instance
simplify readPatch' for Braced
split a basic class out of ShowPatch that requires fewer deps
---------------------------------------------------------
postponed


get rid of some spurious arguments to impossible
------------------------------------------------
> -fromNons :: [Non RealPatch C(x)] -> Maybe (Sealed (FL Prim C(x)))

> -pullInContext :: [Non RealPatch C(x)] -> Maybe (Sealed (Prim C(x)), [Non RealPatch C(x)])

> -            Nothing -> impossible pullInContext fromNons
> +            Nothing -> impossible

Heh, I wonder if this was some kind of attempt to semi-comment-out code.

move writePatch and gzWritePatch outside ShowPatch
--------------------------------------------------
> hunk ./src/Darcs/Patch/Show.lhs 71
> -    writePatch :: FilePath -> p C(x y) -> IO ()
> -    writePatch f p = writeDocBinFile f $ showPatch p <> text "\n"
> -    gzWritePatch :: FilePath -> p C(x y) -> IO ()
> -    gzWritePatch f p = gzWriteDocFile f $ showPatch p <> text "\n"

> +writePatch :: ShowPatch p => FilePath -> p C(x y) -> IO ()
> +writePatch f p = writeDocBinFile f $ showPatch p <> text "\n"
> +gzWritePatch :: ShowPatch p => FilePath -> p C(x y) -> IO ()
> +gzWritePatch f p = gzWriteDocFile f $ showPatch p <> text "\n"

I can buy that we never want to override this.

-- 
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
For a faster response, try +44 (0)1273 64 2905 or
xmpp:kowey@jabber.fr (Jabber or Google Talk only)
msg13316 (view) Author: ganesh Date: 2010-12-10.23:40:56
Hi Eric,

Thanks for the review.

On Fri, 10 Dec 2010, Eric Kow wrote:

> Tighten up type in Darcs.Rollback
> ---------------------------------
>> -rollItBackNow :: (RepoPatch p1, RepoPatch p) =>
>> -                [DarcsFlag] -> Repository p1 C(r u t) ->  FL (PatchInfoAnd p) C(x y)
>> +rollItBackNow :: (RepoPatch p) =>
>> +                [DarcsFlag] -> Repository p C(r u t) ->  FL (PatchInfoAnd p) C(x y)
>
> Is this just a matter of principle, not making types more general than
> we have evidence that they need to be?
>
> Or are we actively asserting that they have the same type here?


> Tighten up type of applyToWorking
> ---------------------------------
>> Ganesh Sittampalam <ganesh@earth.li>**20101121153126
>> -applyToWorking :: Patchy p => Repository p1 C(r u t) -> [DarcsFlag] -> p C(u y) -> IO (Repository p1 C(r y t))
>> +applyToWorking :: Repository p C(r u t) -> [DarcsFlag] -> FL Prim C(u y) -> IO (Repository p C(r y t))
>
> tighten up type of handlePendForAdd
> -----------------------------------
>> -handlePendForAdd :: forall p q C(r u t x y). (RepoPatch p, Effect q)
>> -                    => Repository p C(r u t) -> q C(x y) -> IO ()
>> +handlePendForAdd :: forall p C(r u t x y). (RepoPatch p)
>> +                    => Repository p C(r u t) -> PatchInfoAnd p C(x y) -> IO ()
>
> Similar questions for the patches above?

In all these cases, I think I ran into trouble with the more general types 
when doing the Prim abstraction work. I don't think the more general types 
actually make sense given that if you have a repository you should 
normally be working on the patch type that belongs in that repository, and 
clearly they weren't needed as the code still type checks with the more 
restricted version.

> get rid of some spurious arguments to impossible
> ------------------------------------------------
>> -fromNons :: [Non RealPatch C(x)] -> Maybe (Sealed (FL Prim C(x)))
>
>> -pullInContext :: [Non RealPatch C(x)] -> Maybe (Sealed (Prim C(x)), [Non RealPatch C(x)])
>
>> -            Nothing -> impossible pullInContext fromNons
>> +            Nothing -> impossible
>
> Heh, I wonder if this was some kind of attempt to semi-comment-out code.

Yes, that's the impression I had.

Ganesh
msg13320 (view) Author: kowey Date: 2010-12-11.18:13:13
On Tue, Nov 23, 2010 at 22:55:02 +0000, Ganesh Sittampalam wrote:
>   * Remove an unnecessary call to effect in setTentativePending
>   * Get rid of pointless call to effect in Darcs.Resolution
>   * move pending.new reading/writing into Repository.LowLevel
>   * rename Darcs.Hopefully to Darcs.Patch.PatchInfoAnd
>   * get rid of useless instance

I've pushed the part of the bundle that doesn't depend on other stuff
 
> Mon Nov 22 06:32:09 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
>   * simplify readPatch' for Braced
> 
> Mon Nov 22 06:42:50 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
>   * split a basic class out of ShowPatch that requires fewer deps
>   This allows a bunch of unreachable and duplicated code to be removed

These are waiting on patch437 and patch426 respectively

Remove an unnecessary call to effect in setTentativePending
-----------------------------------------------------------
> -       setTentativePending r $ effect x
> +       setTentativePending r x

This makes sense because effect just brings patches down to FL Prim.
x comes from readPendingFile which gives use FL Prim already.

Get rid of pointless call to effect in Darcs.Resolution
-------------------------------------------------------
> -              Just (mp' :> _) -> doml (effect p +>+ effect mp') ps
> +              Just (mp' :> _) -> doml (p +>+ mp') ps

Same thing

move pending.new reading/writing into Repository.LowLevel
---------------------------------------------------------
I assume this is just in the interest of layering, pushing
and down hiding them as needed.

> hunk ./src/Darcs/Repository/Internal.hs 323
>      do let newname = pendingName tp ++ ".new"
>         debugMessage $ "Writing new pending:  " ++ newname
>         Sealed sfp <- return $ siftForPending origp
> -       writePendingFile newname sfp
> +       writeNewPending repo sfp
>         cur <- readRecorded repo
> hunk ./src/Darcs/Repository/Internal.hs 325
> -       Sealed p <- readPendingFile newname
> +       Sealed p <- readNewPending repo

This is makeNewPending. Does it belong in LowLevel as well?

Do we care about the "pending.new" name duplication between
LowLevel and Internal? It's unlikely that we'll ever see
these things changing, just curiosity.

Low-level:

> +-- |Read the contents of tentative pending. CWD should be the repository directory.
> +readNewPending :: Repository p C(r u t) -> IO (Sealed (FL Prim C(t)))
> +readNewPending (Repo _ _ _ tp) =
> +    readPendingFile (pendingName tp ++ ".new")

> +-- |Read the contents of new pending. CWD should be the repository directory.
> +writeNewPending :: Repository p C(r u t) -> FL Prim C(t y) -> IO ()
> +writeNewPending (Repo _ _ _ tp) pend =
> +    writePendingFile (pendingName tp ++ ".new") pend

rename Darcs.Hopefully to Darcs.Patch.PatchInfoAnd
--------------------------------------------------
> Ganesh Sittampalam <ganesh@earth.li>**20101122062105
>  Ignore-this: ee6b4444dec3c021be5514b49379ec51
>  The new name much better reflects the role of this module.
>  The Hopefully type could in principle be split out back
>  into a new Darcs.Hopefully module, but it's unlikely it would
>  have any independent value.

I buy it.

> replace ./darcs.cabal [A-Za-z_0-9\-\.] Darcs.Hopefully Darcs.Patch.PatchInfoAnd
> replace ./src/Darcs/Arguments.lhs [A-Za-z_0-9\-\.] Darcs.Hopefully Darcs.Patch.PatchInfoAnd

Note that we tend to ask people to avoid '.' and '-' and replace chars
(I think for conflict avoidance)
  http://wiki.darcs.net/Development/GettingStarted

I think this happened after my attempts at using darcs replace to switch
us to System.FilePath caused a huge conflict mess.  Perhaps good to
revisit that policy and see if it still makes sense

get rid of useless instance
---------------------------
> -instance Nonable Prim where
> -    non = Non NilFL

I guess if it ghc doesn't complain, it's useless

simplify readPatch' for Braced
------------------------------
>  instance ReadPatch p => ReadPatch (Braced p) where
> -    readPatch' =
> -       do mps <- (Just <$> bracketedFL readPatch' '{' '}') <|> return Nothing
> -          case mps of
> -            Just (Sealed ps) -> return $ Sealed $ Braced ps
> -            Nothing -> mapSeal Singleton <$> readPatch'
> +    readPatch' = mapSeal Braced <$> bracketedFL readPatch' '{' '}'
> +                   <|>
> +                 mapSeal Singleton <$> readPatch'

This appears to depend on patch437;

Fri Oct 22 06:49:00 BST 2010  Ganesh Sittampalam <ganesh@earth.li>
  * don't silently throw away remaining parse input
  * drop the unused and often ignored "want eof" parameter to readPatch'
  * drop the nested Maybes in the patch parser

It may be worth mentioning that my workflow now is

1. darcs get --lazy http://darcs.net patched
2. use a tweaked
     http://code.haskell.org/darcs/darcs-team/screened.sed
   to pull -a patches from the bundle into patched
3. darcs get --lazy http://darcs.net unstable
4. cd unstable
5. my usual one-at-a-time darcs apply -i approach to review

split a basic class out of ShowPatch that requires fewer deps
-------------------------------------------------------------
This appears to depend on patch426, particularly

Sun Oct 17 16:41:31 BST 2010  Florent Becker <florent.becker@ens-lyon.org>
  * resolve issue114: allow hunk-splitting in revert

-- 
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
For a faster response, try +44 (0)1273 64 2905 or
xmpp:kowey@jabber.fr (Jabber or Google Talk only)
msg13321 (view) Author: ganesh Date: 2010-12-11.18:20:47
On Sat, 11 Dec 2010, Eric Kow wrote:

> move pending.new reading/writing into Repository.LowLevel
> ---------------------------------------------------------
> I assume this is just in the interest of layering, pushing
[...]
> This is makeNewPending. Does it belong in LowLevel as well?
>
> Do we care about the "pending.new" name duplication between
> LowLevel and Internal? It's unlikely that we'll ever see
> these things changing, just curiosity.

I think I actually move it in a later patch anyway. I can't quite 
remember why I didn't do it in this bundle, perhaps the pending.new code 
looked slightly more complicated somehow.

>> replace ./darcs.cabal [A-Za-z_0-9\-\.] Darcs.Hopefully Darcs.Patch.PatchInfoAnd
>> replace ./src/Darcs/Arguments.lhs [A-Za-z_0-9\-\.] Darcs.Hopefully Darcs.Patch.PatchInfoAnd
>
> Note that we tend to ask people to avoid '.' and '-' and replace chars
> (I think for conflict avoidance)
>  http://wiki.darcs.net/Development/GettingStarted

> I think this happened after my attempts at using darcs replace to switch
> us to System.FilePath caused a huge conflict mess.  Perhaps good to
> revisit that policy and see if it still makes sense

Yeah. I did avoid them the last time I did module renames and it hurt me 
quite a bit when trying to keep up to date with main. I think the main 
problem comes when you end up with conflicting with someone else's 
replace. I'm still ambivalent on the right thing to do, and sorry if this 
one causes problems.

Ganesh
msg13480 (view) Author: kowey Date: 2011-01-07.16:28:17
I'd neglected to review this last patch because it depended on patch426,
which was a pretty foolish on my part.

I'll try to push this in, dependencies permitting.
Chatter only below.

Random aside about workflow
---------------------------
As I review these patches, I like to describe the gradual evolution of
my workflow as I slowly figure out how to use screened/patch-tracker
more effectively.  I'm not writing it up properly because it keeps
changing.  Hopefully it'll settle down...

First change is that I should review for understanding first, and worry
about the dependencies later.  Second, since I seem to like reviewing
against context, I made an alias to make it more convenient:

   cd /tmp/patch479
   darcs-context ../tighten-up-type-in-darcs_rollback.dpatch
   # does darcs get http://darcs.net/screened --lazy --context tighten
   cd tighten
   darcs apply -i ../../tighten-up-type-in-darcs_rollback.dpatch
   darcs-gdiff --last=1

To grab my aliases,

   darcs get http://code.haskell.org/darcs/darcs-team

> Mon Nov 22 06:42:50 GMT 2010  Ganesh Sittampalam <ganesh@earth.li>
>   * split a basic class out of ShowPatch that requires fewer deps
>   This allows a bunch of unreachable and duplicated code to be removed

split a basic class out of ShowPatch that requires fewer deps
-------------------------------------------------------------
> hunk ./src/Darcs/Patch/Show.lhs 23
> -class ShowPatch p where
> +class ShowPatchBasic p where
>      showPatch :: p C(x y) -> Doc
> hunk ./src/Darcs/Patch/Show.lhs 59
> +
> +class ShowPatchBasic p => ShowPatch p where
>      showNicely :: p C(x y) -> Doc
>      showNicely = showPatch
>      -- | showContextPatch is used to add context to a patch, as diff

Here's the bulk of our patch.  We're splitting ShowPatch into
ShowPatchBasic which provides showPatch and ShowPatch which does all the
fancy stuff and requires more typeclass deps in practice.  This makes it
easier for Braced, which only needs the basic stuff

The patch only looks big, but basically here's what's going on.

  type          Basic  Fancy
  -------       -----  -----
  Prim          X      X
  Named p       X      X
  FL/RL p       X      X
  PatchInfoAnd  X      X
  Patch (V1)    X      X
  Real  (V2)    X      X
  FLM           X            (no braced around singletons)
  Braced p      X
  --------      -----  -----

I've snipped the rest

> hunk ./src/Darcs/Patch/Show.lhs 79
> -writePatch :: ShowPatch p => FilePath -> p C(x y) -> IO ()
> +writePatch :: ShowPatchBasic p => FilePath -> p C(x y) -> IO ()
> hunk ./src/Darcs/Patch/Show.lhs 81
> -gzWritePatch :: ShowPatch p => FilePath -> p C(x y) -> IO ()
> +gzWritePatch :: ShowPatchBasic p => FilePath -> p C(x y) -> IO ()

Not everything needs the full ShowPatch

> hunk ./src/Darcs/Patch/Viewing.hs 258
> -instance (Apply p, Conflict p, PatchListFormat p, ShowPatch p) => ShowPatch (Named p) where
> +instance (PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (Named p) where

ShowPatchBasic instance for Named p has simpler requirements but
ShowPatch requirements are still tricky.

> hunk ./src/Darcs/Patch/Braced/Instances.hs 13
> -instance MyEq (Braced p) where
> -    unsafeCompare = impossible
> -
> -instance Apply (Braced p) where
> -    apply = impossible
> -
> -instance Conflict (Braced p) where
> -    listConflictedFiles = impossible
> -    resolveConflicts = impossible
> -    commuteNoConflicts = impossible
> -    conflictedEffect = impossible
> -    isInconsistent = impossible
> -
> -instance Effect (Braced p) where
> -    effect = impossible
> -
> -instance Commute (Braced p) where
> -    commute = impossible
> -
> -instance Invert (Braced p) where
> -    invert = impossible
> -    identity = impossible
> -
> -instance ShowPatch p => ShowPatch (Braced p) where
> +instance ShowPatchBasic p => ShowPatchBasic (Braced p) where
>      showPatch (Singleton p) = showPatch p
>      showPatch (Braced NilFL) = blueText "{" $$ blueText "}"
>      showPatch (Braced ps) = blueText "{" $$ vcat (mapFL showPatch ps) $$ blueText "}"

Here's why we're doing this.

> -hashBundle :: RepoPatch p => [PatchInfo] -> FL (Named p) C(x y) -> String
> +hashBundle :: (PatchListFormat p, ShowPatchBasic p) => [PatchInfo] -> FL (Named p) C(x y) -> String
>  hashBundle _ to_be_sent = sha1PS $ renderPS
>                           $ vcat (mapFL showPatch to_be_sent) <> newline
>  
> hunk ./src/Darcs/Patch/Bundle.hs 64
> -hashBundleBraced :: RepoPatch p => [PatchInfo] -> FL (Named (Braced p)) C(x y) -> String
> -hashBundleBraced _ to_be_sent = sha1PS $ renderPS
> -                         $ vcat (mapFL showPatch to_be_sent) <> newline

And here's another reason.  We didn't have a single hashBundle that
takes ShowPatch because implementing ShowPatch for Braced would have
been a pain.

> hunk ./src/Darcs/Repository/LowLevel.hs 80
>  instance ReadPatch p => ReadPatch (FLM p) where
>     readPatch' = mapSeal FLM <$> readMaybeBracketedFL readPatch' '{' '}'
>  
> -instance ShowPatch p => ShowPatch (FLM p) where
> +instance ShowPatchBasic p => ShowPatchBasic (FLM p) where
>     showPatch = showMaybeBracketedFL showPatch '{' '}' . unFLM
>  
>  readPendingContents :: BS.ByteString -> Sealed (FL Prim C(x))

And another reason.

-- 
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
For a faster response, try +44 (0)1273 64 2905 or
xmpp:kowey@jabber.fr (Jabber or Google Talk only)
msg13483 (view) Author: darcswatch Date: 2011-01-07.18:05:50
This patch bundle (with 15 patches) was just applied to the repository http://darcs.net/.
This message was brought to you by DarcsWatch
http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-ed00940b03fcc73b2acae23eba0b4e2220b659f8
msg14046 (view) Author: darcswatch Date: 2011-05-10.17:16:02
This patch bundle (with 15 patches) was just applied to the repository http://darcs.net/reviewed.
This message was brought to you by DarcsWatch
http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-ed00940b03fcc73b2acae23eba0b4e2220b659f8
History
Date User Action Args
2010-11-23 22:55:02ganeshcreate
2010-11-23 22:55:54darcswatchsetdarcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-ed00940b03fcc73b2acae23eba0b4e2220b659f8
2010-11-23 23:13:48darcswatchsetstatus: needs-screening -> needs-review
messages: + msg13238
2010-12-10 17:42:04koweysetstatus: needs-review -> review-in-progress
assignedto: kowey
nosy: + kowey
2010-12-10 19:08:19koweysetmessages: + msg13312
2010-12-10 23:40:56ganeshsetmessages: + msg13316
2010-12-11 18:13:14koweysetmessages: + msg13320
2010-12-11 18:20:47ganeshsetmessages: + msg13321
2011-01-07 16:28:18koweysetmessages: + msg13480
2011-01-07 17:28:30koweysetstatus: review-in-progress -> accepted-pending-tests
2011-01-07 18:05:50darcswatchsetstatus: accepted-pending-tests -> accepted
messages: + msg13483
2011-05-10 17:16:02darcswatchsetmessages: + msg14046