Issues, issues, issues...

Francesco Ariis fa-ml at ariis.it
Thu Jun 25 16:32:14 UTC 2015


On Thu, Jun 25, 2015 at 05:55:47PM +0200, Bardur Arantsson wrote:
> I noticed another thing while perusing the source code: There seem to be
> quite a few TODO comments scattered about.
> 
> Is there some sort of convention whereby it is permitted to add TODOs as
> long as the person doing so pinkie-promises to fix/remove them later? Or
> is it somehow related to severity? Or is it just that people couldn't be
> bothered to make issues and just have them in out-of-band instead? Is it
> all just legacy from before issue tracking was introduced? Do people
> spontaneously clean up TODOs that others have left behind?

I recently released a little something [1] to scan for TODOs in a
codebase (after being overwhelmed by them), so after your comment
I felt compelled to see how cabal and its repo would fare!

I attach the output: there are a lot of todos but the number more or less
on the same level with projects of similar complexity. I guess it is
inevitable.

[1] http://hackage.haskell.org/package/lentil
-------------- next part --------------
Cabal/Distribution/Compat/TempFile.hs
    40  Not sure about JHC
    41  This file should probably be removed.
    80  We want to tell fdToHandle what the file path is, as any exceptions
        etc will only be able to report the FD currently
    89  bits copied from System.FilePath [fixme]
    96  Should use System.FilePath library [fixme]
   104  Copied from GHC.Handle [fixme]
 
Cabal/Distribution/Compiler.hs
    92  In some future release, remove 'parseCompilerFlavorCompat' and use
        ordinary 'parse'. Also add ("nhc", NHC) to the above 'compilerMap'.
 
Cabal/Distribution/License.hs
    66  * remove BSD4
 
Cabal/Distribution/PackageDescription.hs
   356  dedupe?
   547  By having a 'testEnabled' field in the PackageDescription, we are
        mixing build status information (i.e., arguments to 'configure')
        with static package description information. This is undesirable,
        but a better solution is waiting on the next overhaul to the
        GenericPackageDescription -> PackageDescription resolution process.
   688  See TODO for 'testEnabled'.
   921  many of the places where this is used, we actually want to look at
        unbuildable bits too, probably need separate functions [fixme]
  1141  make PackageDescription an instance of Text.
 
Cabal/Distribution/PackageDescription/Check.hs
   162  make this variant go away we should always know the
        GenericPackageDescription
   202  check for name clashes case insensitively: windows file systems
        cannot cope.
   466  recommend the bug reports URL, author and homepage fields
   467  recommend not using the stability field
   468  recommend specifying a source repo
   597  check location looks like a URL for some repo types.
   876  check sets of paths that would be interpreted differently between
        Unix and windows, ie case-sensitive or insensitive. Things that
        might clash, or conversely be distinguished.
   880  use the tar path checks on all the above paths
  1145  If the user writes build-depends: foo with (), this is
        indistinguishable from build-depends: foo, so there won't be an
        error even though there should be [xxx]
  1285  What we really want to do is test if there exists any configuration
        in which the base version is unbounded above. However that's a bit
        tricky because there are many possible configurations. As a cheap
        easy and safe approximation we will pick a single "typical"
        configuration and check if that has an open upper bound. To get a
        typical configuration we finalise using no package index and the
        current platform.
 
Cabal/Distribution/PackageDescription/Configuration.hs
   115  treat Nothing as unknown, rather than empty list once we support
        partial resolution of system parameters [fixme]
   123  Add instances and check
   207  The current algorithm is rather naive. A better approach would be
        to:
   495  we need to find a way to avoid pulling in deps for non-buildable
        components. However cannot simply filter at this stage, since if
        the package were not available we would have failed already.
   550  One particularly tricky case is defaulting. In the original package
        description, e.g., the source directory might either be the default
        or a certain, explicitly set path. Since defaults are filled in
        only after the package has been resolved and when no explicit value
        has been set, the default path will be missing from the package
        description returned by this function.
 
Cabal/Distribution/PackageDescription/Parse.hs
   681  this should take a ByteString, not a String. We have to be able to
        decode UTF8 and handle the BOM. [fixme]
  1228  make this use section syntax add equivalent for
        GenericPackageDescription
 
Cabal/Distribution/PackageDescription/PrettyPrint.hs
    80  this is a temporary hack. Ideally, fields containing default values
        would be filtered out when the @FieldDescr a@ list is generated.
   228  this ends up printing trailing spaces when combined with nest.
 
