possible bug in latest hackage Elf (Elf-0.27)

Hi list,
with below test program:
--
/* test1.c: build with -g -O0 */
include
From above, you can see the steEnclosingSection is wrong and offset by 1.
The *correct* output should be: Just (EST {steName = (9,Just "appmsg"), steEnclosingSection = Just (ElfSection {elfSectionName = ".rodata", elfSectionType = SHT_PROGBITS, elfSectionFlags = [SHF_ALLOC], elfSectionAddr = 4195920, elfSectionSize = 17, elfSectionLink = 0, elfSectionInfo = 0, elfSectionAddrAlign = 4, elfSectionEntSize = 0, elfSectionData = "\SOH\NUL\STX\NULhello, world\NUL"}), steType = STTObject, steBind = STBLocal, steOther = 0, steIndex = SHNIndex 14, steValue = 4195924, steSize = 13}) Just "hello, world\NUL" After check Elf.hs, I found there could be two issues: 1) in sectionByIndex, (SHNIndex) should start from 0, not 1; this cause the steEnclosingSection from my exmaple offset by 1; 2) in findSymbolDefinition, start should substract the sectionAddr (base address). please see below diff for details: -- --- a/Elf.hs 2012-12-04 19:27:51.000000000 -0800 +++ b/Elf.hs 2014-05-14 22:57:01.014498515 -0700 @@ -1,5 +1,5 @@ -- | Data.Elf is a module for parsing a ByteString of an ELF file into an Elf record. -module Data.Elf ( parseElf +module Elf ( parseElf , parseSymbolTables , findSymbolDefinition , Elf(..) @@ -666,12 +666,12 @@ getSymbolTableEntries e s = -- If the size is zero, or the offset larger than the 'elfSectionData', -- then 'Nothing' is returned. findSymbolDefinition :: ElfSymbolTableEntry -> Maybe B.ByteString -findSymbolDefinition e = - let enclosingData = fmap elfSectionData (steEnclosingSection e) - start = fromIntegral (steValue e) +findSymbolDefinition e = steEnclosingSection e >>= \enclosingSection -> + let enclosingData = elfSectionData enclosingSection + start = ( (fromIntegral (steValue e)) - (fromIntegral (elfSectionAddr enclosingSection) ) ) len = fromIntegral (steSize e) - def = fmap (B.take len . B.drop start) enclosingData - in if def == Just B.empty then Nothing else def + def = (B.take len . B.drop start) enclosingData + in if def == B.empty then Nothing else Just def runGetMany :: Get a -> L.ByteString -> [a] runGetMany g bs @@ -712,7 +712,7 @@ getSymbolTableEntry e strtlb = return $ EST (nameIdx,name) sec typ bind other sTlbIdx symVal size sectionByIndex :: Elf -> ElfSectionIndex -> Maybe ElfSection -sectionByIndex e (SHNIndex i) = lookup i . zip [1..] $ (elfSections e) +sectionByIndex e (SHNIndex i) = lookup i . zip [0..] $ (elfSections e) sectionByIndex _ _ = Nothing infoToTypeAndBind :: Word8 -> (ElfSymbolType,ElfSymbolBinding) -- Would you please check above change and update Data.Elf hackage? I cannot find the author from http://hackage.haskell.org/package/elf-0.27 Thanks baojun

re-format patch:
--
--- a/Elf.hs 2012-12-04 19:27:51.000000000 -0800
+++ b/Elf.hs 2014-05-14 23:47:08.565983310 -0700
@@ -666,12 +666,12 @@ getSymbolTableEntries e s =
-- If the size is zero, or the offset larger than the 'elfSectionData',
-- then 'Nothing' is returned.
findSymbolDefinition :: ElfSymbolTableEntry -> Maybe B.ByteString
-findSymbolDefinition e =
- let enclosingData = fmap elfSectionData (steEnclosingSection e)
- start = fromIntegral (steValue e)
+findSymbolDefinition e = steEnclosingSection e >>= \enclosingSection ->
+ let enclosingData = elfSectionData enclosingSection
+ start = ( (fromIntegral (steValue e)) - (fromIntegral
(elfSectionAddr enclosingSection) ) )
len = fromIntegral (steSize e)
- def = fmap (B.take len . B.drop start) enclosingData
- in if def == Just B.empty then Nothing else def
+ def = (B.take len . B.drop start) enclosingData
+ in if def == B.empty then Nothing else Just def
runGetMany :: Get a -> L.ByteString -> [a]
runGetMany g bs
@@ -712,7 +712,7 @@ getSymbolTableEntry e strtlb =
return $ EST (nameIdx,name) sec typ bind other sTlbIdx symVal size
sectionByIndex :: Elf -> ElfSectionIndex -> Maybe ElfSection
-sectionByIndex e (SHNIndex i) = lookup i . zip [1..] $ (elfSections e)
+sectionByIndex e (SHNIndex i) = lookup i . zip [0..] $ (elfSections e)
sectionByIndex _ _ = Nothing
infoToTypeAndBind :: Word8 -> (ElfSymbolType,ElfSymbolBinding)
--
http://github.com/erikcharlebois/elf gives 404.
Thanks
Baojun
On Wed, May 14, 2014 at 11:18 PM, Baojun Wang
Hi list,
with below test program:
-- /* test1.c: build with -g -O0 */ include
static const char appmsg[] = "hello, world";
int main(int argc, char* argv[]) { fputs(appmsg, stdout);
return 0; }
--- elf-test1.hs module Main where
import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as C
import Control.Monad
import Data.Elf
testelf = "/tmp/test1" testelfsym = C.pack "appmsg"
lookupSymbol1 _ [] = Nothing lookupSymbol1 sym (t:ts) = case (snd (steName t)) of Nothing -> lookupSymbol1 sym ts Just sname -> if sname == sym then Just t else lookupSymbol1 sym ts
lookupSymbol _ [] = Nothing lookupSymbol sym (t:ts) = case (lookupSymbol1 sym t) of Nothing -> lookupSymbol sym ts t1 -> t1
test1 elf symtab symbol = mapM_ (print) (elfSections elf)
test2 elf symtab symbol = lookupSymbol symbol symtab
test3 elf symtab symbol = lookupSymbol symbol symtab >>= \et -> findSymbolDefinition et
mainloop elf symtab symbol = -- (test1 elf symtab symbol) >> print (test2 elf symtab symbol) >> print (test3 elf symtab symbol) >> return ()
main = do contents <- B.readFile testelf let elf = parseElf contents symtab = parseSymbolTables elf mainloop elf symtab testelfsym ---
the latest Data.Elf doesn't geive correct output as expected:
output will be:
Just (EST {steName = (9,Just "appmsg"), steEnclosingSection = Just (ElfSection {elfSectionName = ".fini", elfSectionType = SHT_PROGBITS, elfSectionFlags = [SHF_EXECINSTR,SHF_ALLOC], elfSectionAddr = 4195908, elfSectionSize = 9, elfSectionLink = 0, elfSectionInfo = 0, elfSectionAddrAlign = 4, elfSectionEntSize = 0, elfSectionData = "H\131\236\bH\131\196\b\195"}), steType = STTObject, steBind = STBLocal, steOther = 0, steIndex = SHNIndex 14, steValue = 4195924, steSize = 13})
From above, you can see the steEnclosingSection is wrong and offset by 1.
The *correct* output should be: Just (EST {steName = (9,Just "appmsg"), steEnclosingSection = Just (ElfSection {elfSectionName = ".rodata", elfSectionType = SHT_PROGBITS, elfSectionFlags = [SHF_ALLOC], elfSectionAddr = 4195920, elfSectionSize = 17, elfSectionLink = 0, elfSectionInfo = 0, elfSectionAddrAlign = 4, elfSectionEntSize = 0, elfSectionData = "\SOH\NUL\STX\NULhello, world\NUL"}), steType = STTObject, steBind = STBLocal, steOther = 0, steIndex = SHNIndex 14, steValue = 4195924, steSize = 13}) Just "hello, world\NUL"
After check Elf.hs, I found there could be two issues: 1) in sectionByIndex, (SHNIndex) should start from 0, not 1; this cause the steEnclosingSection from my exmaple offset by 1; 2) in findSymbolDefinition, start should substract the sectionAddr (base address).
please see below diff for details:
--
--- a/Elf.hs 2012-12-04 19:27:51.000000000 -0800 +++ b/Elf.hs 2014-05-14 22:57:01.014498515 -0700 @@ -1,5 +1,5 @@ -- | Data.Elf is a module for parsing a ByteString of an ELF file into an Elf record. -module Data.Elf ( parseElf +module Elf ( parseElf , parseSymbolTables , findSymbolDefinition , Elf(..) @@ -666,12 +666,12 @@ getSymbolTableEntries e s = -- If the size is zero, or the offset larger than the 'elfSectionData', -- then 'Nothing' is returned. findSymbolDefinition :: ElfSymbolTableEntry -> Maybe B.ByteString -findSymbolDefinition e = - let enclosingData = fmap elfSectionData (steEnclosingSection e) - start = fromIntegral (steValue e) +findSymbolDefinition e = steEnclosingSection e >>= \enclosingSection -> + let enclosingData = elfSectionData enclosingSection + start = ( (fromIntegral (steValue e)) - (fromIntegral (elfSectionAddr enclosingSection) ) ) len = fromIntegral (steSize e) - def = fmap (B.take len . B.drop start) enclosingData - in if def == Just B.empty then Nothing else def + def = (B.take len . B.drop start) enclosingData + in if def == B.empty then Nothing else Just def
runGetMany :: Get a -> L.ByteString -> [a] runGetMany g bs @@ -712,7 +712,7 @@ getSymbolTableEntry e strtlb = return $ EST (nameIdx,name) sec typ bind other sTlbIdx symVal size
sectionByIndex :: Elf -> ElfSectionIndex -> Maybe ElfSection -sectionByIndex e (SHNIndex i) = lookup i . zip [1..] $ (elfSections e) +sectionByIndex e (SHNIndex i) = lookup i . zip [0..] $ (elfSections e) sectionByIndex _ _ = Nothing
infoToTypeAndBind :: Word8 -> (ElfSymbolType,ElfSymbolBinding)
--
Would you please check above change and update Data.Elf hackage? I cannot find the author from http://hackage.haskell.org/package/elf-0.27
Thanks baojun

Hi Baojun,
* Baojun Wang
Hi list,
...
Would you please check above change and update Data.Elf hackage? I cannot find the author from http://hackage.haskell.org/package/elf-0.27
Thanks baojun
That page lists Erik Charlebois

2014-05-15 9:30 GMT+02:00 Roman Cheplyaka
If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO. In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell.

* Sven Panne
2014-05-15 9:30 GMT+02:00 Roman Cheplyaka
: If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
It works when you are the end user. If you maintain an open source project that depends on a package that happened to break or otherwise have bugs, you can't tell your users to download and fix all those broken packages. Users rightly expect they should be able just `cabal install` the project (if it's well maintained). So if the package is not fixed on package promptly, forking remains the only option.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
I find it funny how you argue against forking, yet propose to create an even stronger incentive to fork.
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell.

On May 15, 2014, at 5:18 AM, Sven Panne
wrote: 2014-05-15 9:30 GMT+02:00 Roman Cheplyaka
: If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell.
But we do need a mechanism to deal with name expansion. Many of us would prefer to make package name usurpation a slow, forgiving process, but we should then contend with the fact that such a policy adds to the rate at which new packages are uploaded. If search results display, and can be sorted by, information regarding number of downloads, downloads in the last year, and latest upload date, we will be suggesting which of these variations a new user should consider. Pair this with a slow name reclaiming process, and we won't have to always consider perpetuity when coming up with package names. Preferably packages would also come with some sort of UUID independent of a user-friendly name so that they could exist on hackage without blocking new uses of a good name if one development has permanently stalled. Anthony

Many thanks for the input, I've sent email to the maintainer, hopefully
could get reply soon :)
Best Regards
baojun
On Thu, May 15, 2014 at 7:00 AM, Anthony Cowley
On May 15, 2014, at 5:18 AM, Sven Panne
wrote: 2014-05-15 9:30 GMT+02:00 Roman Cheplyaka
: If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell.
But we do need a mechanism to deal with name expansion. Many of us would prefer to make package name usurpation a slow, forgiving process, but we should then contend with the fact that such a policy adds to the rate at which new packages are uploaded. If search results display, and can be sorted by, information regarding number of downloads, downloads in the last year, and latest upload date, we will be suggesting which of these variations a new user should consider. Pair this with a slow name reclaiming process, and we won't have to always consider perpetuity when coming up with package names.
Preferably packages would also come with some sort of UUID independent of a user-friendly name so that they could exist on hackage without blocking new uses of a good name if one development has permanently stalled.
Anthony
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I would argue *for* forking. Hackage is big and consists of many packages
which have only a few users, or maybe just one -- the author. I don't see
all these packages if I don't go on the page and look. But when I do, I
will be looking for *them*. If some popular package stops working then I
would be happy to find a fork, because now I can just tell cabal about it.
And if the original gets fixed, I can go back. I don't think people who
fork are looking for aquiring yet another package to maintain forever, or
to take it over.
On Thu, May 15, 2014 at 11:18 AM, Sven Panne
2014-05-15 9:30 GMT+02:00 Roman Cheplyaka
: If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Markus Läll

