Re: [Haskell-cafe] Why so many strings in Network.URI, System.Posix and similar libraries?

2012-03-12 Thread Joey Hess
Jason Dusek wrote:
  :info System.Posix.Env.getEnvironment
 System.Posix.Env.getEnvironment :: IO [(String, String)]
 -- Defined in System.Posix.Env
 
 But there is no law that environment variables must be made of
 characters:

The recent ghc release provides
System.Posix.Env.ByteString.getEnvironment :: IO [(ByteString, ByteString)]

-- 
see shy jo


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


Re: [Haskell-cafe] Helper classes for Generics

2012-03-12 Thread José Pedro Magalhães
Hi Reiner,

It is indeed not strictly necessary to define such helper classes for kind
* generic functions. You do need them for kind * - * functions, though.
Also, I think they should always be used because they help keep things
separate. If we use an implementation of generics with DataKinds [1], then
the helper classes always have a different kind from the user-facing
classes.


Cheers,
Pedro

[1]
http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Kindpolymorphicoverhaul

On Mon, Mar 12, 2012 at 04:27, Reiner Pope reiner.p...@gmail.com wrote:

 Hi all,

 I've been playing with GHC's new generics features (see
 http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for
 instance, the GSerialize class in the above link -- on which one defines
 generic instances.

 It seems to me that this isn't necessary. For example, here's the the
 example from the GHC docs, but without a helper class:

  -- set the phantom type of Rep to (), to avoid ambiguity
  from0 :: Generic a = a - Rep a ()
  from0 = from
 
  data Bit = O | I
 
  class Serialize a where
put :: a - [Bit]
 
default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
put = put . from0
 
  instance Serialize (U1 x) where
put U1 = []
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b) x)
 where
put (x :*: y) = put x ++ put y
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b) x)
 where
put (L1 x) = O : put x
put (R1 x) = I : put x
 
  instance (Serialize (a x)) = Serialize (M1 i c a x) where
put (M1 x) = put x
 
  instance (Serialize a) = Serialize (K1 i a x) where
put (K1 x) = put x

 Is there a reason to prefer using helper classes? Or perhaps we should
 update the wiki page (http://www.haskell.org/haskellwiki/Generics) to
 avoid using helper classes?

 Regards,
 Reiner

 ___
 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] Global Arrays

2012-03-12 Thread Ketil Malde
Clark Gaebel cgae...@csclub.uwaterloo.ca writes:

 In Haskell, what's the canonical way of declaring a top-level array
 (Data.Vector of a huge list of doubles, in my case)? Performance is
 key in my case.

 The straightforward way would just be something like:

 globalArray :: V.Vector Double
 globalArray = V.fromList [ huge list of doubles ]
 {-# NOINLINE globalArray #-}

 However, I don't want to have to run the fromList at runtime.

I think GHC will convert it to an array (and in general evaluate
constants) at compile time (probably requires -O).

-k

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


Re: [Haskell-cafe] using mutable data structures in pure functions

2012-03-12 Thread Stephen Tetley
There is a trick to `nub` where you couldn't implement the internal
lookup list with an (assumed faster) search tree anyway.

`nub` only mandates equality not ordering, so building a ordered
structure like a binary tree is impossible. In practice i would be
hard to beat list as the intermediate structure in this case.

On 12 March 2012 03:38, E R pc88m...@gmail.com wrote:
[Chop]

 For example, consider the definition of Data.List.nub:

 nub l                   = nub' l []
  where
    nub' [] _           = []
    nub' (x:xs) ls
        | x `elem` ls   = nub' xs ls
        | otherwise     = x : nub' xs (x:ls)

 Clearly the memory allocated to ls never escapes nub', so it seems
 that ls could be replaced with a mutable data structure (with an eye
 towards improving performance in special cases).

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


Re: [Haskell-cafe] ANNOUNCE: pipes-core 0.0.1

2012-03-12 Thread Paolo Capriotti
On Mon, Mar 12, 2012 at 3:26 AM, Chris Smith cdsm...@gmail.com wrote:

 With pipes-core (which, recall, is known to be unsound... just felt
 this is a good time for a reminder of that, even though I believe the
 subset that adds tryAwait and forP to be sound), you do get both (pipe
 id) and (forP yield).

I wouldn't say it's unsound, more like not yet proved to be bug-free :)

Note that the latest master fixes all the issues found so far.

I agree that it would be nice to have a proof of correctness, but I
prefer to wait until it stabilizes a bit before embarking in a long
verification of all the cases. Part of the reason to release it now is
so that people can try it out and suggest changes and additions. I am
pretty confident that, if there are other issues, they can be fixed
without significantly altering the interface or the overall approach.

BR,
Paolo

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


Re: [Haskell-cafe] ANNOUNCE: pipes-core 0.0.1

2012-03-12 Thread Paolo Capriotti
On Mon, Mar 12, 2012 at 2:53 AM, Mario Blažević blama...@acanac.net wrote:

    May I enquire what was the reason for the non-termination of idP? Why was
 it not defined as 'forP yield' instead? The following command runs the way I
 expected.

The identity in a homset is unique, and in the case of 'Pipe a b m r',
it happens to be 'idP'. 'forP yield' has its uses, but, as Chris
showed, it's not a real identity.

BR,
Paolo

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


Re: [Haskell-cafe] ANNOUNCE: pipes-core 0.0.1

