Re: [Haskell-cafe] Installing REPA

2012-04-07 Thread Ben Lippmeier

On 07/04/2012, at 9:33 AM, Chris Wong wrote:

 On Sat, Apr 7, 2012 at 2:02 AM, Dominic Steinitz
 idontgetoutm...@googlemail.com wrote:
 Hi,
 
 I'm trying to install REPA but getting the following. Do I just install
 base? Or is it more complicated than that?
 
 Thanks, Dominic.
 
 I think the easiest solution is to just use an older version of Repa.
 According to Hackage, the latest one that works with base 4.3 is Repa
 2.1.1.3:
 
 $ cabal install repa==2.1.1.3

I've just pushed Repa 3 onto Hackage, which has a much better API than the 
older versions, and solves several code fusion problems. However, you'll need 
to upgrade to GHC 7.4 to use it. GHC 7.0.3 is two major releases behind the 
current version.

Ben.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Subscriber-only lists as Maintainer contacts of Cabal packges

2012-04-07 Thread Joachim Breitner
Dear Cabal authors,

if your package is team maintained and you put in a mailing list as the
“Maintainer” contact of your package, that is in general a good thing.
But if you do so, please make sure the list is not set to subscriber
only; it is an unreasonable burden to subscribe for people who just want
to send you one question, and possibly have to contact dozends of
different package authors, e.g. as a distribution packager.

Thanks,
Joachim

(Who really thinks that using the subscriber-only setting of mailman as
an anti-spam-measure is an abuse of the feature, and that mailman should
offer a “non-subscribers get a bounce that allows them to approve the
message themselves“ feature which would give the same spam protection
but much less hassle for the users.)

-- 
Joachim nomeata Breitner
Debian Developer
  nome...@debian.org | ICQ# 74513189 | GPG-Keyid: 4743206C
  JID: nome...@joachim-breitner.de | http://people.debian.org/~nomeata


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Installing REPA

2012-04-07 Thread Peter Simons
Hi Ben,

  I've just pushed Repa 3 onto Hackage, which has a much better API
  than the older versions, and solves several code fusion problems.