On Fri, 2014-05-16 at 11:04 +0200, Markus Läll wrote:
I would argue *for* forking. Hackage is big and consists of many packages which have only a few users, or maybe just one -- the author. I don't see all these packages if I don't go on the page and look. But when I do, I will be looking for *them*. If some popular package stops working then I would be happy to find a fork, because now I can just tell cabal about it. And if the original gets fixed, I can go back. I don't think people who fork are looking for aquiring yet another package to maintain forever, or to take it over.
tl;dr: Eagerly forking is all nice and shiny for 'leaf' packages which don't expose common functionality, but causes troubles for packages which are common library dependencies. Doesn't this cause issues with library interoperability? Say there's a package which implements some standard datatype, e.g. 'vector' by author V. Then there are 2 other packages, 'vector-algorithms' by author A and 'complex-vector-algorithms' by author C. 'vector' exports a datatype 'Vector'. 'vector-algorithms' exports a function 'a :: Int -> Vector'. 'complex-vector-algorithms' exports a function 'c :: Vector -> Float'. Finally, there's the application author who wrote the function 'ingeniousCalculation :: Int -> Float; ingeniousCalculation = c . a' Now, the author of C finds an obscure bug in some function in 'vector' he uses (caused by a bug in some internal 'vector' function which requires access to non-exported internals of the Vector type), and sends a patch to V. This bug doesn't impact 'vector-algorithms' in any way. V doesn't reply within 48 hours, so C impatiently uploads 'vector-c' to Hackage, containing the fix, and updates the 'complex-vector'algorithms' dependencies from 'vector' to 'vector-c' (with whatever version constraint). At this point, the code by the application author breaks since 'vector-algorithms' uses 'Vector' from the 'vector' package, and 'complex-vector-algorithms' uses 'Vector' from 'vector-c', which are different types from a compiler perspective. I see 3 solutions: - 'vector-algorithms' needs to be updated by A to use 'vector-c', something to which A might be reluctant since it could break lots of code using 'vector-algorithms' in combination with other libraries and applications using 'vector'. - The application author needs to patch 'vector-algorithms' locally to use 'vector-c'. - The application author patches 'vector' locally to fix the bug (something V wil most likely do in a couple of days) and reverts the dependency of 'complex-vector-algorithms' from 'vector-c' back to 'vector'. None of these seem very satisfactory. So, whilst forking (in this case) provides a very 'local' solution for the 'complex-vector-algorithms' package and C, it doesn't fix anything (I'd even argue it complicates matters) in the grand scheme of things. My .02, Nicolas
On Thu, May 15, 2014 at 11:18 AM, Sven Panne
wrote: 2014-05-15 9:30 GMT+02:00 Roman Cheplyaka
: If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

The right thing to do is to apply a patch to a local copy of vector and use that until upstream is fixed. Uploading a new forked package doesn't solve the issue in a satisfactory way, as you observed.

I now see what you mean and you are totally right.
I guess what people are craving for, is a seamless solution to fix the
problem quick, and have it be public right away to yourself and others who
need it. Maybe this is material for a later discussion, but as just a
thought, maybe the eager ones could manage an eager hackage to host their
changes (a private hackage has been mentioned before). More work upfront,
but might be worth it in the end.
On Fri, May 16, 2014 at 11:27 AM, Nicolas Trangez
On Fri, 2014-05-16 at 11:04 +0200, Markus Läll wrote:
I would argue *for* forking. Hackage is big and consists of many packages which have only a few users, or maybe just one -- the author. I don't see all these packages if I don't go on the page and look. But when I do, I will be looking for *them*. If some popular package stops working then I would be happy to find a fork, because now I can just tell cabal about it. And if the original gets fixed, I can go back. I don't think people who fork are looking for aquiring yet another package to maintain forever, or to take it over.
tl;dr: Eagerly forking is all nice and shiny for 'leaf' packages which don't expose common functionality, but causes troubles for packages which are common library dependencies.
Doesn't this cause issues with library interoperability?
Say there's a package which implements some standard datatype, e.g. 'vector' by author V. Then there are 2 other packages, 'vector-algorithms' by author A and 'complex-vector-algorithms' by author C.
'vector' exports a datatype 'Vector'. 'vector-algorithms' exports a function 'a :: Int -> Vector'. 'complex-vector-algorithms' exports a function 'c :: Vector -> Float'.
Finally, there's the application author who wrote the function 'ingeniousCalculation :: Int -> Float; ingeniousCalculation = c . a'
Now, the author of C finds an obscure bug in some function in 'vector' he uses (caused by a bug in some internal 'vector' function which requires access to non-exported internals of the Vector type), and sends a patch to V. This bug doesn't impact 'vector-algorithms' in any way.
V doesn't reply within 48 hours, so C impatiently uploads 'vector-c' to Hackage, containing the fix, and updates the 'complex-vector'algorithms' dependencies from 'vector' to 'vector-c' (with whatever version constraint).
At this point, the code by the application author breaks since 'vector-algorithms' uses 'Vector' from the 'vector' package, and 'complex-vector-algorithms' uses 'Vector' from 'vector-c', which are different types from a compiler perspective.
I see 3 solutions: - 'vector-algorithms' needs to be updated by A to use 'vector-c', something to which A might be reluctant since it could break lots of code using 'vector-algorithms' in combination with other libraries and applications using 'vector'. - The application author needs to patch 'vector-algorithms' locally to use 'vector-c'. - The application author patches 'vector' locally to fix the bug (something V wil most likely do in a couple of days) and reverts the dependency of 'complex-vector-algorithms' from 'vector-c' back to 'vector'.
None of these seem very satisfactory.
So, whilst forking (in this case) provides a very 'local' solution for the 'complex-vector-algorithms' package and C, it doesn't fix anything (I'd even argue it complicates matters) in the grand scheme of things.
My .02,
Nicolas
On Thu, May 15, 2014 at 11:18 AM, Sven Panne
wrote:
2014-05-15 9:30 GMT+02:00 Roman Cheplyaka
: If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is
fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage
under a
different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Markus Läll

Teach cabal how to install packages from a URL or even a git
repository, like go or npm can. Then people can upload the patched
project to (or even fork on) github/bitbucket/.. and let others know
so they can update their cabal file.
On Fri, May 16, 2014 at 12:26 PM, Markus Läll
I now see what you mean and you are totally right.
I guess what people are craving for, is a seamless solution to fix the problem quick, and have it be public right away to yourself and others who need it. Maybe this is material for a later discussion, but as just a thought, maybe the eager ones could manage an eager hackage to host their changes (a private hackage has been mentioned before). More work upfront, but might be worth it in the end.
On Fri, May 16, 2014 at 11:27 AM, Nicolas Trangez
wrote: On Fri, 2014-05-16 at 11:04 +0200, Markus Läll wrote:
I would argue *for* forking. Hackage is big and consists of many packages which have only a few users, or maybe just one -- the author. I don't see all these packages if I don't go on the page and look. But when I do, I will be looking for *them*. If some popular package stops working then I would be happy to find a fork, because now I can just tell cabal about it. And if the original gets fixed, I can go back. I don't think people who fork are looking for aquiring yet another package to maintain forever, or to take it over.
tl;dr: Eagerly forking is all nice and shiny for 'leaf' packages which don't expose common functionality, but causes troubles for packages which are common library dependencies.
Doesn't this cause issues with library interoperability?
Say there's a package which implements some standard datatype, e.g. 'vector' by author V. Then there are 2 other packages, 'vector-algorithms' by author A and 'complex-vector-algorithms' by author C.
'vector' exports a datatype 'Vector'. 'vector-algorithms' exports a function 'a :: Int -> Vector'. 'complex-vector-algorithms' exports a function 'c :: Vector -> Float'.
Finally, there's the application author who wrote the function 'ingeniousCalculation :: Int -> Float; ingeniousCalculation = c . a'
Now, the author of C finds an obscure bug in some function in 'vector' he uses (caused by a bug in some internal 'vector' function which requires access to non-exported internals of the Vector type), and sends a patch to V. This bug doesn't impact 'vector-algorithms' in any way.
V doesn't reply within 48 hours, so C impatiently uploads 'vector-c' to Hackage, containing the fix, and updates the 'complex-vector'algorithms' dependencies from 'vector' to 'vector-c' (with whatever version constraint).
At this point, the code by the application author breaks since 'vector-algorithms' uses 'Vector' from the 'vector' package, and 'complex-vector-algorithms' uses 'Vector' from 'vector-c', which are different types from a compiler perspective.
I see 3 solutions: - 'vector-algorithms' needs to be updated by A to use 'vector-c', something to which A might be reluctant since it could break lots of code using 'vector-algorithms' in combination with other libraries and applications using 'vector'. - The application author needs to patch 'vector-algorithms' locally to use 'vector-c'. - The application author patches 'vector' locally to fix the bug (something V wil most likely do in a couple of days) and reverts the dependency of 'complex-vector-algorithms' from 'vector-c' back to 'vector'.
None of these seem very satisfactory.
So, whilst forking (in this case) provides a very 'local' solution for the 'complex-vector-algorithms' package and C, it doesn't fix anything (I'd even argue it complicates matters) in the grand scheme of things.
My .02,
Nicolas
On Thu, May 15, 2014 at 11:18 AM, Sven Panne
wrote: 2014-05-15 9:30 GMT+02:00 Roman Cheplyaka
: If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Markus Läll
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 16 May 2014 21:10, Tomas Carnecky
Teach cabal how to install packages from a URL or even a git repository, like go or npm can. Then people can upload the patched project to (or even fork on) github/bitbucket/.. and let others know so they can update their cabal file.
How does that solve anything? You still end up potentially needing multiple different forks of a package!
On Fri, May 16, 2014 at 12:26 PM, Markus Läll
wrote: I now see what you mean and you are totally right.
I guess what people are craving for, is a seamless solution to fix the problem quick, and have it be public right away to yourself and others who need it. Maybe this is material for a later discussion, but as just a thought, maybe the eager ones could manage an eager hackage to host their changes (a private hackage has been mentioned before). More work upfront, but might be worth it in the end.
On Fri, May 16, 2014 at 11:27 AM, Nicolas Trangez
wrote: On Fri, 2014-05-16 at 11:04 +0200, Markus Läll wrote:
I would argue *for* forking. Hackage is big and consists of many packages which have only a few users, or maybe just one -- the author. I don't see all these packages if I don't go on the page and look. But when I do, I will be looking for *them*. If some popular package stops working then I would be happy to find a fork, because now I can just tell cabal about it. And if the original gets fixed, I can go back. I don't think people who fork are looking for aquiring yet another package to maintain forever, or to take it over.
tl;dr: Eagerly forking is all nice and shiny for 'leaf' packages which don't expose common functionality, but causes troubles for packages which are common library dependencies.
Doesn't this cause issues with library interoperability?
Say there's a package which implements some standard datatype, e.g. 'vector' by author V. Then there are 2 other packages, 'vector-algorithms' by author A and 'complex-vector-algorithms' by author C.
'vector' exports a datatype 'Vector'. 'vector-algorithms' exports a function 'a :: Int -> Vector'. 'complex-vector-algorithms' exports a function 'c :: Vector -> Float'.
Finally, there's the application author who wrote the function 'ingeniousCalculation :: Int -> Float; ingeniousCalculation = c . a'
Now, the author of C finds an obscure bug in some function in 'vector' he uses (caused by a bug in some internal 'vector' function which requires access to non-exported internals of the Vector type), and sends a patch to V. This bug doesn't impact 'vector-algorithms' in any way.
V doesn't reply within 48 hours, so C impatiently uploads 'vector-c' to Hackage, containing the fix, and updates the 'complex-vector'algorithms' dependencies from 'vector' to 'vector-c' (with whatever version constraint).
At this point, the code by the application author breaks since 'vector-algorithms' uses 'Vector' from the 'vector' package, and 'complex-vector-algorithms' uses 'Vector' from 'vector-c', which are different types from a compiler perspective.
I see 3 solutions: - 'vector-algorithms' needs to be updated by A to use 'vector-c', something to which A might be reluctant since it could break lots of code using 'vector-algorithms' in combination with other libraries and applications using 'vector'. - The application author needs to patch 'vector-algorithms' locally to use 'vector-c'. - The application author patches 'vector' locally to fix the bug (something V wil most likely do in a couple of days) and reverts the dependency of 'complex-vector-algorithms' from 'vector-c' back to 'vector'.
None of these seem very satisfactory.
So, whilst forking (in this case) provides a very 'local' solution for the 'complex-vector-algorithms' package and C, it doesn't fix anything (I'd even argue it complicates matters) in the grand scheme of things.
My .02,
Nicolas
On Thu, May 15, 2014 at 11:18 AM, Sven Panne
wrote: 2014-05-15 9:30 GMT+02:00 Roman Cheplyaka
: If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Markus Läll
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