2012-03-12 Thread Paolo Capriotti
On Sun, Mar 11, 2012 at 10:41 PM, Chris Smith cdsm...@gmail.com wrote:
 On Sun, Mar 11, 2012 at 2:33 PM, Twan van Laarhoven twa...@gmail.com wrote:
 I think you should instead move unwaits in and out of the composition on the
 left side:

    unawait x  (p1 + p2) === (unawait x  p1) + p2

 This makes idP a left-identity for (+), but not a right-identity, since
 you can't move unawaits in and out of p2.

 Not sure how we got to the point of debating which of the category
 laws pipes should break... messy business there.  I'm going to be in
 favor of not breaking the laws at all.  The problem here is that
 composition of chunked pipes requires agreement on the chunk type,
 which gives the type-level guarantees you need that all chunked pipes
 in a horizontal composition (by which I mean composition in the
 category... I think you were calling that vertical?  no matter...)
 share the same chunk type.  Paolo's pipes-extra does this by inventing
 a newtype for chunked pipes, in which the input type appears in the
 result as well.  There are probably some details to quibble with, but
 I think the idea there is correct.  I don't like this idea of
 implicitly just throwing away perfectly good data because the types
 are wrong.  It shows up in the category-theoretic properties of the
 package as a result, but it also shows up in the fact that you're
 *throwing* *away* perfectly good data just because the type system
 doesn't give you a place to put it!  What's become obvious from this
 is that a (ChunkedPipe a b m r) can NOT be modelled correctly as a
 (Pipe a b m r).

I completely agree with this. For the subset consisting of pipes that
never terminate (basically stream processors), it might be possible to
add 'unawait'. However, the example

(idP + unawait x)  await

shows that it's impossible to implement on general pipes without
changing the Pipe type in some deeper way.

ChunkPipe can be somewhat awkward to use because of the newtype
wrapping/unwrapping, but from my experience, there's no need to use it
very much in practice. What you can usually do is insert a
'regularize' Pipe (using ChunkPipe) early in the pipeline which splits
chunks that cross logical boundaries, so that the rest of the
pipeline can deal with chunked input without worrying about leftovers.

BR,
Paolo

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


Re: [Haskell-cafe] Associative prefix operators in Parsec

2012-03-12 Thread Christian Maeder

Am 08.03.2012 17:16, schrieb Troels Henriksen:

Christian Maederchristian.mae...@dfki.de  writes:


The simplest solution is to parse the prefixes yourself and do not put
it into the table.

(Doing the infixes  and | by hand is no big deal, too, and
possibly easier then figuring out the capabilities of
buildExpressionParser)


Is there another solution?  My post was a simplified example to showcase
the problem; in general I would prefer to use a function to build the
expression parser.  I could just write my own that does not have this
problem, and in fact, I already have, I just wanted to know whether
Parsec could be wrangled into shape.


Yes, it certainly could do better. The code for prefix and postfix 
currently looks like:


   termP  = do{ pre  - prefixP
 ; x- term
 ; post - postfixP
 ; return (post (pre x))
 }

This supports (only) one prefix or postfix (or both), where the prefix 
binds stronger than the postfix (although, they have equal precedence).


Problem 1: - - 5 is not supported

Another problem are prefix or postfix operators that bind weaker than 
infixes, like infix ^ and prefix -.


Problem 2: 1 ^ -2 is rejected, although no other parsing is possible.

(The same would apply to a weakly binding postfix operator following the 
left argument: 4+ ^ 5. This would even need some look ahead to find 
out, if + is not an infix and ^ a prefix operator)


(Haskell features these problems, too.)

Maybe the special case of repeated prefixes could be solved by putting 
in the prefix entry twice into the table for the 
currentbuildExpressionParser, but considering possibly equal symbols for 
prefix, postfix or infix symbols seems quite difficult, although only an 
ambiguity needs to be reported.


Cheers C.

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


Re: [Haskell-cafe] Understanding GC time

2012-03-12 Thread Steffen Schuldenzucker



On 03/10/2012 07:50 PM, Thiago Negri wrote:

I see. Thanks for the answers.

Any data structure or source annotation that would prevent that?

For example, if I try the same program to run on a
[1..] list, I'll get an out of memory error for the
single-threaded version. Any way to prevent it without declaring two
different versions of list?



Maybe you'd like to treat your list more like a stream of input data, 
similar to, say, user input via IO? If your algorithms generalize to 
such streams, you can be sure that they don't force the whole list into 
memory (at least not accidentally).


You might want to take a look at iteratees or conduits.

-- Steffen



2012/3/10 Anthony Cowleyacow...@gmail.com:

 From that profiling data, I think you're just seeing a decrease in sharing. 
With one thread, you create the list structure in memory: the first fold could 
consume it in-place, but the second fold is still waiting for its turn.  The 
list is built on the heap so the two folds can both refer to the same list.

With two threads, GHC is being clever and inlining the definition you give for 
list, which is then optimized into two parallel loops. No list on the heap 
means there's not much for the GC to do.

Sharing of index lists like this is a common source of problems. In particular, 
nested loops can make it even trickier to prevent sharing as there may not be 
an opportunity for parallel evaluation.

Anthony

On Mar 10, 2012, at 10:21 AM, Thiago Negrievoh...@gmail.com  wrote:


Hi all.

I wrote a very simple program to try out parallel Haskel and check how
it would look like to make use of more than one core in this language.

When I tried the program with RTS option -N1, total time shows it took
2.48 seconds to complete and around 65% of that time was taken by GC.

Then I tried the same program with RTS options -N2 and total time
decreased to 1.15 seconds as I expected a gain here. But what I didn't
expect is the GC time to drop to 0%.

I guess I'm having trouble to understand the output of the RTS option -s.
Can you enlighten me?


The source for the testing program:


module Main where