Cabal/Distribution/ParseUtils.hs
   125  what is this double parse thing all about? Can't we just do the all
        isSpace test the first time?
   251  this is a bit smelly hack. It's because we want to parse bool
        fields liberally but not accept new parses. We cannot do that with
        ReadP because it does not support warnings. We need a new parser
        framework!
 
Cabal/Distribution/Simple.hs
   402  should we write the modified package descr back to the
        localbuildinfo?
 
Cabal/Distribution/Simple/Bench.hs
   115  This is abusing the notion of a 'PathTemplate'. The result isn't
        necessarily a path.
 
Cabal/Distribution/Simple/Build.hs
   521  build separate libs in separate dirs so that we can build multiple
        libs, e.g. for 'LibTest' library-style test suites
 
Cabal/Distribution/Simple/BuildPaths.hs
   102  This should be determined via autoconf (AC_EXEEXT) | Extension for
        executable files (typically @\"\"@ on Unix and @\"exe\"@ on Windows
        or OS\/2)
   110  This should be determined via autoconf (AC_OBJEXT) | Extension for
        object files. For GHC the extension is @\"o\"@.
 
Cabal/Distribution/Simple/Command.hs
   585  eliminate this function and turn it into a variant on
        commandAddAction instead like commandAddActionNoArgs that doesn't
        supply the [String]
 
Cabal/Distribution/Simple/Configure.hs
   372  should use a per-compiler method to map the source package ID into
        an installed package id we can use for the internal package set.
        The open-codes use of InstalledPackageId . display here is a hack.
   400  mention '--exact-configuration' in the error message when this
        fails?
   544  Do we need the internal deps? NB: does *not* include holeDeps!
        [xxx]
   944  we don't check that all dependencies are used!
  1023  internal dependencies (e.g. the test package depending on the main
        library) is not currently supported
  1429  Refine this check for signatures
  1474  produce a log file from the compiler errors, if any.
  1539  do we also need dependent packages' ld options?
 
Cabal/Distribution/Simple/GHC.hs
   461  do we need to put hs-boot files into place for mutually recursive
        modules?
   572  problem here is we need the .c files built first, so we can load
        them with ghci, but .c files can depend on .h files generated by
        ghc by ffi exports.
   729  do we need to put hs-boot files into place for mutually recursive
        modules? FIX: what about exeName.hi-boot?
   869  problem here is we need the .c files built first, so we can load
        them with ghci, but .c files can depend on .h files generated by
        ghc by ffi exports.
 
Cabal/Distribution/Simple/GHC/Internal.hs
   220  should be using --supported-languages rather than hard coding
   400  perhaps override?
 
Cabal/Distribution/Simple/GHCJS.hs
   344  do we need to put hs-boot files into place for mutually recursive
        modules?
   454  problem here is we need the .c files built first, so we can load
        them with ghci, but .c files can depend on .h files generated by
        ghc by ffi exports.
   572  do we need to put hs-boot files into place for mutually recursive
        modules? FIX: what about exeName.hi-boot?
   705  problem here is we need the .c files built first, so we can load
        them with ghci, but .c files can depend on .h files generated by
        ghc by ffi exports.
 
Cabal/Distribution/Simple/Haddock.hs
   713  these should be moved elsewhere.
 
Cabal/Distribution/Simple/Install.hs
    74  decide if we need the user to be able to control the libdir for
        shared libs independently of the one for static libs. If so it
        should also have a flag in the command line UI For the moment use
        dynlibdir = libdir
 
Cabal/Distribution/Simple/LHC.hs
   211  does lhc support -XHaskell98 flag? from what version? [fixme]
   343  do we need to put hs-boot files into place for mutually recursive
        modules?
   470  discover this at configure time or runtime on Unix The value is 32k
        on Windows and POSIX specifies a minimum of 4k but all sensible
        Unixes use more than 4k. we could use getSysVar ArgumentLimit but
        that's in the Unix lib
   508  do we need to put hs-boot files into place for mutually recursive
        modules? FIX: what about exeName.hi-boot?
 
Cabal/Distribution/Simple/LocalBuildInfo.hs
   113  inplaceDirTemplates :: InstallDirs FilePath
   159  what about non-buildable components?
 
Cabal/Distribution/Simple/PackageIndex.hs
   119  Clarify what "preference order" means. Check that this invariant is
        preserved. See #1463 for discussion. [fixme]
 