You can totally cabal install from a URL.
A good example of this Johan shared a URL pointing to a Tarball when he
wanted testers befor he released an update to cabal and cabal install.
It's really easy. Cabal sdist the project as per usual, but instead put it
somewhere online where it has a URL. Then cabal install URL. This
actually works.
On Friday, May 16, 2014, Ivan Lazar Miljenovic
On 16 May 2014 21:10, Tomas Carnecky
javascript:;> wrote: Teach cabal how to install packages from a URL or even a git repository, like go or npm can. Then people can upload the patched project to (or even fork on) github/bitbucket/.. and let others know so they can update their cabal file.
How does that solve anything? You still end up potentially needing multiple different forks of a package!
On Fri, May 16, 2014 at 12:26 PM, Markus Läll
I now see what you mean and you are totally right.
I guess what people are craving for, is a seamless solution to fix the problem quick, and have it be public right away to yourself and others who need it. Maybe this is material for a later discussion, but as just a thought, maybe the eager ones could manage an eager hackage to host
changes (a private hackage has been mentioned before). More work upfront, but might be worth it in the end.
On Fri, May 16, 2014 at 11:27 AM, Nicolas Trangez
wrote:
On Fri, 2014-05-16 at 11:04 +0200, Markus Läll wrote:
I would argue *for* forking. Hackage is big and consists of many packages which have only a few users, or maybe just one -- the author. I don't see all these packages if I don't go on the page and look. But when I
do, I
will be looking for *them*. If some popular package stops working
wrote: their then I
would be happy to find a fork, because now I can just tell cabal about it. And if the original gets fixed, I can go back. I don't think people who fork are looking for aquiring yet another package to maintain forever, or to take it over.
tl;dr: Eagerly forking is all nice and shiny for 'leaf' packages which don't expose common functionality, but causes troubles for packages which are common library dependencies.
Doesn't this cause issues with library interoperability?
Say there's a package which implements some standard datatype, e.g. 'vector' by author V. Then there are 2 other packages, 'vector-algorithms' by author A and 'complex-vector-algorithms' by author C.
'vector' exports a datatype 'Vector'. 'vector-algorithms' exports a function 'a :: Int -> Vector'. 'complex-vector-algorithms' exports a function 'c :: Vector -> Float'.
Finally, there's the application author who wrote the function 'ingeniousCalculation :: Int -> Float; ingeniousCalculation = c . a'
Now, the author of C finds an obscure bug in some function in 'vector' he uses (caused by a bug in some internal 'vector' function which requires access to non-exported internals of the Vector type), and sends a patch to V. This bug doesn't impact 'vector-algorithms' in any way.
V doesn't reply within 48 hours, so C impatiently uploads 'vector-c' to Hackage, containing the fix, and updates the 'complex-vector'algorithms' dependencies from 'vector' to 'vector-c' (with whatever version constraint).
At this point, the code by the application author breaks since 'vector-algorithms' uses 'Vector' from the 'vector' package, and 'complex-vector-algorithms' uses 'Vector' from 'vector-c', which are different types from a compiler perspective.
I see 3 solutions: - 'vector-algorithms' needs to be updated by A to use 'vector-c', something to which A might be reluctant since it could break lots of code using 'vector-algorithms' in combination with other libraries and applications using 'vector'. - The application author needs to patch 'vector-algorithms' locally to use 'vector-c'. - The application author patches 'vector' locally to fix the bug (something V wil most likely do in a couple of days) and reverts the dependency of 'complex-vector-algorithms' from 'vector-c' back to 'vector'.
None of these seem very satisfactory.
So, whilst forking (in this case) provides a very 'local' solution for the 'complex-vector-algorithms' package and C, it doesn't fix anything (I'd even-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com javascript:; http://IvanMiljenovic.wordpress.com
Haskell-Cafe mailing list Haskell-Cafe@haskell.org javascript:; http://www.haskell.org/mailman/listinfo/haskell-cafe