import Data.List (foldl1')
import Control.Parallel (par, pseq)
import Control.Arrow (())

f `parApp` (a, b) = a `par` (b `pseq` (f a b))
seqApp = uncurry

main = print result
  where result = (+) `parApp` minMax list
minMax = minlist  maxlist
minlist = foldl1' min
maxlist = foldl1' max
list = [1..1999]



The results on a Windows 7 64bits with an Intel Core 2 Duo, compiled
with GHC from Haskell Platform:

c:\tmp\hspar +RTS -s -N1
par +RTS -s -N1
2000
 803,186,152 bytes allocated in the heap
 859,916,960 bytes copied during GC
 233,465,740 bytes maximum residency (10 sample(s))
  30,065,860 bytes maximum slop
 483 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  1523 collections, 0 parallel,  0.80s,  0.75s elapsed
  Generation 1:10 collections, 0 parallel,  0.83s,  0.99s elapsed

  Parallel GC work balance: nan (0 / 0, ideal 1)

MUT time (elapsed)   GC time  (elapsed)
  Task  0 (worker) :0.00s(  0.90s)   0.00s(  0.06s)
  Task  1 (worker) :0.00s(  0.90s)   0.00s(  0.00s)
  Task  2 (bound)  :0.86s(  0.90s)   1.62s(  1.69s)

  SPARKS: 1 (0 converted, 0 pruned)

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.86s  (  0.90s elapsed)
  GCtime1.62s  (  1.74s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time2.48s  (  2.65s elapsed)

  %GC time  65.4%  (65.9% elapsed)

  Alloc rate936,110,032 bytes per MUT second

  Productivity  34.6% of total user, 32.4% of total elapsed

gc_alloc_block_sync: 0
whitehole_spin: 0
gen[0].sync_large_objects: 0
gen[1].sync_large_objects: 0


c:\tmp\hspar +RTS -s -N2
par +RTS -s -N2
2000
   1,606,279,644 bytes allocated in the heap
  74,924 bytes copied during GC
  28,340 bytes maximum residency (1 sample(s))
  29,004 bytes maximum slop
   2 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  1566 collections,  1565 parallel,  0.00s,  0.01s elapsed
  Generation 1: 1 collections, 1 parallel,  0.00s,  0.00s elapsed

  Parallel GC work balance: 1.78 (15495 / 8703, ideal 2)

MUT time (elapsed)   GC time  (elapsed)
  Task  0 (worker) :0.00s(  0.59s)   0.00s(  0.00s)
  Task  1 (worker) :0.58s(  0.59s)   0.00s(  0.01s)
  Task  2 (bound)  :0.58s(  0.59s)   0.00s(  0.00s)
  Task  3 (worker) :0.00s(  0.59s)   0.00s(  0.00s)

  SPARKS: 1 (1 converted, 0 pruned)

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time1.15s  (  0.59s elapsed)
  GCtime0.00s  (  0.01s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time1.15s  (  0.61s elapsed)

  %GC time   0.0%  (2.4% elapsed)

  Alloc 

Re: [Haskell-cafe] ANNOUNCE: pipes-core 0.0.1

2012-03-12 Thread Twan van Laarhoven

On 11/03/12 23:41, Chris Smith wrote:

On Sun, Mar 11, 2012 at 2:33 PM, Twan van Laarhoventwa...@gmail.com  wrote:

I think you should instead move unwaits in and out of the composition on the
left side:

unawait x  (p1+  p2) === (unawait x  p1)+  p2

This makes idP a left-identity for (+), but not a right-identity, since
you can't move unawaits in and out of p2.


Not sure how we got to the point of debating which of the category
laws pipes should break... messy business there.  I'm going to be in
favor of not breaking the laws at all.  The problem here is that
composition of chunked pipes requires agreement on the chunk type,
which gives the type-level guarantees you need that all chunked pipes
in a horizontal composition (by which I mean composition in the
category... I think you were calling that vertical?  no matter...)
share the same chunk type.  Paolo's pipes-extra does this by inventing
a newtype for chunked pipes, in which the input type appears in the
result as well.  There are probably some details to quibble with, but
I think the idea there is correct.  I don't like this idea of
implicitly just throwing away perfectly good data because the types
are wrong.  It shows up in the category-theoretic properties of the
package as a result, but it also shows up in the fact that you're
*throwing* *away* perfectly good data just because the type system
doesn't give you a place to put it!  What's become obvious from this
is that a (ChunkedPipe a b m r) can NOT be modelled correctly as a
(Pipe a b m r).


Agreed. There are many things to be said for making sure that Pipe is a 
real category. I suppose the morally correct thing to do is, as you 
said, have a separate ChunkedPipe type. That would make the type system 
guarantee that there are no calls to 'unawait' in the second part of a 
categorical composition.


The API could even look something like this:

data Chunk
data NoChunk
data Pipe chunkiness a b m r

await :: Pipe anyChunk a b m a
yield :: b - Pipe anyChunk a b m ()
unawait :: a - Pipe Chunk a b m ()

runChunkedPipe :: Pipe Chunk a b m r - Pipe NoChunk a b m r

-- composition in the category
(+) :: Pipe NoChunk a b m r - Pipe NoChunk b c m r
  - Pipe NoChunk a c m r

The following generalization of category composition is still fine:

compose :: Pipe anyChunk a b m r - Pipe NoChunk b c m r
- Pipe anyChunk a c m r

But this would not be:

almostEntirelyNotUnlikeCompose :: Pipe anyChunk a b m r
 - Pipe discardChunksHere b c m r - Pipe anyChunk a c m r


By the way, a ChunkedPipe can be implemented not only as
type ChunkedPipe a b m r = StateT [a] (Pipe a b m) r
but also as
type ChunkedPipe a b m r = CodensityT (Pipe a b m) r
by using the 'feed' function to implement unawait.


Twan

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


Re: [Haskell-cafe] Question about concurrency, threads and GC

2012-03-12 Thread Paul Graphov
Hi!

Thanks to all who responded! I got a lot of information to read and think about.
For now I decided to use stm-channelize as the simplest approach which
seem to be enough.

On Mon, Mar 5, 2012 at 9:50 PM, Alexander V Vershilov
alexander.vershi...@gmail.com wrote:
 Hello.

 I've also written simple chat server based on conduits and stm channels

 https://github.com/qnikst/chat-server/blob/master/src/Main.hs

 it has quite similar aproach and maybe this solution can be used together
 to have better results.

 --
 Alexander Vershilov

 Sat, Mar 03, 2012 at 02:05:17AM -0500, Joey Adams wrote
 On Fri, Mar 2, 2012 at 7:34 PM, Joey Adams joeyadams3.14...@gmail.com 
 wrote:
  I'll try to put together a simple chat server example, like the one I
  wrote for stm-channelize.

 Here it is:

     https://github.com/joeyadams/haskell-chat-server-example

 See, in particular, the serveLoop function.  When a message is
 received from the client, it is written to the send channel of every
 other client.  When a message is written on the client's own send
 channel, it is transmitted to the client.  The primary thread for the
 client waits until one of the worker threads signals completion, then
 kills both of the worker threads.

 I hope this example gives you some ideas.

 -Joey

 ___
 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] Global Arrays

2012-03-12 Thread Clark Gaebel
Is there any proof of this? I'm not familiar enough with core to check.

On Mon, Mar 12, 2012 at 3:48 AM, Ketil Malde ke...@malde.org wrote:
 Clark Gaebel cgae...@csclub.uwaterloo.ca writes:

 In Haskell, what's the canonical way of declaring a top-level array
 (Data.Vector of a huge list of doubles, in my case)? Performance is
 key in my case.

 The straightforward way would just be something like:

 globalArray :: V.Vector Double
 globalArray = V.fromList [ huge list of doubles ]
 {-# NOINLINE globalArray #-}

 However, I don't want to have to run the fromList at runtime.

 I think GHC will convert it to an array (and in general evaluate
 constants) at compile time (probably requires -O).

 -k


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


Re: [Haskell-cafe] ANNOUNCE: pipes-core 0.0.1

2012-03-12 Thread Chris Smith
On Mon, Mar 12, 2012 at 3:26 AM, Paolo Capriotti p.caprio...@gmail.com wrote:
 I wouldn't say it's unsound, more like not yet proved to be bug-free :)

 Note that the latest master fixes all the issues found so far.

I was referring to the released version of pipes-core, for which
known to be unsound is an accurate description.  Good to hear that
you've got a fix coming, though.  Given the history here, maybe
working out the proofs of the category laws sooner rather than later
would be a good thing.  I'll have a look today and see if I can bang
out a proof of the category laws for your new code without ensure.

It will then be interesting to see how that compares to Gabriel's
approach, which at this point we've heard a bit about but I haven't
seen.

-- 
Chris Smith

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


[Haskell-cafe] Is there a better way to subtyping?

2012-03-12 Thread Jeff Shaw
More specifically, if I have a record type from which I construct 
multiple sub-record types, and I want to store these in a collection 
which I want to map over while preserving the ability to get at the 
sub-fields, is there a better way to do it than to have an enumeration 
for the sub-types and then use Dynamic? I also have a nastier version 
that doesn't require the enumeration, which throws an exception when 
fromDynamic can't return a value with one of the expected types.


{-# LANGUAGE Rank2Types, DeriveDataTypeable #-}
module Super where

import Data.Dynamic
import Data.Typeable
import Data.Maybe

data Super a = Super { commonFields :: (), subFields :: a }
deriving Typeable

data SubTypes = SubA | SubB | SubC

data A = A { aFields :: () }
deriving Typeable

data B = B { bFields :: () }
deriving Typeable

data C = C { cFields :: () }
deriving Typeable

doSomethingWithSubType :: (Super A - ()) - (Super B - ()) - (Super C 
- ()) - (SubTypes, Dynamic) - Maybe ()
doSomethingWithSubType a _ _ (SubA, dynamic) = fromDynamic dynamic = 
return . a
doSomethingWithSubType _ b _ (SubB, dynamic) = fromDynamic dynamic = 
return . b
doSomethingWithSubType _ _ c (SubC, dynamic) = fromDynamic dynamic = 
return . c


doSomethingWithSubType2 :: (Super A - ()) - (Super B - ()) - (Super 
C - ()) - Dynamic - ()

doSomethingWithSubType2 a b c dynamic =
let dynamicAsA = fromDynamic dynamic :: Maybe (Super A)
dynamicAsB = fromDynamic dynamic :: Maybe (Super B)
dynamicAsC = fromDynamic dynamic :: Maybe (Super C) in
head $ catMaybes [ dynamicAsA = return . a
 , dynamicAsB = return . b
 , dynamicAsC = return . c]


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


Re: [Haskell-cafe] Helper classes for Generics

2012-03-12 Thread Yves Parès
I'd have a question concerning GHC.Generics: how does it relate to SYB's
Data.Generics?
Is it intended to replace it or complete it?
In other words: does class Data.Generics.Data class do things that class
GHC.Generics.Generic can't do?


Le 12 mars 2012 04:27, Reiner Pope reiner.p...@gmail.com a écrit :

 Hi all,

 I've been playing with GHC's new generics features (see
 http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for
 instance, the GSerialize class in the above link -- on which one defines
 generic instances.

 It seems to me that this isn't necessary. For example, here's the the
 example from the GHC docs, but without a helper class:

  -- set the phantom type of Rep to (), to avoid ambiguity
  from0 :: Generic a = a - Rep a ()
  from0 = from
 
  data Bit = O | I
 
  class Serialize a where
put :: a - [Bit]
 
default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
put = put . from0
 
  instance Serialize (U1 x) where
put U1 = []
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b) x)
 where
put (x :*: y) = put x ++ put y
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b) x)
 where
