On 23/09/2008, at 14:59, Roman Leshchinskiy wrote:
dotp :: [:Int:] -> [:Int:] -> Int
dotp v w = I.sumP [: (I.*) x y | x <- v, y <- w :]
The way the vectoriser works at the moment, it will repeat the array
w (lengthP v) times, i.e., create an array of length (lengthP v *
lengthP w). This is
Am Montag, 22. September 2008 08:52 schrieb Yitzchak Gale:
> […]
> Unfortunately, the so-called "generic" Linux binary distribution
> package for GHC 6.8.3 does not work on the current, up-to-date
> Debian stable distribution because it is "too old".
GHC 6.8.2 worked for me (on i386).
> […]
Bes
The error far below is caused by "-perm /a+x" in mk/bindist.mk
during find:
I've changed it to "-perm -111"
Then "make install" could not replace links:
ln -s runghc /local/home/maeder/bin/runhaskell
ln: cannot create /local/home/maeder/bin/runhaskell: File exists
gmake[2]: *** [install] Error 2
Hello,
please consider the following code:
> {-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies #-}
>
> data GADT a where
>
> GADT :: GADT ()
>
> class Class a b | a -> b
>
> instance Class () ()
>
> fun :: (Class a b) => GADT a -> b
> fun GADT = ()
I’d expect this to wor
On Tue, Sep 23, 2008 at 6:07 PM, Wolfgang Jeltsch
<[EMAIL PROTECTED]> wrote:
> Hello,
>
> please consider the following code:
>
>> {-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies #-}
>>
>> data GADT a where
>>
>> GADT :: GADT ()
>>
>> class Class a b | a -> b
>>
>> instance Cl
Am Dienstag, 23. September 2008 18:19 schrieben Sie:
> On Tue, Sep 23, 2008 at 6:07 PM, Wolfgang Jeltsch
>
> <[EMAIL PROTECTED]> wrote:
> > Hello,
> >
> > please consider the following code:
> >> {-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies #-}
> >>
> >> data GADT a where
> >>
On Tue, Sep 23, 2008 at 6:36 PM, Wolfgang Jeltsch
<[EMAIL PROTECTED]> wrote:
> Pattern matching against the data constructor GADT specializes a to (). Since
> Class uses a functional dependency, it is clear that b has to be ().
True, but it wont work if you provide () as the result and b in the
e
On Tue, Sep 23, 2008 at 9:36 AM, Wolfgang Jeltsch
<[EMAIL PROTECTED]> wrote:
> Am Dienstag, 23. September 2008 18:19 schrieben Sie:
>> On Tue, Sep 23, 2008 at 6:07 PM, Wolfgang Jeltsch
>>
>> <[EMAIL PROTECTED]> wrote:
>> > Hello,
>> >
>> > please consider the following code:
>> >> {-# LANGUAGE GADT
On Tue, Sep 23, 2008 at 9:36 AM, Wolfgang Jeltsch
<[EMAIL PROTECTED]> wrote:
> Am Dienstag, 23. September 2008 18:19 schrieben Sie:
>> On Tue, Sep 23, 2008 at 6:07 PM, Wolfgang Jeltsch
>>
>> <[EMAIL PROTECTED]> wrote:
>> > Hello,
>> >
>> > please consider the following code:
>> >> {-# LANGUAGE GADT
On Tue, Sep 23, 2008 at 9:07 AM, Wolfgang Jeltsch
<[EMAIL PROTECTED]> wrote:
> Hello,
>
> please consider the following code:
>
>> {-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies #-}
>>
>> data GADT a where
>>
>> GADT :: GADT ()
>>
>> class Class a b | a -> b
>>
>> instance Cl
Christian, I'm not sure about the other issues you mentioned but can
probably help with the following.
On Tue, Sep 23, 2008 at 6:38 AM, Christian Maeder
<[EMAIL PROTECTED]> wrote:
>
> But finally installation succeeded (editline is missing and the arrow
> keys don't work).
This means that the edi
You cannot create a normal function "fun". You can make a type class function
fun :: Class a b => GADT a -> b
data GADT a where
GADT :: GADT ()
GADT2 :: GADT String
-- fun1 :: GADT () -> () -- infers type
fun1 g = case g of
(GADT :: GADT ()) -> ()
-- fun2 :: GADT String
Serge D. Mechveliani wrote:
On Fri, Sep 19, 2008 at 08:17:12PM +0100, Ian Lynagh wrote:
On Tue, Sep 16, 2008 at 10:44:53AM +0100, Simon Peyton-Jones wrote:
|
| And still ghc-6.8.3 builds itself from source.
I have no idea how -- Happy has been needed for some time. Maybe someone else
does.
Hi,
On Tue, Sep 23, 2008 at 03:38:56PM +0200, Christian Maeder wrote:
> The error far below is caused by "-perm /a+x" in mk/bindist.mk
> during find:
>
> I've changed it to "-perm -111"
Unfortunately, this will only find files with the executable bit
set for user, group and owner, so it should b
On Tue, Sep 23, 2008 at 1:44 PM, Chris Kuklewicz
<[EMAIL PROTECTED]> wrote:
> You cannot create a normal function "fun". You can make a type class
> function
>
> fun :: Class a b => GADT a -> b
>
>> data GADT a where
>> GADT :: GADT ()
>> GADT2 :: GADT String
>>
>> -- fun1 :: GADT () -> ()
On Tue, Sep 23, 2008 at 08:34:36PM +0200, Matthias Kilian wrote:
> > I've changed it to "-perm -111"
>
> Unfortunately, this will only find files with the executable bit
> set for user, group and owner, so it should be "-perm +111". However,
> even more unfortunately, at least the find(1) on OpenB
Chris Kuklewicz wrote:
I am cross-posting this message to several lists.
I had learned the trick before the documentation was updated. It seems
I have used a very unreliable trick. And the "use castToSTUArray"
suggested alternative is a really poor one since I am not using arrays
at all.
I ran into some problems due to having gmp installed in an unusual
place. I passed --with-gmp-{includes,libraries} to ./configure, set
$CPPFLAGS and $LDFLAGS for ./configure, and set the corresponding
-optl, etc., flags in SRC_HC_OPTS and GHC_CC_OPTS in mk/build.mk.
With all that, the first probl
On 2008 Sep 23, at 9:38, Christian Maeder wrote:
But finally installation succeeded (editline is missing and the arrow
keys don't work). Why are there 2 base packages?
Backward compatibility; older Haskell programs using base-3.x will
still work. (6.10 has unbundled a bunch more libraries fr
19 matches
Mail list logo