I think the problem is that it's impossible to depend on URLs. This means
that the package will not be installable using just `cabal install
<packagename>`, but instead, an user would have to know that he first needs
to install a patched version of `foo` before he can use `<packagename>`.
2014-05-16 18:00 GMT+02:00 Carter Schonwald
You can totally cabal install from a URL.
A good example of this Johan shared a URL pointing to a Tarball when he wanted testers befor he released an update to cabal and cabal install.
It's really easy. Cabal sdist the project as per usual, but instead put it somewhere online where it has a URL. Then cabal install URL. This actually works.
On Friday, May 16, 2014, Ivan Lazar Miljenovic
wrote: On 16 May 2014 21:10, Tomas Carnecky
wrote: Teach cabal how to install packages from a URL or even a git repository, like go or npm can. Then people can upload the patched project to (or even fork on) github/bitbucket/.. and let others know so they can update their cabal file.
How does that solve anything? You still end up potentially needing multiple different forks of a package!
On Fri, May 16, 2014 at 12:26 PM, Markus Läll
I now see what you mean and you are totally right.
I guess what people are craving for, is a seamless solution to fix the problem quick, and have it be public right away to yourself and others who need it. Maybe this is material for a later discussion, but as just a thought, maybe the eager ones could manage an eager hackage to host
changes (a private hackage has been mentioned before). More work upfront, but might be worth it in the end.
On Fri, May 16, 2014 at 11:27 AM, Nicolas Trangez < nicolas@incubaid.com> wrote:
On Fri, 2014-05-16 at 11:04 +0200, Markus Läll wrote:
I would argue *for* forking. Hackage is big and consists of many packages which have only a few users, or maybe just one -- the author. I
don't
see all these packages if I don't go on the page and look. But when I do, I will be looking for *them*. If some popular package stops working
wrote: their then I
would be happy to find a fork, because now I can just tell cabal about it. And if the original gets fixed, I can go back. I don't think people who fork are looking for aquiring yet another package to maintain forever, or to take it over.
tl;dr: Eagerly forking is all nice and shiny for 'leaf' packages which don't expose common functionality, but causes troubles for packages which are common library dependencies.
Doesn't this cause issues with library interoperability?
Say there's a package which implements some standard datatype, e.g. 'vector' by author V. Then there are 2 other packages, 'vector-algorithms' by author A and 'complex-vector-algorithms' by author C.
'vector' exports a datatype 'Vector'. 'vector-algorithms' exports a function 'a :: Int -> Vector'. 'complex-vector-algorithms' exports a function 'c :: Vector -> Float'.
Finally, there's the application author who wrote the function 'ingeniousCalculation :: Int -> Float; ingeniousCalculation = c . a'
Now, the author of C finds an obscure bug in some function in 'vector' he uses (caused by a bug in some internal 'vector' function which requires access to non-exported internals of the Vector type), and sends a patch to V. This bug doesn't impact 'vector-algorithms' in any way.
V doesn't reply within 48 hours, so C impatiently uploads 'vector-c' to Hackage, containing the fix, and updates the 'complex-vector'algorithms' dependencies from 'vector' to 'vector-c' (with whatever version constraint).
At this point, the code by the application author breaks since 'vector-algorithms' uses 'Vector' from the 'vector' package, and 'complex-vector-algorithms' uses 'Vector' from 'vector-c', which are different types from a compiler perspective.
I see 3 solutions: - 'vector-algorithms' needs to be updated by A to use 'vector-c', something to which A might be reluctant since it could break lots of code using 'vector-algorithms' in combination with other libraries and applications using 'vector'. - The application author needs to patch 'vector-algorithms' locally to use 'vector-c'. - The application author patches 'vector' locally to fix the bug (something V wil most likely do in a couple of days) and reverts the dependency of 'complex-vector-algorithms' from 'vector-c' back to 'vector'.
None of these seem very satisfactory.
So, whilst forking (in this case) provides a very 'local' solution for the 'complex-vector-algorithms' package and C, it doesn't fix anything (I'd even--
Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 2014-05-16 at 13:10:13 +0200, Tomas Carnecky wrote:
Teach cabal how to install packages from a URL
cabal install <url-to-tarball>
or even a git repository, like go or npm can.
not yet available as a single command, but the following comes close: cabal get -s <package-name> && cd <package-name-ver> && cabal install