put (L1 x) = O : put x
put (R1 x) = I : put x
 
  instance (Serialize (a x)) = Serialize (M1 i c a x) where
put (M1 x) = put x
 
  instance (Serialize a) = Serialize (K1 i a x) where
put (K1 x) = put x

 Is there a reason to prefer using helper classes? Or perhaps we should
 update the wiki page (http://www.haskell.org/haskellwiki/Generics) to
 avoid using helper classes?

 Regards,
 Reiner

 ___
 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] Helper classes for Generics

2012-03-12 Thread José Pedro Magalhães
Hi Yves,

GHC.Generics [1] and SYB [2] are two rather different approaches to generic
programming. There are things that can be done in one but not in the other,
and there are things that are easier on one rather than the other. For
instance, SYB tends to be very useful for large AST transformations, with
functions that have a general behaviour but a couple of particular cases
for a few constructors. GHC.Generics, on the other hand, can encode
functions such as generic fmap and traverse. It lends itself better to
optimisation since it doesn't use runtime casts, and as such tends to be
faster than SYB. It isn't planned to replace SYB.


Cheers,
Pedro

[1] http://www.haskell.org/haskellwiki/Generics
[2] http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB

On Mon, Mar 12, 2012 at 16:35, Yves Parès yves.pa...@gmail.com wrote:

 I'd have a question concerning GHC.Generics: how does it relate to SYB's
 Data.Generics?
 Is it intended to replace it or complete it?
 In other words: does class Data.Generics.Data class do things that class
 GHC.Generics.Generic can't do?


 Le 12 mars 2012 04:27, Reiner Pope reiner.p...@gmail.com a écrit :

  Hi all,

 I've been playing with GHC's new generics features (see
 http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for
 instance, the GSerialize class in the above link -- on which one defines
 generic instances.

 It seems to me that this isn't necessary. For example, here's the the
 example from the GHC docs, but without a helper class:

  -- set the phantom type of Rep to (), to avoid ambiguity
  from0 :: Generic a = a - Rep a ()
  from0 = from
 
  data Bit = O | I
 
  class Serialize a where
put :: a - [Bit]
 
default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
put = put . from0
 
  instance Serialize (U1 x) where
put U1 = []
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b) x)
 where
put (x :*: y) = put x ++ put y
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b) x)
 where
put (L1 x) = O : put x
put (R1 x) = I : put x
 
  instance (Serialize (a x)) = Serialize (M1 i c a x) where
put (M1 x) = put x
 
  instance (Serialize a) = Serialize (K1 i a x) where
put (K1 x) = put x

 Is there a reason to prefer using helper classes? Or perhaps we should
 update the wiki page (http://www.haskell.org/haskellwiki/Generics) to
 avoid using helper classes?

 Regards,
 Reiner

 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Helper classes for Generics

2012-03-12 Thread Yves Parès
Thanks for the clarification.
But could not class Data have been used for generic Deriving of classes? I
imagine it would have been harder, but I fail to see if would have been
possible...

Le 12 mars 2012 16:58, José Pedro Magalhães j...@cs.uu.nl a écrit :

 Hi Yves,

 GHC.Generics [1] and SYB [2] are two rather different approaches to
 generic programming. There are things that can be done in one but not in
 the other, and there are things that are easier on one rather than the
 other. For instance, SYB tends to be very useful for large AST
 transformations, with functions that have a general behaviour but a couple
 of particular cases for a few constructors. GHC.Generics, on the other
 hand, can encode functions such as generic fmap and traverse. It lends
 itself better to optimisation since it doesn't use runtime casts, and as
 such tends to be faster than SYB. It isn't planned to replace SYB.


 Cheers,
 Pedro

 [1] http://www.haskell.org/haskellwiki/Generics
 [2] http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB


 On Mon, Mar 12, 2012 at 16:35, Yves Parès yves.pa...@gmail.com wrote:

 I'd have a question concerning GHC.Generics: how does it relate to SYB's
 Data.Generics?
 Is it intended to replace it or complete it?
 In other words: does class Data.Generics.Data class do things that class
 GHC.Generics.Generic can't do?


 Le 12 mars 2012 04:27, Reiner Pope reiner.p...@gmail.com a écrit :

  Hi all,

 I've been playing with GHC's new generics features (see
 http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for
 instance, the GSerialize class in the above link -- on which one defines
 generic instances.

 It seems to me that this isn't necessary. For example, here's the the
 example from the GHC docs, but without a helper class:

  -- set the phantom type of Rep to (), to avoid ambiguity
  from0 :: Generic a = a - Rep a ()
  from0 = from
 
  data Bit = O | I
 
  class Serialize a where
put :: a - [Bit]
 
default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
put = put . from0
 
  instance Serialize (U1 x) where
put U1 = []
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b) x)
 where
put (x :*: y) = put x ++ put y
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b) x)
 where
put (L1 x) = O : put x
put (R1 x) = I : put x
 
  instance (Serialize (a x)) = Serialize (M1 i c a x) where
put (M1 x) = put x
 
  instance (Serialize a) = Serialize (K1 i a x) where