Cabal/Distribution/Simple/PreProcess.hs
   125  deal with pre-processors that have implementaion dependent output
        eg alex and happy have --ghc flags. However we can't really inlcude
        ghc-specific code into supposedly portable source tarballs.
   227  try to list all the modules that could not be found not just the
        first one. It's annoying and slow due to the need to reconfigure
        after editing the .cabal file each time.
   274  eliminate sdist variant, just supply different handlers
   295  This is a somewhat nasty hack. GHC requires that hs-boot files be
        in the same place as the hs files, so if we put the hs file in
        dist/ then we need to copy the hs-boot file there too. This should
        probably be done another way. Possibly we should also be looking
        for .lhs-boot files, but I think that preprocessors only produce
        .hs files. [fixme]
   498  install .chi files for packages, so we can --include those dirs
        here, for the dependencies
   513  perhaps use this with hsc2hs too
   514  remove cc-options from cpphs for cabal-version: >= 1.10
   551  move this into the compiler abstraction
   552  this forces GHC's crazy 4.8.2 -> 408 convention on all the other
        compilers. Check if that's really what they want. [fixme]
 
Cabal/Distribution/Simple/Program/HcPkg.hs
   180  this could be a lot faster. We're doing normaliseLineEndings twice
        and converting back and forth with lines/unlines.
   241  use a proper named function for the conversion from source package
        id to installed package id
 
Cabal/Distribution/Simple/Program/Run.hs
   251  discover this at configure time or runtime on unix The value is 32k
        on Windows and posix specifies a minimum of 4k but all sensible
        unixes use more than 4k. we could use getSysVar ArgumentLimit but
        that's in the unix lib [fixme]
 
Cabal/Distribution/Simple/Register.hs
   129  there's really no guarantee this will work. registering into a
        totally different db stack can fail if dependencies cannot be
        satisfied. [fixme]
   166  eliminate pwd!
   169  the method of setting the InstalledPackageId is compiler specific
        this aspect should be delegated to a per-compiler helper.
 
Cabal/Distribution/Simple/Setup.hs
   112  Not sure where this should live [fixme]
   274  the configPrograms is only here to pass info through to configure
        because the type of configure is constrained by the UserHooks. when
        we change UserHooks next we should pass the initial
        ProgramConfiguration directly and not via ConfigFlags ^All programs
        that cabal may run [fixme]
   359  reverse this
  1519  this one should not be here, it's just that the silly UserHooks
        stop us from passing extra info in other ways
  1554  re-enable once we have support for module/file targets ++ " " ++
        pname ++ " build Foo.Bar " ++ " A module\n" ++ " " ++ pname ++ "
        build Foo/Bar.hs" ++ " A file\n\n" ++ "If a target is ambiguous it
        can be qualified with the component " ++ "name, e.g.\n" ++ " " ++
        pname ++ " build foo:Foo.Bar\n" ++ " " ++ pname ++ " build
        testsuite1:Foo/Bar.hs\n"
  1687  re-enable once we have support for module/file targets ++ " " ++
        pname ++ " repl Foo.Bar " ++ " A module\n" ++ " " ++ pname ++ "
        repl Foo/Bar.hs" ++ " A file\n\n" ++ "If a target is ambiguous it
        can be qualified with the component " ++ "name, e.g.\n" ++ " " ++
        pname ++ " repl foo:Foo.Bar\n" ++ " " ++ pname ++ " repl
        testsuite1:Foo/Bar.hs\n"
  1744  do we need this instance?
  1756  think about if/how options are passed to test exes
  2128  kill off thic bc hack when defaultUserHooks is removed.
 
Cabal/Distribution/Simple/Test/ExeV10.hs
   155  This is abusing the notion of a 'PathTemplate'. The result isn't
        necessarily a path.
 
Cabal/Distribution/Simple/Test/LibV09.hs
   159  This is abusing the notion of a 'PathTemplate'. The result isn't
        necessarily a path.
 
Cabal/Distribution/Simple/UHC.hs
   114  determine in some other way
   139  Actually make use of the information provided in the file.
 
Cabal/Distribution/Simple/Utils.hs
   497  handle exceptions like text decoding.
   509  this probably fails if the process refuses to consume or if it
        closes stdin (eg if it exits)
 
Cabal/Distribution/System.hs
   197  probably should disallow starting with a number
 
Cabal/Distribution/Version.hs
    93  maybe move this to Distribution.Package.Version? (package-specific
        versioning scheme).
 
Cabal/tests/PackageTests/PackageTester.hs
   312  Convert to a "-v" flag instead.
 