On 2014-05-16 at 14:08:35 +0200, Herbert Valerio Riedel wrote:
On 2014-05-16 at 13:10:13 +0200, Tomas Carnecky wrote:
Teach cabal how to install packages from a URL
cabal install <url-to-tarball>
or even a git repository, like go or npm can.
not yet available as a single command, but the following comes close:
cabal get -s <package-name> && cd <package-name-ver> && cabal install
sorry, should have been cabal get -s <package-name> && cabal install <package-name>

Hi cafe,
It's been for quite a while and there's no version upgrade of this package,
may I ask to take maintainer ship of this package?
Regards
baojun
On Fri, May 16, 2014 at 2:04 AM Markus Läll
I would argue *for* forking. Hackage is big and consists of many packages which have only a few users, or maybe just one -- the author. I don't see all these packages if I don't go on the page and look. But when I do, I will be looking for *them*. If some popular package stops working then I would be happy to find a fork, because now I can just tell cabal about it. And if the original gets fixed, I can go back. I don't think people who fork are looking for aquiring yet another package to maintain forever, or to take it over.
On Thu, May 15, 2014 at 11:18 AM, Sven Panne
wrote: 2014-05-15 9:30 GMT+02:00 Roman Cheplyaka
: If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Markus Läll _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

CCing admin@hackage which is the group of folks who can take care of such a request :-) -g On February 15, 2017 at 6:00:59 PM, Baojun Wang (wangbj@gmail.com) wrote:
Hi cafe,
It's been for quite a while and there's no version upgrade of this package, may I ask to take maintainer ship of this package?
Regards baojun
On Fri, May 16, 2014 at 2:04 AM Markus Läll wrote:
I would argue *for* forking. Hackage is big and consists of many packages which have only a few users, or maybe just one -- the author. I don't see all these packages if I don't go on the page and look. But when I do, I will be looking for *them*. If some popular package stops working then I would be happy to find a fork, because now I can just tell cabal about it. And if the original gets fixed, I can go back. I don't think people who fork are looking for aquiring yet another package to maintain forever, or to take it over.
On Thu, May 15, 2014 at 11:18 AM, Sven Panne wrote:
2014-05-15 9:30 GMT+02:00 Roman Cheplyaka :
If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Markus Läll _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi Baojun,
I've added you to the maintainers of 'elf' on hackage.
Regards,
Erik
On 16 February 2017 at 08:56, Gershom B
CCing admin@hackage which is the group of folks who can take care of such a request :-)
-g
Hi cafe,
It's been for quite a while and there's no version upgrade of this
may I ask to take maintainer ship of this package?
Regards baojun
On Fri, May 16, 2014 at 2:04 AM Markus Läll wrote:
I would argue *for* forking. Hackage is big and consists of many
On February 15, 2017 at 6:00:59 PM, Baojun Wang (wangbj@gmail.com) wrote: package, packages
which have only a few users, or maybe just one -- the author. I don't see all these packages if I don't go on the page and look. But when I do, I will be looking for *them*. If some popular package stops working then I would be happy to find a fork, because now I can just tell cabal about it. And if the original gets fixed, I can go back. I don't think people who fork are looking for aquiring yet another package to maintain forever, or to take it over.
On Thu, May 15, 2014 at 11:18 AM, Sven Panne wrote:
2014-05-15 9:30 GMT+02:00 Roman Cheplyaka :
If there's no response, then you have two choices:
Actually three: Fix things locally until the "official" package is fixed.
* request package maintainership, which will take several weeks
I really hope that this will take months, not weeks, see the other discussion
* fork the package (i.e. upload your patched version to hackage under a different name)
This proposal worries me quite a bit, because if everybody follows that advice, it will turn Hackage into a chaotic collection of packages with various degrees of being fixed/maintained/etc. Imagine a package 'foo', which needs a fix, and several pepole think it's a good idea to fork and fix the issue at hand. Now we have 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Of course people normally have no incentive to really take over maintainership for 'foo', they just want a working 'foo' right now for their own project. Later the real maintainer re-appears after vacation/sabbatical/whatever, fixes 'foo', and continues to work on it, adding new features. Now somebody new comes to Hackage to see if there is already a package for some use case, and finds 'foo', 'foo-XY', 'foo-my-cool-acronym', ... Then it takes some non-trivial detective work to find out which packages are actually dead (again) and which is the real one. => Chaos IMHO.
In a nutshell: If you are really in a hurry, fix things locally. Hackage is not the place to fork like hell.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Markus Läll _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (14)
-
Anthony Cowley
-
Baojun Wang
-
Benno Fünfstück
-
Carter Schonwald
-
Erik Hesselink
-
Gershom B
-
Herbert Valerio Riedel
-
Ivan Lazar Miljenovic
-
Johan Tibell
-
Markus Läll
-
Nicolas Trangez
-
Roman Cheplyaka
-
Sven Panne
-
Tomas Carnecky