[darcs-users] [patch422] remove unused exports (and 11 more)

Florent Becker bugs at darcs.net
Thu Nov 11 12:16:29 UTC 2010


Florent Becker <florent.becker at ens-lyon.org> added the comment:

Thanks for the (austral) spring cleaning, applying.

remove unused exports
---------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017113320

hunk ./src/Lcs.hs 44
>  -- The last step tries to create longer changed regions and line up 
deletions
>  -- in the first file to insertions in the second by shifting changed 
lines
>  -- forward and backward.
> -module Lcs ( getChanges, aLen,
> -             BArray, PArray, BSTArray,
> +module Lcs ( getChanges,
>               shiftBoundaries ) where
>  
>  import Control.Monad

Ok

drop unused verboseMode global
------------------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017113325

[snip]

Unused indeed

clean up some dead code in Darcs.Patch
--------------------------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017113941

dead code removal, except:

hunk ./src/Darcs/Patch/V2/Non.hs 180
>            adj NilRL n = Just n
>            adj (x:<:xs) n = fromPrim x >* n >>= adj xs
>  
> +-- TODO why don't any tests run this?
>  propAdjustTwice :: (Patchy p, ToFromPrim p) => p C(x y) -> Non p C(y) 
-> Maybe Doc
>  propAdjustTwice p n =
>      do n' <- p >* n

This is a little bit of a rider, but well… 
Also, what does propAdjustTwice do?


remove dead code from Darcs.Utils
---------------------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017114050

ok, dead code indeed

drop unused flag
----------------
Ganesh Sittampalam <ganesh at earth.li>**20101017114053

Great, at least we get rid of that flag. For how long has it been a dud?


explicit exports/imports for Darcs.Repository.Merge
---------------------------------------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017114055

hunk ./src/Darcs/Commands/Pull.lhs 51
>                            finalizeRepositoryChanges, applyToWorking,
>                            readRepo, checkUnrelatedRepos, 
invalidateIndex, modifyCache, modifyCache,  Cache(..), CacheLoc(..), 
WritableOrNot(..))
>  import qualified Darcs.Repository.Cache as DarcsCache
> -import Darcs.Repository.Merge
> +import Darcs.Repository.Merge ( tentativelyMergePatches )
>  import Darcs.Hopefully ( info, hopefully, patchDesc )
>  import Darcs.Patch ( RepoPatch, description )
>  import Darcs.Patch.Bundle( makeBundleN, patchFilename )

ok

hunk ./src/Darcs/Repository/Merge.hs 22
>  
>  #include "gadts.h"
>  
> -module Darcs.Repository.Merge where
> +module Darcs.Repository.Merge ( tentativelyMergePatches, 
considerMergeToWorking ) where
>  
>  import Darcs.Resolution ( standardResolution, externalResolution )
>  import Darcs.External ( backupByCopying )

ok

explicit import of Darcs.Test.Patch.Test
----------------------------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017114148