Cabal/tests/PackageTests/ReexportedModules/Check.hs
    23  Turn this into a utility function
 
Cabal/tests/Test/Distribution/Version.hs
   311  see equivalentVersionRange for details [fixme]
   557  this is wrong. consider version ranges "<=1" and "<1.0" this
        algorithm cannot distinguish them because there is no version that
        is included by one that is excluded by the other. Alternatively we
        must reconsider the semantics of '<' and '<=' in version ranges /
        version intervals. Perhaps the canonical representation should use
        just < v and interpret "<= v" as "< v.0". [fixme]
 
cabal-install/Distribution/Client/BuildReports/Anonymous.hs
   194  this does not allow for optional or repeated fields [fixme]
 
cabal-install/Distribution/Client/BuildReports/Storage.hs
    63  make this concurrency safe, either lock the report file or make
        sure the writes for each report are atomic (under 4k and flush at
        boundaries)
    88  make this concurrency safe, either lock the report file or make
        sure the writes for each report are atomic
   103  In principle, we can support $pkgkey, but only if the configure
        step succeeds. So add a Maybe field to the build report, and either
        use that or make up a fake identifier if it's not available.
 
cabal-install/Distribution/Client/BuildReports/Upload.hs
    71  do something if the request fails [fixme]
 
cabal-install/Distribution/Client/Check.hs
    36  this may give more warnings than it should give; consider two
        branches of a condition, one saying ghc-options: -Wall and the
        other ghc-options: -Werror joined into ghc-options: -Wall -Werror
        checkPackages will yield a warning on the last line, but it would
        not on each individual branch. Hovever, this is the same way
        hackage does it, so we will yield the exact same errors as it will.
 
cabal-install/Distribution/Client/Compat/Time.hs
   104  What if the result is not representable as POSIX seconds? Probably
        fine to return garbage.
 
cabal-install/Distribution/Client/Config.hs
   253  NubListify
   255  NubListify
   267  NubListify
   278  NubListify
   280  NubListify
   285  NubListify
   291  NubListify
   293  NubListify
   296  NubListify
   313  NubListify
   315  NubListify
   351  NubListify
   353  NubListify
   450  misleading, there's no way to override this default either make it
        possible or rename to simply getCabalDir.
   610  this is only here because viewAsFieldDescr gives us a parser that
        only recognises 'ghc' etc, the case-sensitive flag names, not what
        the normal case-insensitive parser gives us. [fixme]
   616  The following is a temporary fix. The "optimization" and
        "debug-info" fields are OptArg, and viewAsFieldDescr fails on that.
        Instead of a hand-written hackaged parser and printer, we should
        handle this case properly in the library.
   682  this is a hack, hiding the user name and password. But otherwise it
        masks the upload ones. Either need to share the options or make
        then distinct. In any case they should probably be per-server.
        [fixme]
   697  next step, make the deprecated fields elicit a warning.
 
cabal-install/Distribution/Client/Configure.hs
   256  should warn or error on constraints that are not on direct deps or
        flag constraints not on the package in question.
 
cabal-install/Distribution/Client/Dependency.hs
   264  the top down resolver chokes on the base constraints below when
        there are no targets and thus no dep on base. Need to refactor
        constraints separate from needing packages.
   284  this should work using exclude constraints instead
   295  this should work using exclude constraints instead
   305  this should work using exclude constraints instead
   498  warn about unsupported options
   513  is this needed here? see dontUpgradeNonUpgradeablePackages
 
cabal-install/Distribution/Client/Dependency/Modular/Assignment.hs
    74  This function is (sort of) ok. However, there's an open bug w.r.t.
        unqualification. There might be several different instances of one
        package version chosen by the solver, which will lead to clashes.
 
cabal-install/Distribution/Client/Dependency/Modular/Builder.hs
   123  data structure conversion is rather ugly here
   128  Should we include the flag default in the tree?
   148  We could inline this above.
 
cabal-install/Distribution/Client/Dependency/Modular/Dependency.hs
    78  This isn't the ideal location to declare the type, but we need them
        for constrained instances.
   137  Different pairs might have different conflict sets. We're obviously
        interested to return a conflict that has a "better" conflict set in
        the sense the it contains variables that allow us to backjump
        further. We might apply some heuristics here, such as to change the
        order in which we check the constraints.
 
cabal-install/Distribution/Client/Dependency/Modular/Explore.hs
   134  This isn't quite optimal, because we do not merely report the shape
        of the tree, but rather make assumptions about where that shape
        originated from. It'd be better if the pruning itself would leave
        information that we could pick up at this point.
 
cabal-install/Distribution/Client/Dependency/Modular/IndexConversion.hs
    77  Installed packages should also store their encapsulations!
   187  Nothing should be treated as unknown, rather than empty list. This
        code should eventually be changed to either support partial
        resolution of compiler flags or to complain about incompletely
        configured compilers. [fixme]
 
cabal-install/Distribution/Client/Dependency/Modular/Linking.hs
   360  The enumeration of OptionalStanza names is very brittle; if a
        constructor is added to the datatype we won't notice it here
 
cabal-install/Distribution/Client/Dependency/Modular/Package.hs
    33  More information is needed about the repo.
 
cabal-install/Distribution/Client/Dependency/Modular/Preference.hs
   212  It would be better to actually check the reverse dependencies of
        installed packages. If they're not depended on, then reinstalling
        should be fine. Even if they are, perhaps this should just result
        in trying to reinstall those other packages as well. However, doing
        this all neatly in one pass would require to change the builder, or
        at least to change the goal set after building.
 
cabal-install/Distribution/Client/Fetch.hs
    97  when we add support for remote tarballs then this message will need
        to be changed because for remote tarballs we fetch them at the
        earlier phase.
 
cabal-install/Distribution/Client/GZipUtils.hs
    37  alternatively, we might consider looking for the two magic bytes at
        the beginning of the gzip header.
 
cabal-install/Distribution/Client/Get.hs
   111  add command-line constraint and preference args for unpack
 
cabal-install/Distribution/Client/HttpUtils.hs
    58  print info message when we're using a proxy based on verbosity
   157  check the content-length header matches the body length. [fixme]
   158  stream the download into the file rather than buffering the whole
        thing in memory.
 
cabal-install/Distribution/Client/IndexUtils.hs
    97  make getInstalledPackages use sensible verbosity in the first place
        [fixme]
 
cabal-install/Distribution/Client/Init.hs
   382  really should use guessed source roots. [xxx]
 
cabal-install/Distribution/Client/Init/Heuristics.hs
   178  we should probably make a better attempt at parsing comments above.
        Unfortunately we can't use a full-fledged Haskell parser since
        cabal's dependencies must be kept at a minimum. [xxx]
 
cabal-install/Distribution/Client/Install.hs
   220  use a better error message, remove duplication.
   228  Make InstallContext a proper data type with documented fields. |
        Common context for makeInstallPlan and processInstallPlan.
   233  Make InstallArgs a proper data type with documented fields or just
        get rid of it completely. | Initial arguments given to 'install' or
        'makeInstallContext'.
   372  this just applies all flags to all targets which is silly. We
        should check if the flags are appropriate [fixme]
   412  this is a general feature and should be moved to D.C.Dependency
        Also, the InstallPlan.remove should return info more precise to the
        problem, rather than the very general PlanProblem type.
   554  This is a bit of a hack, pretending that each package is installed
        It's doubly a hack because the installed package ID didn't get
        updated... [fixme]
   668  this should be a proper function in a proper place [fixme]
   770  does not handle flags [fixme]
   855  might be nice if the install plan gave us the new
        InstalledPackageInfo
  1293  'cabal get happy && cd sandbox && cabal install ../happy' still
        fails even with this workaround. We probably can live with that.
 
cabal-install/Distribution/Client/InstallPlan.hs
   652  It would be nicer to use ComponentDeps here so we can be more
        precise in our checks. That's a bit tricky though, as this
        currently relies on the 'buildDepends' field of
        'PackageDescription'. (OTOH, that field is deprecated and should be
        removed anyway.) As long as we _do_ use a flat list here, we have
        to allow for duplicates when we fold specifiedDeps; once we have
        proper ComponentDeps here we should get rid of the `nubOn` in
        `mergeDeps`.
   661  use something lower level than finalizePackageDescription
 
cabal-install/Distribution/Client/InstallSymlink.hs
   112  do we want to do this here? : createDirectoryIfMissing True
        publicBinDir
 
cabal-install/Distribution/Client/List.hs
   380  exclude non-buildable exes
   440  installed package info is missing synopsis
 
cabal-install/Distribution/Client/ParseUtils.hs
    24  replace this with something better [fixme]
 
cabal-install/Distribution/Client/Sandbox.hs
    39  move somewhere else [fixme]
   220  should we allow multiple package DBs (e.g. with 'inherit')?
   246  Instead of modifying the global process state, it'd be better to
        set the environment individually for each subprocess invocation.
        This will have to wait until the Shell monad is implemented;
        without it the required changes are too intrusive.
   379  path canonicalisation is done in addBuildTreeRefs, but we do it
        twice because of the timestamps file. [fixme]
   599  use a better error message, remove duplication.
   742  Is this compatible with the 'inherit' feature? [fixme]
   748  configPackageDB' and configCompilerAux' don't really belong in this
        module [fixme]
   762  make configCompilerAux use a sensible verbosity [fixme]
 
cabal-install/Distribution/Client/Sandbox/Index.hs
   104  Move this to D.C.Utils?
   175  return only the refs that vere actually removed. [fixme]
   180  removing snapshot deps is done with `delete-source
        .cabal-sandbox/snapshots/$SNAPSHOT_NAME`. Perhaps we also want to
        support removing snapshots by providing the original path. [fixme]
 
cabal-install/Distribution/Client/Sandbox/PackageEnvironment.hs
    84  would be nice to remove duplication between
        D.C.Sandbox.PackageEnvironment and D.C.Config.
   148  Currently, we follow cabal-dev and set 'user-install: False' in the
        config file. In the future we may want to distinguish between
        global, sandbox and user install types.
   334  Use substPathTemplate with compilerTemplateEnv ++
        platformTemplateEnv ++ abiTemplateEnv.
   342  Also check for an initialised package DB?
   411  Should we make these fields part of ~/.cabal/config ? [fixme]
 
cabal-install/Distribution/Client/Sandbox/Timestamp.hs
    71  We should keep this info in the index file, together with build
        tree refs. [fixme]
   214  This function is not thread-safe because of 'inDir'. [fixme]
   261  What if the clock jumps backwards at any point? For now we only
        print a warning. [fixme]
 
cabal-install/Distribution/Client/Setup.hs
    44  stop exporting these:
  1456  remove when "cabal install" avoids
  1918  this should be an 'add-source'-only flag. [fixme]
  2058  this is too GHC-focused for my liking..
  2193  Disabled for now because it does not work as advertised (yet).
  2223  do we want to allow per-package flags?
 
cabal-install/Distribution/Client/SrcDist.hs
   129  use runProgramInvocation, but has to be able to set CWD
 
cabal-install/Distribution/Client/Tar.hs
   798  check integer widths, eg for large file sizes
 
cabal-install/Distribution/Client/Targets.hs
   416  should we warn if there are no world targets?
   716  use Text instance for FlagName and FlagAssignment [fixme]
 
cabal-install/Distribution/Client/Types.hs
   114  I wonder if it would make sense to promote this datatype to Cabal
        and use it consistently instead of InstalledPackageIds?
 
cabal-install/Distribution/Client/Upload.hs
    38  how do we find this path for an arbitrary hackage server? is it
        always at some fixed location relative to the server root? [fixme]
    59  better error message when no repos are given [fixme]
 
cabal-install/Main.hs
   660  It'd be nice if 'cabal install' picked up the '-w' flag passed to
        'configure' when run inside a sandbox. Right now, running
   683  Redesign ProgramDB API to prevent such problems as #2241 in the
        future.
   703  Passing 'SandboxPackageInfo' to install unconditionally here means
        that 'cabal install some-package' inside a sandbox will sometimes
        reinstall modified add-source deps, even if they are not among the
        dependencies of 'some-package'. This can also prevent packages that
        depend on older versions of add-source'd packages from building
        (see #1362). [fixme]
 
cabal-install/tests/PackageTests/Freeze/Check.hs
    45  Test this against a package installed in the sandbox but not
        depended upon. [xxx]
 
cabal-install/tests/PackageTests/PackageTester.hs
     3  This module was originally based on the PackageTests.PackageTester
        module in Cabal, however it has a few differences. I suspect that
        as this module ages the two modules will diverge further. As such,
        I have not attempted to merge them into a single module nor to
        extract a common module from them. Refactor this module and/or
        Cabal's PackageTests.PackageTester to remove commonality.
        2014-05-15 Ben Armston
   229  Convert to a "-v" flag instead.
 
cabal-install/tests/UnitTests/Distribution/Client/Dependency/Modular/DSL.hs
    55  Perhaps these should be made comments of the corresponding data
        type definitions. For now these are just my own conclusions and may
        be wrong.


More information about the cabal-devel mailing list