put (K1 x) = put x

 Is there a reason to prefer using helper classes? Or perhaps we should
 update the wiki page (http://www.haskell.org/haskellwiki/Generics) to
 avoid using helper classes?

 Regards,
 Reiner

 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Helper classes for Generics

2012-03-12 Thread José Pedro Magalhães
It could, yes. Actually, using DefaultSignatures you can probably use SYB
for defining classes with generic default methods, by adding Data and
Typeable constraints instead of Generic.


Cheers,
Pedro

2012/3/12 Yves Parès yves.pa...@gmail.com

 Thanks for the clarification.
 But could not class Data have been used for generic Deriving of classes? I
 imagine it would have been harder, but I fail to see if would have been
 possible...

 Le 12 mars 2012 16:58, José Pedro Magalhães j...@cs.uu.nl a écrit :

 Hi Yves,

 GHC.Generics [1] and SYB [2] are two rather different approaches to
 generic programming. There are things that can be done in one but not in
 the other, and there are things that are easier on one rather than the
 other. For instance, SYB tends to be very useful for large AST
 transformations, with functions that have a general behaviour but a couple
 of particular cases for a few constructors. GHC.Generics, on the other
 hand, can encode functions such as generic fmap and traverse. It lends
 itself better to optimisation since it doesn't use runtime casts, and as
 such tends to be faster than SYB. It isn't planned to replace SYB.


 Cheers,
 Pedro

 [1] http://www.haskell.org/haskellwiki/Generics
 [2] http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB


 On Mon, Mar 12, 2012 at 16:35, Yves Parès yves.pa...@gmail.com wrote:

 I'd have a question concerning GHC.Generics: how does it relate to SYB's
 Data.Generics?
 Is it intended to replace it or complete it?
 In other words: does class Data.Generics.Data class do things that class
 GHC.Generics.Generic can't do?


 Le 12 mars 2012 04:27, Reiner Pope reiner.p...@gmail.com a écrit :

  Hi all,

 I've been playing with GHC's new generics features (see
 http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html).
 All the documentation I've seen suggests creating a helper class -- for
 instance, the GSerialize class in the above link -- on which one defines
 generic instances.

 It seems to me that this isn't necessary. For example, here's the the
 example from the GHC docs, but without a helper class:

  -- set the phantom type of Rep to (), to avoid ambiguity
  from0 :: Generic a = a - Rep a ()
  from0 = from
 
  data Bit = O | I
 
  class Serialize a where
put :: a - [Bit]
 
default put :: (Generic a, Serialize (Rep a ())) = a - [Bit]
put = put . from0
 
  instance Serialize (U1 x) where
put U1 = []
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :*: b)
 x) where
put (x :*: y) = put x ++ put y
 
  instance (Serialize (a x), Serialize (b x)) = Serialize ((a :+: b)
 x) where
put (L1 x) = O : put x
put (R1 x) = I : put x
 
  instance (Serialize (a x)) = Serialize (M1 i c a x) where
put (M1 x) = put x
 
  instance (Serialize a) = Serialize (K1 i a x) where
put (K1 x) = put x

 Is there a reason to prefer using helper classes? Or perhaps we should
 update the wiki page (http://www.haskell.org/haskellwiki/Generics) to
 avoid using helper classes?

 Regards,
 Reiner

 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Empty Input list

2012-03-12 Thread Kevin Clees
Dear Haskell friends,

what can I do, if a function gets an empty input list? I want, that it only 
returns nothing.
This is my source code:

tmp:: [(Int, Int)] - Int - (Int, Int)
tmp (x:xs) y
| y == 1 = x
| y  1 = tmp xs (y-1)

If this function gets an empty list, he throws Exception: 
sortAlgo.hs:(18,1)-(21,44): Non-exhaustive patterns in function Main.tmp

*Main tmp [(1,2),(3,2)] 1
(1,2)
*Main tmp [(1,2),(3,2)] 2
(3,2)
*Main tmp [] 1
*** Exception: sortAlgo.hs:(20,1)-(22,44): Non-exhaustive patterns in function 
Main.listElementIntInt


Thank you for any help !

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


Re: [Haskell-cafe] IO() and other datatypes

2012-03-12 Thread Kevin Clees
Great, Thank you !

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


Re: [Haskell-cafe] Empty Input list

2012-03-12 Thread Chris Smith
On Mon, Mar 12, 2012 at 2:41 PM, Kevin Clees k.cl...@web.de wrote:
 what can I do, if a function gets an empty input list? I want, that it only 
 returns nothing.
 This is my source code:

 tmp:: [(Int, Int)] - Int - (Int, Int)
 tmp (x:xs) y
        | y == 1 = x
        | y  1 = tmp xs (y-1)

It's not clear what you mean by returns nothing when the result is
(Int, Int)... there is no nothing value of that type.  But you can
add another equation to handle empty lists one you decide what to
return in that case.  For example, after (or before) the existing
equation, add:

tmp [] y = (-1, -1)

Or, you may want to use a Maybe type for the return... which would
mean there *is* a Nothing value you can return:

tmp:: [(Int, Int)] - Int - Maybe (Int, Int)
tmp (x:xs) y
       | y == 1 = Just x
       | y  1  = tmp xs (y-1)
tmp [] y = Nothing

Does that help?
-- 
Chris Smith

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


Re: [Haskell-cafe] Empty Input list

2012-03-12 Thread Chris Smith
Oh, and just to point this out, the function you're writing already
exists in Data.List.  It's called (!!).  Well, except that it's zero
indexed, so your function is more like:

tmp xs y = xs !! (y-1)

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


Re: [Haskell-cafe] Empty Input list

2012-03-12 Thread Kevin Clees
Hey Chris,

thank you for your help! Your last comment with the (!!)-thing was a very good 
idea! 

Now my function looks like this: 

tmp:: [(Int, Int)] - Int - (Int, Int)
tmp [] y = (0,0)
tmp xs y = xs !! (y-1)

If the function returns (0,0) it will blocked by another  function. 
If I want to use the maybe return, I get some new trouble that I don't like - 
so I chose that way :)