when using the latest version of REPA with GHC 7.4.1, I have trouble
building the repa-examples package:

 | Building repa-examples-3.0.0.1...
 | Preprocessing executable 'repa-volume' for repa-examples-3.0.0.1...
 | [1 of 1] Compiling Main ( examples/Volume/Main.hs, 
dist/build/repa-volume/repa-volume-tmp/Main.o )
 | Linking dist/build/repa-volume/repa-volume ...
 | Preprocessing executable 'repa-sobel' for repa-examples-3.0.0.1...
 | [1 of 2] Compiling Solver   ( examples/Sobel/src-repa/Solver.hs, 
dist/build/repa-sobel/repa-sobel-tmp/Solver.o )
 | Loading package ghc-prim ... linking ... done.
 | Loading package integer-gmp ... linking ... done.
 | Loading package base ... linking ... done.
 | Loading package array-0.4.0.0 ... linking ... done.
 | Loading package bytestring-0.9.2.1 ... linking ... done.
 | Loading package deepseq-1.3.0.0 ... linking ... done.
 | Loading package containers-0.4.2.1 ... linking ... done.
 | Loading package binary-0.5.1.0 ... linking ... done.
 | Loading package bmp-1.2.1.1 ... linking ... done.
 | Loading package old-locale-1.0.0.4 ... linking ... done.
 | Loading package old-time-1.1.0.0 ... linking ... done.
 | Loading package extensible-exceptions-0.1.1.4 ... linking ... done.
 | Loading package time-1.4 ... linking ... done.
 | Loading package random-1.0.1.1 ... linking ... done.
 | Loading package pretty-1.1.1.0 ... linking ... done.
 | Loading package template-haskell ... linking ... done.
 | Loading package QuickCheck-2.4.2 ... linking ... done.
 | Loading package primitive-0.4.1 ... linking ... done.
 | Loading package vector-0.9.1 ... linking ... done.
 | Loading package repa-3.0.0.1 ... linking ... done.
 | Loading package repa-io-3.0.0.1 ... linking ... done.
 | Loading package repa-algorithms-3.0.0.1 ... linking ... done.
 | [2 of 2] Compiling Main ( examples/Sobel/src-repa/Main.hs, 
dist/build/repa-sobel/repa-sobel-tmp/Main.o )
 | Linking dist/build/repa-sobel/repa-sobel ...
 | Preprocessing executable 'repa-mmult' for repa-examples-3.0.0.1...
 | 
 | examples/MMult/src-repa/Main.hs:3:8:
 | Could not find module `Solver'
 | Use -v to see a list of the files searched for.

When I attempt to use repa 3.1.x, the build won't even get past the
configure stage, because Cabal refuses these dependencies. Is that a
known problem, or am I doing something wrong?

Take care,
Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Subscriber-only lists as Maintainer contacts of Cabal packges

2012-04-07 Thread Peter Simons
Hi Joachim,

  Please make sure the list is not set to subscriber only; it is an
  unreasonable burden to subscribe for people who just want to send you
  one question, and possibly have to contact dozends of different
  package authors, e.g. as a distribution packager.

+1

I have had that problem, too. Maintainers give contact details, but then
I have to jump through hoops before I can actually contact them. I see
why people want to protect themselves from spam, but this approach seems
counter-productive to me.


  (Who really thinks that using the subscriber-only setting of mailman as
  an anti-spam-measure is an abuse of the feature, and that mailman should
  offer a “non-subscribers get a bounce that allows them to approve the
  message themselves“ feature which would give the same spam protection
  but much less hassle for the users.)

The way to accomplish that is to configure the list as moderated, and
to set all list subscribers as unmoderated. This makes postings from
subscribers go right through, and everyone else's message are forwarded
to the list moderator for approval. It's not quite the same as a
challenge-response scheme that empowers casual posters to confirm their
honest intentions (i.e. the correctness of their mail envelope address),
but it's still a lot better than just dropping every mail from anyone
who isn't subscribed.

Take care,
Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Installing REPA

2012-04-07 Thread Ben Lippmeier

On 07/04/2012, at 21:38 , Peter Simons wrote:

 Hi Ben,
 
 I've just pushed Repa 3 onto Hackage, which has a much better API
 than the older versions, and solves several code fusion problems.
 
 when using the latest version of REPA with GHC 7.4.1, I have trouble
 building the repa-examples package:
 
 | Building repa-examples-3.0.0.1...
 | Preprocessing executable 'repa-volume' for repa-examples-3.0.0.1...

 When I attempt to use repa 3.1.x, the build won't even get past the
 configure stage, because Cabal refuses these dependencies. Is that a
 known problem, or am I doing something wrong?

It is a conjunction of tedious Cabal and Hackage limitations, as well as my 
failure to actually upload the new repa-examples package.

Please try again now, and if that doesn't work email be the output of:

$ cabal update
$ cabal install repa-examples
$ ghc-pkg list

Thanks,
Ben.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Installing REPA

2012-04-07 Thread Peter Simons
Hi Ben,

  Please try again now.

thank you very much for the quick update! Everything installs fine now.
I've also packaged the latest versions for NixOS. 

Take care,
Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell integration with C/C++ (GSOC)

2012-04-07 Thread Daniël de Kok
On Apr 5, 2012, at 5:08 PM, Donn Cave wrote:
 As things stand, it is quite a hassle to use a Haskell library of
 any complexity called from C.
 
[…]
 I wonder if the fact that we recognize these problems but haven't
 been super-motivated to solve them, suggests that there hasn't really
 been that much call for stand alone Haskell libraries?

Good question. Since there are not so many complete GUI toolkits yet, I can 
imagine that someone would write a GUI in C++ or Objective-C and use a Haskell 
library from there. Other than that, I think most people prefer writing an 
application in Haskell as much as possible to exploit its benefits over C/C++.

-- Daniël
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Installing REPA

2012-04-07 Thread Dominic Steinitz

On 07/04/2012 11:14, Ben Lippmeier wrote:

On 07/04/2012, at 9:33 AM, Chris Wong wrote:


On Sat, Apr 7, 2012 at 2:02 AM, Dominic Steinitz
idontgetoutm...@googlemail.com  wrote:

Hi,

I'm trying to install REPA but getting the following. Do I just install
base? Or is it more complicated than that?

Thanks, Dominic.

I think the easiest solution is to just use an older version of Repa.
According to Hackage, the latest one that works with base 4.3 is Repa
2.1.1.3:

$ cabal install repa==2.1.1.3

I've just pushed Repa 3 onto Hackage, which has a much better API than the 
older versions, and solves several code fusion problems. However, you'll need 
to upgrade to GHC 7.4 to use it. GHC 7.0.3 is two major releases behind the 
current version.

Ben.



Hi Ben, Chris and Others,

Thanks for your replies and suggestions. All I want to do is invert 
(well solve actually) a tridiagonal matrix so upgrading ghc from the 
version that comes with the platform seems a bit overkill. I think I 
will go with Chris' suggestion for now and maybe upgrade ghc (and REPA) 
when I am feeling braver.


Dominic.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] GHCi runtime linker: fatal error (was Installing REPA)

2012-04-07 Thread Dominic Steinitz

On 07/04/2012 15:42, Dominic Steinitz wrote:

On 07/04/2012 11:14, Ben Lippmeier wrote:

On 07/04/2012, at 9:33 AM, Chris Wong wrote:


On Sat, Apr 7, 2012 at 2:02 AM, Dominic Steinitz
idontgetoutm...@googlemail.com  wrote:

Hi,

I'm trying to install REPA but getting the following. Do I just 
install

base? Or is it more complicated than that?

Thanks, Dominic.

I think the easiest solution is to just use an older version of Repa.
According to Hackage, the latest one that works with base 4.3 is Repa
2.1.1.3:

$ cabal install repa==2.1.1.3
I've just pushed Repa 3 onto Hackage, which has a much better API 
than the older versions, and solves several code fusion problems. 
However, you'll need to upgrade to GHC 7.4 to use it. GHC 7.0.3 is 
two major releases behind the current version.


Ben.



Hi Ben, Chris and Others,

Thanks for your replies and suggestions. All I want to do is invert 
(well solve actually) a tridiagonal matrix so upgrading ghc from the 
version that comes with the platform seems a bit overkill. I think I 
will go with Chris' suggestion for now and maybe upgrade ghc (and 
REPA) when I am feeling braver.


Dominic.
Sadly I now get this when trying to mulitply two matrices. Is this 
because I have two copies of Primitive? I thought Cabal was supposed to 
protect me from this sort of occurrence. Does anyone have any 
suggestions on how to solve this?


Tests-MacBook-Pro:PDE Test$ ghc-pkg list | grep -i prim
WARNING: there are broken packages.  Run 'ghc-pkg check' for more details.
ghc-prim-0.2.0.0
primitive-0.3.1
primitive-0.4.0.1

*Main mmMult xx xx
Loading package primitive-0.4.0.1 ...

GHCi runtime linker: fatal error: I found a duplicate definition for symbol
   _memcpy_off
whilst processing object file
   
/Users/Test/Library/Haskell/ghc-7.0.3/lib/primitive-0.4.0.1/lib/HSprimitive-0.4.0.1.o

This could be caused by:
   * Loading two different object files which export the same symbol
   * Specifying the same object file twice on the GHCi command line
   * An incorrect `package.conf' entry, causing some object to be
 loaded twice.