hunk ./src/Darcs/Test/Unit.lhs 56
>  import Darcs.Patch
>  import Darcs.Patch.Prim ( FromPrim )
>  import Darcs.Patch.V1 ( Patch )
> -import Darcs.Test.Patch.Test hiding ( quickmerge )
> +import Darcs.Test.Patch.Test
> +    ( checkAPatch
> +    , subcommutesInverse, subcommutesNontrivialInverse, 
subcommutesFailure
> +    , propReadShow, propCommuteInverse, propPatchAndInverseIsIdentity
> +    , propSimpleSmartMergeGoodEnough, propCommuteEquivalency
> +    , propMergeValid, propInverseValid, propOtherInverseValid
> +    , propInverseComposition, propCommuteTwice
> +    , propCommuteEitherOrder, propCommuteEitherWay
> +    , propMergeIsCommutableAndCorrect, propMergeIsSwapable
> +    )
>  import Darcs.Test.Patch.Unit ( patchUnitTests )
>  import Darcs.Test.Email ( emailParsing, emailHeaderNoLongLines,
>                            emailHeaderAsciiChars, 
emailHeaderLinesStart,

ok

remove some dead code in Darcs.Repository
-----------------------------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017114358

hunk ./src/Darcs/Repository/Checkpoint.hs 22
>  
>  #include "gadts.h"
>  
> -module Darcs.Repository.Checkpoint ( getCheckpoint, 
getCheckpointByDefault,
> +module Darcs.Repository.Checkpoint ( getCheckpoint,
>                                       identifyCheckpoint,
>                                       writeCheckpointPatch,
>                                     ) where

ok, we get rid of getCheckpointByDefault. All checkpoints are going to
die soon, anyway.

hunk ./src/Darcs/Repository/Checkpoint.hs 42
>                            showPatchInfo, readPatchInfos )
>  import Darcs.Patch.Set( PatchSet(..), Tagged(..) )
>  import Darcs.External ( gzFetchFilePS, fetchFilePS, Cachable(..) )
> -import Darcs.Flags ( DarcsFlag( Partial, Complete ) )
> +import Darcs.Flags ( DarcsFlag( Partial ) )
>  import Darcs.Utils ( catchall )
>  import Darcs.Global ( darcsdir )
>  import Printer ( Doc, ($$), empty )

ok

hunk ./src/Darcs/Repository/Checkpoint.hs 54
>                                                then getCheckInternal 
repository
>                                                else return Nothing
>  
> -getCheckpointByDefault :: RepoPatch p => Repository p C(r u t) -> IO 
(Maybe (Sealed (Named p C(x))))
> -getCheckpointByDefault repository@(Repo _ opts _ _) = if Complete 
`elem` opts
> -                                                         then return 
Nothing
> -                                                         else 
getCheckInternal repository
> -
>  identifyCheckpoint :: RepoPatch p => Repository p C(r u t) -> IO 
(Maybe PatchInfo)
>  identifyCheckpoint repository@(Repo r _ _ _) = do
>    pis <- (map sp2i . extractTags) `liftM` readRepo repository

ok

hunk ./src/Darcs/Repository/DarcsRepo.lhs 53
>  #include "gadts.h"
>  
>  module Darcs.Repository.DarcsRepo ( writeInventory, 
writeInventoryAndPatches,
> -                                    addToInventory, 
addToTentativePristine,
> +                                    addToTentativePristine,
>                                      addToTentativeInventory, 
removeFromTentativeInventory,
>                                      finalizeTentativeChanges, 
finalizePristineChanges,
>                                      revertTentativeChanges,

Remove addToInventory. I gather it's done automatically through
addToTentative* and finalizeTentativeChanges.

hunk ./src/Darcs/Repository/DarcsRepo.lhs 181
>  writeInventoryAndPatches compr ps =   do writeInventory "." ps
>                                           sequence_ $ mapRL 
(writePatch compr . hopefully) $ newset2RL ps
>  
> -addToInventory :: FilePath -> [PatchInfo] -> IO ()
> -addToInventory dir pinfos =
> -    appendDocBinFile (dir++"/"++darcsdir++"/inventory") $ text "\n" 
<> pidocs pinfos
> -    where
> -        pidocs [] = text ""
> -        pidocs (p:ps) = showPatchInfo p $$ pidocs ps
> -
>  addToTentativeInventory :: forall p C(x y). RepoPatch p => 
Compression -> Named p C(x y) -> IO FilePath
>  addToTentativeInventory compr p =
>      do appendDocBinFile (darcsdir++"/tentative_inventory") $ text 
"\n"

as above

hunk ./src/Darcs/Repository/Format.hs 10
>  module Darcs.Repository.Format ( RepoFormat(..), RepoProperty(..), 
identifyRepoFormat,
>                      createRepoFormat, writeRepoFormat,
>                      writeProblem, readProblem, 
readfromAndWritetoProblem,
> -                    formatHas, formatHasTogether,
> +                    formatHas,
>                    ) where
>  

Never used anyway

hunk ./src/Darcs/Repository/Format.hs 13
> -import Data.List ( sort )
>  import Data.Maybe ( isJust, catMaybes )
>  import Control.Monad ( msum )
>  

hunk ./src/Darcs/Repository/Format.hs 148
>  formatHas :: RepoProperty -> RepoFormat -> Bool
>  formatHas f (RF ks) = rp2ps f `elem` concat ks
>  
> -formatHasTogether :: [RepoProperty] -> RepoFormat -> Bool
> -formatHasTogether fs (RF ks) = fht (sort $ map rp2ps fs) ks
> -    where fht _ [] = False
> -          fht x (y:ys) | x == sort y = True
> -                       | otherwise = fht x ys
> -
>  rp2ps :: RepoProperty -> B.ByteString
>  rp2ps Darcs1_0 = BC.pack "darcs-1.0"
>  rp2ps Darcs2 = BC.pack "darcs-2"

ok

hunk ./src/Darcs/Repository/Internal.hs 24
>  #include "gadts.h"
>  
>  module Darcs.Repository.Internal ( Repository(..), RepoType(..), 
RIO(unsafeUnRIO), ($-),
> -                    maybeIdentifyRepository, 
identifyDarcs1Repository, identifyRepositoryFor,
> +                    maybeIdentifyRepository, identifyRepositoryFor,
>                      IdentifyRepo(..),
>                      findRepository, amInRepository, 
amNotInRepository,
>                      revertRepositoryChanges,

I think I have reexported identifyDarcs1Repository as
identifyDarcsRepository in a later patch (issue1978)…

hunk ./src/Darcs/Repository/Internal.hs 44
>                      createPristineDirectoryTree, 
createPartialsPristineDirectoryTree,
>                      optimizeInventory, cleanRepository,
>                      getMarkedupFile,
> -                    PatchSet, SealedPatchSet,
>                      setScriptsExecutable, 
setScriptsExecutablePatches,
>                      getRepository, rIO,
>                      testTentative, testRecorded,

No point in reexporting these.

drop some dead exports/code from ByteStringUtils
------------------------------------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017114402

Ok

[snip]


explicit import list from Printer
---------------------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017114403

ok

hunk ./src/Darcs/RemoteApply.hs 13
>  import Darcs.URL ( isUrl, isSsh )
>  import Darcs.External
>  import qualified Ssh( remoteDarcs )
> -import Printer
> +import Printer ( Doc )
>  
>  remoteApply :: [DarcsFlag] -> String -> Doc -> IO ExitCode
>  remoteApply opts repodir bundle


add some explicit export lists in Darcs.Commands
------------------------------------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017114405

that should be import lists… otherwise, ok

[snip]

make sure all of Darcs.Patch is imported with explicit import lists
-------------------------------------------------------------------
Ganesh Sittampalam <ganesh at earth.li>**20101017115317

ok

[snip]

----------
status: review-in-progress -> accepted-pending-tests

__________________________________
Darcs bug tracker <bugs at darcs.net>
<http://bugs.darcs.net/patch422>
__________________________________


More information about the darcs-users mailing list