Thank you again 
Kevin



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


Re: [Haskell-cafe] Empty Input list

2012-03-12 Thread Chris Smith
On Mon, Mar 12, 2012 at 3:14 PM, Kevin Clees k.cl...@web.de wrote:
 Now my function looks like this:

 tmp:: [(Int, Int)] - Int - (Int, Int)
 tmp [] y = (0,0)
 tmp xs y = xs !! (y-1)

Just a warning that this will still crash if the list is non-empty by
the index exceeds the length.  That's because your function is no
longer recursive, so you only catch the case where the top-level list
is empty.  The drop function doesn't crash when dropping too many
elements though, so you can do this and get a non-recursive function
that's still total:

tmp :: [(Int,Int)] - Int - (Int, Int)
tmp xs y = case drop (y-1) xs of
[] - (0,0)
Just (x:_) - x

-- 
Chris Smith

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


[Haskell-cafe] Leksah Install Issue (cabal experts please help)

2012-03-12 Thread Hamish Mackenzie
pozic raised an install issue on IRC.  Basically he was getting...

~$ cabal install leksah-server
Resolving dependencies...
cabal: Couldn't read cabal file leksah-server/0.12.0.3/leksah-server.cabal

To reproduce this issue.  Use GHC 6.12.3, 7.0.3 or 7.2.2 to cabal install 
cabal-install then run cabal install leksah-server.

To work around it install GHC 7.0.4 or 7.4.1 and use it to run cabal install 
cabal-install (then you can go back to the old GHC if you want).


Cabal experts, is there a better work around than this?

The current leksah-server.cabal requires Cabal 1.10.2 or greater because it has 
a test-suite section for cabal test.

This is fine if you have installed cabal-install with GHC 7.0.4 or 7.4.1, but 
if you install cabal-install with older versions of GHC (including 7.2.2) then 
it can't handle the file format.

I could upload a new leksah-server to hackage (with the unit tests removed), 
but that would not stop cabal-install from failing to read leksah-server 
0.12.0.3 and bombing out (there is already a 0.12.0.4 and it is not getting to 
that one).

Even if you cabal unpack and then modify the .cabal file and run cabal 
install it still fails with the same error.

If you can think of a better solution than asking users to install GHC 7.0.4 or 
7.4.1 to build cabal-install, then please let me know.




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


Re: [Haskell-cafe] Leksah Install Issue (cabal experts please help)

2012-03-12 Thread Ivan Lazar Miljenovic
On 13 March 2012 12:33, Hamish Mackenzie
hamish.k.macken...@googlemail.com wrote:
 pozic raised an install issue on IRC.  Basically he was getting...

 ~$ cabal install leksah-server
 Resolving dependencies...
 cabal: Couldn't read cabal file leksah-server/0.12.0.3/leksah-server.cabal

 To reproduce this issue.  Use GHC 6.12.3, 7.0.3 or 7.2.2 to cabal install 
 cabal-install then run cabal install leksah-server.

 To work around it install GHC 7.0.4 or 7.4.1 and use it to run cabal install 
 cabal-install (then you can go back to the old GHC if you want).


 Cabal experts, is there a better work around than this?

 The current leksah-server.cabal requires Cabal 1.10.2 or greater because it 
 has a test-suite section for cabal test.

 This is fine if you have installed cabal-install with GHC 7.0.4 or 7.4.1, but 
 if you install cabal-install with older versions of GHC (including 7.2.2) 
 then it can't handle the file format.

 I could upload a new leksah-server to hackage (with the unit tests removed), 
 but that would not stop cabal-install from failing to read leksah-server 
 0.12.0.3 and bombing out (there is already a 0.12.0.4 and it is not getting 
 to that one).

 Even if you cabal unpack and then modify the .cabal file and run cabal 
 install it still fails with the same error.

How did you modify it?  Did you change the cabal-version field as well?


 If you can think of a better solution than asking users to install GHC 7.0.4 
 or 7.4.1 to build cabal-install, then please let me know.

Just build a newer version of cabal-install based upon Cabal-1.10 ?





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



-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] Leksah Install Issue (cabal experts please help)

2012-03-12 Thread Hamish Mackenzie
On 13 Mar 2012, at 15:56, Ivan Lazar Miljenovic wrote:
 Even if you cabal unpack and then modify the .cabal file and run cabal 
 install it still fails with the same error.
 
 How did you modify it?  Did you change the cabal-version field as well?

I changed cabal-version and removed the test-suites.  I think it must be 
looking at all the available versions of the package (in hackage).

 If you can think of a better solution than asking users to install GHC 7.0.4 
 or 7.4.1 to build cabal-install, then please let me know.
 
 Just build a newer version of cabal-install based upon Cabal-1.10 ?


I just tried this and it works...

cabal install Cabal-1.10.0.2
cabal install cabal-install
cabal install leksah-server

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


Re: [Haskell-cafe] Leksah Install Issue (cabal experts please help)

2012-03-12 Thread Hamish Mackenzie

On 13 Mar 2012, at 16:51, Hamish Mackenzie wrote:

 On 13 Mar 2012, at 15:56, Ivan Lazar Miljenovic wrote:
 Even if you cabal unpack and then modify the .cabal file and run cabal 
 install it still fails with the same error.
 
 How did you modify it?  Did you change the cabal-version field as well?
 
 I changed cabal-version and removed the test-suites.  I think it must be 
 looking at all the available versions of the package (in hackage).
 
 If you can think of a better solution than asking users to install GHC 
 7.0.4 or 7.4.1 to build cabal-install, then please let me know.
 
 Just build a newer version of cabal-install based upon Cabal-1.10 ?
 
 
 I just tried this and it works...
 
 cabal install Cabal-1.10.0.2
 cabal install cabal-install
 cabal install leksah-server
 
 Thanks Ivan