GHCi cannot safely continue in this situation.  Exiting now.  Sorry.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] using FlexibleInstances and OverlappingInstances

2012-04-07 Thread TP
Hello,

In a module I am writing, I would like to use FlexibleInstances and 
OverlappingInstances.
But I get errors, so I am trying to reproduce the problems on a smaller 
program:


{-# LANGUAGE FlexibleInstances, OverlappingInstances #-}

data Foo = Foo Int
deriving ( Show )

instance Show [Foo] where
show [] = [0]
show l  = map show l

main = do
let l = [ Foo 1, Foo 2 ]
print l


The first error I obtain is:

test_overlappinginstances.hs:7:19:
Couldn't match expected type `Char' with actual type `[Char]'
Expected type: a0 - Char
  Actual type: a0 - String
In the first argument of `map', namely `show'
In the expression: map show l


Where does this Char come from? How to solve this problem?

The second error is:

test_overlappinginstances.hs:11:5:
Overlapping instances for Show [Foo]
  arising from a use of `print'
Matching instances:
  instance Show a = Show [a] -- Defined in GHC.Show
  instance [overlap ok] Show [Foo]
-- Defined at test_overlappinginstances.hs:5:10-19


The overlap is ok (overlap ok does not appear if not using the pragma 
OverlappingInstances), so it should work?

Thanks in advance,

TP


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Conduits and Unix Pipes

2012-04-07 Thread Clark Gaebel
Has anyone built an adapter between unix pipes and conduits? Something like:

upipe2conduit :: String - Conduit Char Char

let someLines = hello\nworld
nLines - (read . runResourceT $ sourceList someLines $= upipe2conduit wc
-l $$ consume) :: Integer

If this has been done, is it on hackage?

Thanks,
  - clark
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Conduits and Unix Pipes

2012-04-07 Thread Bin Jin
I think process-conduit is what you are looking for.
On Apr 8, 2012 1:22 AM, Clark Gaebel cgae...@uwaterloo.ca wrote:

 Has anyone built an adapter between unix pipes and conduits? Something
 like:

 upipe2conduit :: String - Conduit Char Char

 let someLines = hello\nworld
 nLines - (read . runResourceT $ sourceList someLines $= upipe2conduit wc
 -l $$ consume) :: Integer

 If this has been done, is it on hackage?

 Thanks,
   - clark

 ___
 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


Re: [Haskell-cafe] Conduits and Unix Pipes

2012-04-07 Thread Clark Gaebel
Well look at that. Thanks!

On Sat, Apr 7, 2012 at 1:49 PM, Bin Jin bjin1...@gmail.com wrote:

 I think process-conduit is what you are looking for.
 On Apr 8, 2012 1:22 AM, Clark Gaebel cgae...@uwaterloo.ca wrote:

 Has anyone built an adapter between unix pipes and conduits? Something
 like:

 upipe2conduit :: String - Conduit Char Char

 let someLines = hello\nworld
 nLines - (read . runResourceT $ sourceList someLines $= upipe2conduit
 wc -l $$ consume) :: Integer

 If this has been done, is it on hackage?

 Thanks,
   - clark

 ___
 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


Re: [Haskell-cafe] using FlexibleInstances and OverlappingInstances

2012-04-07 Thread Antoine Latter
On Sat, Apr 7, 2012 at 12:08 PM, TP paratribulati...@free.fr wrote:
 Hello,

 In a module I am writing, I would like to use FlexibleInstances and
 OverlappingInstances.
 But I get errors, so I am trying to reproduce the problems on a smaller
 program:


Is your actual issue with Showing a list? If so, you might be better
off using the 'showList' member of the 'Show' typeclass:

instance Show Foo where
   show x = ...
   showList xs = ...

Then your 'showList' method will be called when 'show' is called on a
list of 'Foo' values.

The first error is because 'map show l' is the wrong type - mapping
show over a list will give you a list of strings, but 'show' must
return a string. I think you could use 'concatMap' here.

Other than that the only advice I can give is that I try my hardest to
avoid OverlappingInstances.

Antoine

Antoine

 
 {-# LANGUAGE FlexibleInstances, OverlappingInstances #-}

 data Foo = Foo Int
            deriving ( Show )

 instance Show [Foo] where
    show [] = [0]
    show l  = map show l

 main = do
    let l = [ Foo 1, Foo 2 ]
    print l
 

 The first error I obtain is:
 
 test_overlappinginstances.hs:7:19:
    Couldn't match expected type `Char' with actual type `[Char]'
    Expected type: a0 - Char
      Actual type: a0 - String
    In the first argument of `map', namely `show'
    In the expression: map show l
 

 Where does this Char come from? How to solve this problem?

 The second error is:
 
 test_overlappinginstances.hs:11:5:
    Overlapping instances for Show [Foo]
      arising from a use of `print'
    Matching instances:
      instance Show a = Show [a] -- Defined in GHC.Show
      instance [overlap ok] Show [Foo]
        -- Defined at test_overlappinginstances.hs:5:10-19
 

 The overlap is ok (overlap ok does not appear if not using the pragma
 OverlappingInstances), so it should work?

 Thanks in advance,

 TP


 ___
 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


[Haskell-cafe] Mixing Unboxed Mutable Vectors and Parsers

2012-04-07 Thread Myles C. Maxfield
CC: Maintainers of STMonadTrans, Vector, and JuicyPixels

Hello,
I am writing a Haskell Attoparsec parser which will modify 2-d arrays
of small values (Word8, Int8, etc.).

My first idea was to simply parse all the deltas, and later apply them
to the input list. However, I can't do that because the value of the
deltas depend on the value they're modifying.

My first pass at this program used a function of the form:

p :: [[Word8]] - Parser [[Word8]]

This approach works, however, the program uses far too much memory.
Some quick testing shows that lists of Word8s are ~52.6x larger than
unboxed vectors of Word8s, and boxed vectors of Word8s are ~7.5x
larger than unboxed vectors of Word8s. A better approach would be to
use Data.Vector.Unboxed.Mutable and do the mutations inline with the
parser. Because mutable vectors require a monad in PrimMonad to do the
mutations inside of, I'd have to use a monad transformer to combine
Parser and something in PrimMonad. Attoparsec doesn't support being
used as a monad transformer, so I can't say something like

p :: (PrimMonad m, UM.Unbox a) = M.MVector (PrimState m) (UM.MVector
(PrimState m) a) - ParserT m ()

I can't use Parsec (instead of Attoparsec) because I require streaming
semantics -- eventually I'm going to hook this up to Data.Conduit and
parse directly from the net.

There is STT (in the package STMonadTrans), however, so I could
potentially make the function result in STT Parser (). However, STT
doesn't work with Data.Vector.Mutable or Data.Vector.Unboxed.Mutable,
because STT isn't a member of the PrimMonad class (as far as I can
tell). STT itself doesn't define unboxed mutable vectors (only boxed
mutable vectors), but I feel that giving up unboxing isn't really an
option because of the memory footprint.

As a general observation, it seems silly to have two different mutable
vector implementations, one for STT and the other for PrimMonad.

So here are my questions:
1. Is it possible to implement PrimMonad with STT? I looked around for
a little while, but couldn't find anything that did this.
2. Otherwise, is it reasonable to try to implement unboxed mutable
vectors in STT? I feel this is probably going down the wrong path.
3. Are there any parsers that support streaming semantics and being
used as a monad transformer? This would require rewriting my whole
program to use this new parser, but if that's what I have to do, then
so be it.

Thanks,
Myles C. Maxfield

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] using FlexibleInstances and OverlappingInstances

2012-04-07 Thread TP
On Saturday 07 April 2012 14:22:15 you wrote:
 Is your actual issue with Showing a list? If so, you might be better
 off using the 'showList' member of the 'Show' typeclass:
 
 instance Show Foo where
show x = ...
showList xs = ...
 
 Then your 'showList' method will be called when 'show' is called on a
 list of 'Foo' values.

Yes, my problem is to show a list. Thanks a lot. Your solution should work in 
my more complicated module. I have modified the simple program of my post to 
make it work with showList as you advised:

data Foo = Foo Int

instance Show Foo where
show (Foo i) = show i

-- Implementation of showList found at:
-- http://www.haskell.org/pipermail/haskell-cafe/2010-May/077818.html
-- showList []   = showString []
-- showList (x:xs)   = showChar '[' . shows x . showl xs
--   where showl [] = showChar ']'
-- showl (x:xs) = showChar ',' . shows x . showl xs
--  So with the inspiration from above, I can create my implementation
--  in the accumulator style:
--  http://www.willamette.edu/~fruehr/haskell/evolution.html
--  Not a lot of information on Show instance. Haskell, the Craft of
--  functional programming quotes:
--  http://www.haskell.org/tutorial/stdclasses.html#sect8.3
-- Not a lot of information at:
-- http://book.realworldhaskell.org/read/using-typeclasses.html#id608052

showList [] = shows Empty list
showList (x:xs) = showChar '' . shows x . showl xs
where showl [] = showChar ''
  showl (x:xs) = showChar ';' . shows x . showl xs

main = do
print [ Foo 1, Foo 2]
print ([] :: [Foo])


 The first error is because 'map show l' is the wrong type - mapping
 show over a list will give you a list of strings, but 'show' must
 return a string. I think you could use 'concatMap' here.

Thanks. The first error was so stupid... Perhaps I was a little disturbed by 
overlapping instances.
 
 Other than that the only advice I can give is that I try my hardest to
 avoid OverlappingInstances.

I have found more information about overlapping instances at:

http://book.realworldhaskell.org/read/using-typeclasses.html#id608052

but it does not seem to work well; or it is rather tricky: I have been unable 
to make my initial post example work with overlapping instances. However, I 
don't see why it could not work.

Thanks

TP


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Too much inlining on text package

2012-04-07 Thread Bryan O'Sullivan
On Sun, Mar 18, 2012 at 12:02 AM, Michael Snoyman mich...@snoyman.comwrote:


 OK, issue created: https://github.com/bos/text/issues/19


I fixed the too-much-inlining
bughttps://github.com/bos/text/commit/2b2cb084c4689c06f1a7851ff8eb1e412eb02c1btonight.
As a bonus, Text literals are now decoded straight from GHC's
packed encoding, without an intermediate step through String.

Generated code now looks like this at -O and above:

$ ghc -O -ddump-simpl -c CS.hs
CS.foo :: Data.Text.Internal.Text
[GblId, ...]
CS.foo = Data.Text.unpackCString# x\NULy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe