[Hackage] #179: support GHC's main-is extension

#179: support GHC's main-is extension --------------------------+------------------------------------------------- Reporter: duncan | Owner: Type: enhancement | Status: new Priority: normal | Milestone: Component: Cabal | Version: 1.2.2.0 Severity: normal | Keywords: Difficulty: normal | Ghcversion: 6.4.2 Platform: Linux | --------------------------+------------------------------------------------- Query on haskell-cafe: http://haskell.org/pipermail/haskell- cafe/2007-November/034686.html {{{ It seems the meaning of the -main-is switch for GHC and the Main-Is build option for Cabal executables differ. With GHC, I can point to any function "main" in any module, but in Cabal I must point to a filename with precisely the module name "Main". This is tying my hands with regard to organizing a default executable and exposing some of its functionality as a library. Is there a way to get around this restriction? Concretely, I want to point Cabal's Main-Is to Program/Main.hs which starts with module Program.Main where instead of just module Main where }}} So in GHC it has this meaning: http://haskell.org/ghc/docs/latest/html/users_guide/options-phases.html #options-linker {{{ -main-is thing The normal rule in Haskell is that your program must supply a main function in module Main. When testing, it is often convenient to change which function is the "main" one, and the -main-is flag allows you to do so. The thing can be one of: A lower-case identifier foo. GHC assumes that the main function is Main.foo. An module name A. GHC assumes that the main function is A.main. An qualified name A.foo. GHC assumes that the main function is A.foo. }}} In Cabal the {{{main-is:}}} field specifies the '''file name''' of the Main module. GHC's {{{-main-is}}} flag is an extension to Haskell that is not supported by the other Haskell implementations. -- Ticket URL: http://hackage.haskell.org/trac/hackage/ticket/179 Hackage http://haskell.org/cabal/ Hackage: Cabal and related projects

#179: support GHC's main-is extension --------------------------+------------------------------------------------- Reporter: duncan | Owner: Type: enhancement | Status: new Priority: normal | Milestone: Component: Cabal | Version: 1.2.2.0 Severity: normal | Resolution: Keywords: | Difficulty: normal Ghcversion: 6.4.2 | Platform: Linux --------------------------+------------------------------------------------- Comment (by duncan): So the question is how would we support this extension? Perhaps by specifying a module name for {{{main-is:}}} ? Would that be distinguishable from a file name? It wouldn't have a file extension. Perhaps it'd be better to be explicit and specify {{{main-module-is: Foo.Bar}}}. Note that we do need both a file name and a module name because we have to pass that file to ghc since it's very common for people to use main modules that are not called {{{Main.hs}}}. -- Ticket URL: http://hackage.haskell.org/trac/hackage/ticket/179#comment:1 Hackage http://haskell.org/cabal/ Hackage: Cabal and related projects

#179: support GHC's main-is extension --------------------------+------------------------------------------------- Reporter: duncan | Owner: Type: enhancement | Status: new Priority: normal | Milestone: Component: Cabal | Version: 1.2.2.0 Severity: normal | Resolution: Keywords: | Difficulty: normal Ghcversion: 6.4.2 | Platform: Linux --------------------------+------------------------------------------------- Comment (by ross@soi.city.ac.uk): Why complicate Cabal and break compatibility with non-GHC implementations when the portable solution (a little Main module) is so easy? -- Ticket URL: http://hackage.haskell.org/trac/hackage/ticket/179#comment:2 Hackage http://haskell.org/cabal/ Hackage: Cabal and related projects

#179: support GHC's main-is extension ----------------------------+----------------------------------------------- Reporter: duncan | Owner: Type: enhancement | Status: new Priority: low | Milestone: _|_ Component: Cabal library | Version: 1.2.2.0 Severity: normal | Resolution: Keywords: | Difficulty: normal Ghcversion: 6.4.2 | Platform: Linux ----------------------------+----------------------------------------------- Changes (by duncan): * priority: normal => low * milestone: => _|_ -- Ticket URL: http://hackage.haskell.org/trac/hackage/ticket/179#comment:3 Hackage http://haskell.org/cabal/ Hackage: Cabal and related projects

#179: support GHC's main-is extension ----------------------------+----------------------------------------------- Reporter: duncan | Owner: Type: enhancement | Status: new Priority: low | Milestone: _|_ Component: Cabal library | Version: 1.2.2.0 Severity: normal | Resolution: Keywords: | Difficulty: normal Ghcversion: 6.4.2 | Platform: Linux ----------------------------+----------------------------------------------- Comment (by cjs): Well, first of all, I think it's a bad idea that Cabal has an option with exactly the same name as a GHC option that ostensibly does something similar, but with different semantics. That said, the best we can do is something to make it more obvious that the semantics are different, unless we sacrifice backward compatability. As to why people want to use this, I can think of a couple of good reasons. One is that some people like to build an entire source tree into an object tree directly with ghc, in which case you cannot have multiple modules named Main (at least not simply). The second is that it can save an extra file, or six or eight, if you've got that many command-line programs to generate. So is there a good reason to refuse to support this, for those ghc users that work this way? It seems to me it would be easy enough to extend the syntax of this option slightly to allow specifying the module and/or function to use as main. Perhaps something along the lines of "main-is: Foo.hs Foo.foo". In other words: main-is: Foo.hs file Foo.hs, module Main, function main main-is: Foo.hs Bar file Foo.hs, module Bar, function main main-is: Foo.hs baz file Foo.hs, module Main, function baz main-is: Foo.hs Bar.baz file Foo.hs, module Bar, function baz This isn't quite compatable with ghc's main-is option, but it's close, at least, and maintains backward compatability with current main-is behaviour. Slightly more friendly might be to have the module name default to the module name declared inside the source file, if that's not too much work. -- Ticket URL: http://hackage.haskell.org/trac/hackage/ticket/179#comment:4 Hackage http://haskell.org/cabal/ Hackage: Cabal and related projects

#179: support GHC's main-is extension ----------------------------+----------------------------------------------- Reporter: duncan | Owner: Type: enhancement | Status: new Priority: low | Milestone: _|_ Component: Cabal library | Version: 1.2.2.0 Severity: normal | Resolution: Keywords: | Difficulty: normal Ghcversion: 6.4.2 | Platform: Linux ----------------------------+----------------------------------------------- Changes (by bos): * cc: bos (added) Comment: Oop, just ran into this one myself. The current behaviour is definitely surprising :-( -- Ticket URL: http://hackage.haskell.org/trac/hackage/ticket/179#comment:5 Hackage http://haskell.org/cabal/ Hackage: Cabal and related projects

#179: support GHC's main-is extension ----------------------------+----------------------------------------------- Reporter: duncan | Owner: Type: enhancement | Status: new Priority: low | Milestone: _|_ Component: Cabal library | Version: 1.2.2.0 Severity: normal | Resolution: Keywords: | Difficulty: normal Ghcversion: 6.4.2 | Platform: Linux ----------------------------+----------------------------------------------- Comment (by duncan): If possible we should check for this, given that the failure mode is not ideal. Unfortunately that seems to be part of the infrastructure for properly understanding modules, though in this case a relatively small part of it (unless the Main module requires pre-processing). -- Ticket URL: http://hackage.haskell.org/trac/hackage/ticket/179#comment:6 Hackage http://haskell.org/cabal/ Hackage: Cabal and related projects
participants (1)
-
Hackage