Oops transposed the last two parts of the version number.  It should should 
have read...

cabal install Cabal-1.10.2.0
cabal install cabal-install
cabal install leksah-server
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Leksah Install Issue (cabal experts please help)

2012-03-12 Thread Hamish Mackenzie

On 13 Mar 2012, at 16:56, Hamish Mackenzie wrote:

 
 On 13 Mar 2012, at 16:51, Hamish Mackenzie wrote:
 
 On 13 Mar 2012, at 15:56, Ivan Lazar Miljenovic wrote:
 Even if you cabal unpack and then modify the .cabal file and run cabal 
 install it still fails with the same error.
 
 How did you modify it?  Did you change the cabal-version field as well?
 
 I changed cabal-version and removed the test-suites.  I think it must be 
 looking at all the available versions of the package (in hackage).
 
 If you can think of a better solution than asking users to install GHC 
 7.0.4 or 7.4.1 to build cabal-install, then please let me know.
 
 Just build a newer version of cabal-install based upon Cabal-1.10 ?
 
 
 I just tried this and it works...
 
 cabal install Cabal-1.10.0.2
 cabal install cabal-install
 cabal install leksah-server
 
 Thanks Ivan
 
 Oops transposed the last two parts of the version number.  It should should 
 have read...
 
 cabal install Cabal-1.10.2.0
 cabal install cabal-install
 cabal install leksah-server

This also works...
cabal install --constrain='Cabal=1.10.2' cabal-install
cabal install leksah-server



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


Re: [Haskell-cafe] Leksah Install Issue (cabal experts please help)

2012-03-12 Thread Ivan Lazar Miljenovic
On 13 March 2012 15:03, Hamish Mackenzie
hamish.k.macken...@googlemail.com wrote:

 On 13 Mar 2012, at 16:56, Hamish Mackenzie wrote:


 On 13 Mar 2012, at 16:51, Hamish Mackenzie wrote:

 On 13 Mar 2012, at 15:56, Ivan Lazar Miljenovic wrote:
 Even if you cabal unpack and then modify the .cabal file and run cabal 
 install it still fails with the same error.

 How did you modify it?  Did you change the cabal-version field as well?

 I changed cabal-version and removed the test-suites.  I think it must be 
 looking at all the available versions of the package (in hackage).

 If you can think of a better solution than asking users to install GHC 
 7.0.4 or 7.4.1 to build cabal-install, then please let me know.

 Just build a newer version of cabal-install based upon Cabal-1.10 ?


 I just tried this and it works...

 cabal install Cabal-1.10.0.2
 cabal install cabal-install
 cabal install leksah-server

 Thanks Ivan

 Oops transposed the last two parts of the version number.  It should should 
 have read...

 cabal install Cabal-1.10.2.0
 cabal install cabal-install
 cabal install leksah-server

 This also works...
 cabal install --constrain='Cabal=1.10.2' cabal-install
 cabal install leksah-server

Wouldn't just a cabal update  cabal install cabal-install work to
bring in the newest version of cabal-install (which requires
Cabal-1.10.*) ?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] Empty Input list

2012-03-12 Thread Chris Wong
On Tue, Mar 13, 2012 at 12:24 PM, Chris Smith cdsm...@gmail.com wrote:
 On Mon, Mar 12, 2012 at 3:14 PM, Kevin Clees k.cl...@web.de wrote:
 Now my function looks like this:

 tmp:: [(Int, Int)] - Int - (Int, Int)
 tmp [] y = (0,0)
 tmp xs y = xs !! (y-1)

 Just a warning that this will still crash if the list is non-empty by
 the index exceeds the length.  That's because your function is no
 longer recursive, so you only catch the case where the top-level list
 is empty.  The drop function doesn't crash when dropping too many
 elements though, so you can do this and get a non-recursive function
 that's still total:

 tmp :: [(Int,Int)] - Int - (Int, Int)
 tmp xs y = case drop (y-1) xs of
    []         - (0,0)
    Just (x:_) - x

That last line should be

(x:_) - x

without the Just. Hopefully that'll save a bit of confusion.

Chris

 --
 Chris Smith

 ___
 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] Leksah Install Issue (cabal experts please help)

2012-03-12 Thread Hamish Mackenzie

 This also works...
 cabal install --constrain='Cabal=1.10.2' cabal-install
 cabal install leksah-server
 
 Wouldn't just a cabal update  cabal install cabal-install work to
 bring in the newest version of cabal-install (which requires
 Cabal-1.10.*) ?

Cabal 1.10.1 is installed with ghc 7.0.3 and 7.2.2

That is the one that causes the problem.

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


Re: [Haskell-cafe] Leksah Install Issue (cabal experts please help)

2012-03-12 Thread Ivan Lazar Miljenovic
On 13 March 2012 15:28, Hamish Mackenzie
hamish.k.macken...@googlemail.com wrote:

 This also works...
 cabal install --constrain='Cabal=1.10.2' cabal-install
 cabal install leksah-server

 Wouldn't just a cabal update  cabal install cabal-install work to
 bring in the newest version of cabal-install (which requires
 Cabal-1.10.*) ?

 Cabal 1.10.1 is installed with ghc 7.0.3 and 7.2.2

 That is the one that causes the problem.

Hmmm, interesting that the problem is that specific.  Though I would
have thought that the cabal install invocation would have upgraded
Cabal as well...

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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