Re: [Haskell-cafe] Rank-2 types in classes

2011-03-03 Thread oleg

Yves Pare`s  wrote:
 I'm working on a library which aims to be a generic interface for 2D
 rendering. To do that, one of my goals is to enable each implementation of
 this interface to run in its own monad (most of the time an overlay to IO),
 thus giving me the following class

 class (Monad (IM i x)) = Impl i x where
 data IM i x :: * - *

 (where IM means Implementation Monad)

 I would like to write something like :

 class (forall x. Monad (IM i x)) = Impl i where
 data IM i :: * - * - *

It is not clear if the class constraint is really needed. As an aside,
a class constraint is perhaps a bit of mis-feature of type classes: it sure
improves convenience by making signatures shorter. But it isn't really
necessary. Perhaps there are other, better ways of achieving the
convenience (the constraint alias proposal comes to mind).

If we drop the class constraint, we can move Monad (IM i x) as the
constraint on specific methods of the Impl class. The implicit uiniversal
quantification on x is well allowed then. For example:

 class Impl (i :: * - *) where
 data IM i :: * - * - *
 foo :: Monad (IM i x) = Int - IM i x Int
 bar :: Monad (IM i x) = IM i x Int - IM i x Bool
 cast :: IM i x a - IM i y a

 data Window

 instance Impl IO where
 newtype IM IO x a = IMIO (IO a)
 foo = IMIO . return
 bar (IMIO x) = IMIO (fmap ( 42) x)
 cast (IMIO x) = IMIO x

 test :: (Monad (IM i Window), Impl i) = IM i Window Int - IM i x Bool
 test = cast . bar

Perhaps this isn't what you had in mind; I more elaborate example
would help then.

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


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread Andrew Butterfield

On 3 Mar 2011, at 07:05, Hauschild, Klaus (EXT) wrote:

 Hi Haskellers,
  
 whats your Haskell IDE of choise? Currently I use leksah. Is the EclipseFP 
 Plugin for Eclipse a real alternative?

WinEdt*/MikTex/GHCi

do leksah/EclipseFP support literate haskell programming (mix of .tex and .lhs 
files) ?


* not to be confused with WinEdit !

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


Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204
Foundations and Methods Research Group Director.
School of Computer Science and Statistics,
Room F.13, O'Reilly Institute, Trinity College, University of Dublin
http://www.cs.tcd.ie/Andrew.Butterfield/


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


Re: [Haskell-cafe] operations on lists with continuations

2011-03-03 Thread Mark Lentczner
To make up for my total misunderstanding of what you were asking
before, I hereby offer you the Plumbing module, available here:
 
https://bitbucket.org/mtnviewmark/haskell-playground/src/2d022b576c4e/Plumbing.hs

With it, I think you can construct the kinds of pipelines you describe
with the composition aspects you desire:

 :load Plumbing.hs
[1 of 1] Compiling Plumbing ( Plumbing.hs, interpreted )
Ok, modules loaded: Plumbing.
 let filterUntil cond start end = (passUntil (=start) =|= pfilter cond) =+= 
 passWhile (end)
 let filterUntilPlus1 cond start end = filterUntil cond start end =+= pass 1
 filterUntil even 10 15 `pump` [1..]
[2,4,6,8,10,11,12,13,14]
 filterUntilPlus1 even 10 15 `pump` [1..]
[2,4,6,8,10,11,12,13,14,15]

- Mark

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


[Haskell-cafe] Project structure

2011-03-03 Thread Hauschild, Klaus (EXT)
Hi Haskellers,

is there a recommended structure for Haskell projects. I like the Maven way 
(http://maven.apache.org/guides/introduction/introduction-to-the-standard-directory-layout.html)
 for Java projects. How to separate productive from test code, how to separate 
source code from other resources?

Thanks

Klaus

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


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread JP Moresmau
On Thu, Mar 3, 2011 at 9:12 AM, Andrew Butterfield
andrew.butterfi...@cs.tcd.ie wrote:

 On 3 Mar 2011, at 07:05, Hauschild, Klaus (EXT) wrote:

 Hi Haskellers,

 whats your Haskell IDE of choise? Currently I use leksah. Is the EclipseFP
 Plugin for Eclipse a real alternative?

 WinEdt*/MikTex/GHCi
 do leksah/EclipseFP support literate haskell programming (mix of .tex and
 .lhs files) ?

 * not to be confused with WinEdit !


 Thanks

 Klaus


 
 Andrew Butterfield     Tel: +353-1-896-2517     Fax: +353-1-677-2204
 Foundations and Methods Research Group Director.
 School of Computer Science and Statistics,
 Room F.13, O'Reilly Institute, Trinity College, University of Dublin
                             http://www.cs.tcd.ie/Andrew.Butterfield/



EclipseFP supports lhs files. Not too sure about tex files, I know
some support was built but I haven't worked on it.

-- 
JP Moresmau
http://jpmoresmau.blogspot.com/

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


Re: [Haskell-cafe] A practical Haskell puzzle

2011-03-03 Thread Eric Mertens
There were a number of emails discussing what a type-safe list solution
would like look. This was the approach that first came to mind when I read
your email (but I've had my head in Agda lately)

http://hpaste.org/44469/software_stack_puzzle

I've written up a minimal working example of this approach for those that
are curious.


As for the Haskell98 approach, I'd love to see a solution that didn't
require deserialization/serialization at each layer boundary. This sounds
like a case for the techniques used in list fusion, but GHC RULES are hardly
Haskell98 :-) I'd also like to avoid cramming all of the possible layer
input and output types into one giant ADT in such a solution.

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


Re: [Haskell-cafe] Rank-2 types in classes

2011-03-03 Thread Yves Parès
Thanks for your proposal.

 It is not clear if the class constraint is really needed.

Well 'IM' means 'ImplementationMonad', so it wouldn't make much sense if an
IM of an implementation wasn't also a monad. And since IM is the central
monad of the library, a lot of functions will use IM.
The methods will be spreaded over various classes. For instance the class
IWindow :

class IWindow i where
withinWindow :: Window - IM i Window a - IM i x a

So a method like 'cast' shouldn't exist, since it would allow the user to
switch the context freely. Methods like withinWindow will do that, but
safely.

2011/3/3 o...@okmij.org


 Yves Pare`s  wrote:
  I'm working on a library which aims to be a generic interface for 2D
  rendering. To do that, one of my goals is to enable each implementation
 of
  this interface to run in its own monad (most of the time an overlay to
 IO),
  thus giving me the following class
 
  class (Monad (IM i x)) = Impl i x where
  data IM i x :: * - *
 
  (where IM means Implementation Monad)
 
  I would like to write something like :
 
  class (forall x. Monad (IM i x)) = Impl i where
  data IM i :: * - * - *

 It is not clear if the class constraint is really needed. As an aside,
 a class constraint is perhaps a bit of mis-feature of type classes: it sure
 improves convenience by making signatures shorter. But it isn't really
 necessary. Perhaps there are other, better ways of achieving the
 convenience (the constraint alias proposal comes to mind).

 If we drop the class constraint, we can move Monad (IM i x) as the
 constraint on specific methods of the Impl class. The implicit uiniversal
 quantification on x is well allowed then. For example:

  class Impl (i :: * - *) where
  data IM i :: * - * - *
  foo :: Monad (IM i x) = Int - IM i x Int
  bar :: Monad (IM i x) = IM i x Int - IM i x Bool
  cast :: IM i x a - IM i y a
 
  data Window
 
  instance Impl IO where
  newtype IM IO x a = IMIO (IO a)
  foo = IMIO . return
  bar (IMIO x) = IMIO (fmap ( 42) x)
  cast (IMIO x) = IMIO x
 
  test :: (Monad (IM i Window), Impl i) = IM i Window Int - IM i x Bool
  test = cast . bar

 Perhaps this isn't what you had in mind; I more elaborate example
 would help then.

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


[Haskell-cafe] Haskell KMP(Knuth-Morris-Pratt) algorithm

2011-03-03 Thread larry.liuxinyu
Hi,

I read about some KMP implementation in Haskell including:

 [1] Richard Bird. ``Pearls of Functional algorithm design''
 [2] http://twan.home.fmf.nl/blog/haskell/Knuth-Morris-Pratt-in-Haskell.details
 [3] http://www.haskell.org/haskellwiki/Runtime_compilation
 [4] LazyString version

[1] builds a infinite lazy state transfer trees, while [3] uses index
to build overlap table.

I created a version which isn't as efficient as in [1]. Just for fun:

failure :: (Eq a)= ([a], [a]) - ([a], [a])
failure ([], ys) = ([], ys)
failure (xs, ys) = fallback (init xs) (last xs:ys) where
fallback as bs | as `isSuffixOf` xs = (as, bs)
   | otherwise = fallback (init as) (last as:bs)

kmpSearch2 :: (Eq a) = [a] - [a] -[Int]
kmpSearch2 ws txt = snd $ foldl f (([], ws), []) (zip txt [1..]) where
f (p@(xs, (y:ys)), ns) (x, n) | x == y = if ys==[] then ((xs++[y],
ys), ns++[n])
 else ((xs++[y], ys), ns)
  | xs == [] = (p, ns)
  | otherwise = f (failure p, ns) (x,
n)
f (p, ns) e = f (failure p, ns) e

The function failure just follows the idea that in case (xs, ys) fails
matching some letter c in text,
where xs++ys = pattern and c!= head ys, it means we must fallback to
(xs', ys') so that
  xs' = longest { s: s is prefix of xs AND s is suffix of xs }

The bad thing is that failure can't memorize what it has compute
before, for example, as pattern = ababc
and we fails at (abab, c), then we call function failure to get
the new one as (ab, abc).
After several matches, we fails again at (abab, c), failure can't
just return (ab, abc) what it has
been compute already. It has too do the same work again.

Function f inside kmpSearch2 is in fact a state-transfer function. If
we try to use some data structure (for example tree) to memorize the
results which failure function calculated, we can finally reach to the
idea in [1].

--
LIU
http://sites.google.com/site/algoxy/

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


Re: [Haskell-cafe] A practical Haskell puzzle

2011-03-03 Thread Yitzchak Gale
Brandon Moore wrote:
 This code produces and uses a table of all
 allowed combinations. I think this makes it easier
 to understand why the code works (and is H98).
 It's just as easy to make a direct version that
 produces one requested composition in linear time,
 so I haven't worried whether lazy evaluation of this
 table works nicely.

Given that you are allowing serializing and deserializing
at every step, you're right that it's not hard to do it
in Haskell 98. I'm not convinced that you gain
anything by building that big table though.

Anyway, my idea was to try to find a solution that
does not require the runtime cost of serializing and
deserializing at every step just to solve a type problem.
Sorry I didn't make that more clear in my statement
of the problem.

Thanks,
Yitz

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


Re: [Haskell-cafe] A practical Haskell puzzle

2011-03-03 Thread Yitzchak Gale
Eric Mertens wrote:
 (but I've had my head in Agda lately)

Indeed, coming across this problem tempted me
to abandon the real world and take refuge in Agda.

 http://hpaste.org/44469/software_stack_puzzle

Wow, so simple, and no higher-rank types! This is the
best solution yet. I am now truly in awe of the power
of GADTs.

Thanks,
Yitz

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


Re: [Haskell-cafe] Haskell KMP(Knuth-Morris-Pratt) algorithm

2011-03-03 Thread larry.liuxinyu
Hi,

Here is Richard Bird's version for reference. I changed it a bit.

data State a = E | S a (State a) (State a)

matched (S (_, []) _ _) = True
matched _ = False

kmpSearch4 :: (Eq a) = [a] - [a] - [Int]
kmpSearch4 ws txt = snd $ foldl tr (root, []) (zip txt [1..]) where
root = build E ([], ws)
build fails (xs, []) = S (xs, []) fails E
build fails s@(xs, (y:ys)) = S s fails succs where
succs = build' (fst (tr (fails, []) (y, 0))) (xs++[y], ys)
tr (E, ns) _ = (root, ns)
tr ((S (xs, ys) fails succs), ns) (x, n)
| [x] `isPrefixOf` ys = if matched succs then (succs, ns++[n])
else (succs, ns)
| otherwise = tr (fails, ns) (x, n)

In the program, tr is the transfer function applied to the state tree.
And build function is used to build the automaton.

Best regards.
--
LIU

On Mar 3, 5:25 pm, larry.liuxinyu liuxiny...@gmail.com wrote:
 Hi,

 I read about some KMP implementation in Haskell including:

  [1] Richard Bird. ``Pearls of Functional algorithm design''
  [2]http://twan.home.fmf.nl/blog/haskell/Knuth-Morris-Pratt-in-Haskell.de...
  [3]http://www.haskell.org/haskellwiki/Runtime_compilation
  [4] LazyString version

 [1] builds a infinite lazy state transfer trees, while [3] uses index
 to build overlap table.

 I created a version which isn't as efficient as in [1]. Just for fun:

 failure :: (Eq a)= ([a], [a]) - ([a], [a])
 failure ([], ys) = ([], ys)
 failure (xs, ys) = fallback (init xs) (last xs:ys) where
     fallback as bs | as `isSuffixOf` xs = (as, bs)
                    | otherwise = fallback (init as) (last as:bs)

 kmpSearch2 :: (Eq a) = [a] - [a] -[Int]
 kmpSearch2 ws txt = snd $ foldl f (([], ws), []) (zip txt [1..]) where
     f (p@(xs, (y:ys)), ns) (x, n) | x == y = if ys==[] then ((xs++[y],
 ys), ns++[n])
                                              else ((xs++[y], ys), ns)
                                   | xs == [] = (p, ns)
                                   | otherwise = f (failure p, ns) (x,
 n)
     f (p, ns) e = f (failure p, ns) e

 The function failure just follows the idea that in case (xs, ys) fails
 matching some letter c in text,
 where xs++ys = pattern and c!= head ys, it means we must fallback to
 (xs', ys') so that
   xs' = longest { s: s is prefix of xs AND s is suffix of xs }

 The bad thing is that failure can't memorize what it has compute
 before, for example, as pattern = ababc
 and we fails at (abab, c), then we call function failure to get
 the new one as (ab, abc).
 After several matches, we fails again at (abab, c), failure can't
 just return (ab, abc) what it has
 been compute already. It has too do the same work again.

 Function f inside kmpSearch2 is in fact a state-transfer function. If
 we try to use some data structure (for example tree) to memorize the
 results which failure function calculated, we can finally reach to the
 idea in [1].

 --
 LIUhttp://sites.google.com/site/algoxy/

 ___
 Haskell-Cafe mailing list
 Haskell-C...@haskell.orghttp://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] Project structure

2011-03-03 Thread John Lato

 From: Hauschild, Klaus (EXT)

 Hi Haskellers,

 is there a recommended structure for Haskell projects. I like the Maven way
 (
 http://maven.apache.org/guides/introduction/introduction-to-the-standard-directory-layout.html)
 for Java projects. How to separate productive from test code, how to
 separate source code from other resources?


I like the way the Snap-framework is organized:

./
./src/
./test/
./test/data/
./test/suite/
./snap-framework.cabal

Then if you have e.g.
./src/Snap/Types.hs

the tests go in
./tests/suite/Snap/Types/Tests.hs

Basically src is for all productive code, test is for tests of that
code.  I sometimes add these to the top level:
./tools
./resources

tools is for code generators or similar tools that auto-generate stuff to
go in ./src which cabal doesn't know about.  resources would be data
files, images, or similar resources that get bundled with the distribution.

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


Re: [Haskell-cafe] Terminal library : which ?

2011-03-03 Thread Alexander Danilov

25.02.2011 03:36, Permjacov Evgeniy пишет:

What terminal library you will recomedn?
Requirements: crossplatform (win/lin), with direct (i.e. with
line/column number pair) cursor positioning and possybly direct symbol
output. MUST provide function to get terminal dimensions. (could not
find one).



ncurses(linux)/pdcurses(dos/windows), there are some packages in cabal database,
but I didn't try.


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


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread Mihai Maruseac
On Thu, Mar 3, 2011 at 9:05 AM, Hauschild, Klaus (EXT)
klaus.hauschild@siemens.com wrote:
 Hi Haskellers,

 whats your Haskell IDE of choise? Currently I use leksah. Is the EclipseFP
 Plugin for Eclipse a real alternative?

 Thanks


Hi,

I use vim in terminator: one window with the source, one with ghci and
one small window with the directory tree. It is just like a IDE but
only bundled with what I use.

-- 
Mihai

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


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread Alexander Danilov

03.03.2011 16:05, Hauschild, Klaus (EXT) пишет:

Hi Haskellers,
whats your Haskell IDE of choise? Currently I use leksah. Is the
EclipseFP Plugin for Eclipse a real alternative?
Thanks
Klaus




Emacs, look at haskell wiki for details about haskell-mode.


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


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread Paul Sujkov
Hi,

I use emacs. Tried leksah a couple of times, but wasn't satisfied by it's
stability and user friendliness.

On 3 March 2011 09:05, Hauschild, Klaus (EXT) 
klaus.hauschild@siemens.com wrote:

  Hi Haskellers,

 whats your Haskell IDE of choise? Currently I use leksah. Is the EclipseFP
 Plugin for Eclipse a real alternative?

 Thanks

 Klaus



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




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


Re: [Haskell-cafe] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread Paul Sujkov
Hi,

you can always check the types using GHCi prompt:

*Prelude :i (,)
data (,) a b = (,) a b -- Defined in GHC.Tuple
instance (Bounded a, Bounded b) = Bounded (a, b)
  -- Defined in GHC.Enum
instance (Eq a, Eq b) = Eq (a, b) -- Defined in Data.Tuple
instance Functor ((,) a) -- Defined in Control.Monad.Instances
instance (Ord a, Ord b) = Ord (a, b) -- Defined in Data.Tuple
instance (Read a, Read b) = Read (a, b) -- Defined in GHC.Read
instance (Show a, Show b) = Show (a, b) -- Defined in GHC.Show

that's for a tuple. You can see that tuple has an instance for the Ord
class.

*Prelude :i ()
data () = () -- Defined in GHC.Unit
instance Bounded () -- Defined in GHC.Enum
instance Enum () -- Defined in GHC.Enum
instance Eq () -- Defined in Data.Tuple
instance Ord () -- Defined in Data.Tuple
instance Read () -- Defined in GHC.Read
instance Show () -- Defined in GHC.Show

and that's for a unit type.

On 3 March 2011 08:09, Karthick Gururaj karthick.guru...@gmail.com wrote:

 Hello,

 I'm learning Haskell from the extremely well written (and well
 illustrated as well!) tutorial - http://learnyouahaskell.com/chapters.
 I have couple of questions from my readings so far.

 In typeclasses - 101
 (http://learnyouahaskell.com/types-and-typeclasses#typeclasses-101),
 there is a paragraph that reads:
 Enum members are sequentially ordered types - they can be enumerated.
 The main advantage of the Enum typeclass is that we can use its types
 in list ranges. They also have defined successors and predecesors,
 which you can get with the succ and pred functions. Types in this
 class: (), Bool, Char, Ordering, Int, Integer, Float and Double.

 What is the () type? Does it refer to a tuple? How can tuple be
 ordered, let alone be enum'd? I tried:
 Prelude take 10 [(1,1) ..]
 interactive:1:8:
 No instance for (Enum (t, t1))
   arising from the arithmetic sequence `(1, 1) .. '
at interactive:1:8-17
 Possible fix: add an instance declaration for (Enum (t, t1))
 In the second argument of `take', namely `[(1, 1) .. ]'
 In the expression: take 10 [(1, 1) .. ]
 In the definition of `it': it = take 10 [(1, 1) .. ]

 This is expected and is logical.

 But, surprise:
 Prelude (1,1)  (1,2)
 False
 Prelude (2,2)  (1,1)
 True
 Prelude (1,2)  (2,1)
 False
 Prelude (1,2)  (2,1)
 True

 So tuples are in Ord type class atleast. What is the ordering logic?

 Another question, on the curried functions - specifically for infix
 functions. Suppose I need a function that takes an argument and adds
 five to it. I can do:
 Prelude let addFive = (+) 5
 Prelude addFive 4
 9

 The paragraph: Infix functions can also be partially applied by using
 sections. To section an infix function, simply surround it with
 parentheses and only supply a parameter on one side. That creates a
 function that takes one parameter and then applies it to the side
 that's missing an operand: describes a different syntax. I tried that
 as well:

 Prelude let addFive' = (+5)
 Prelude addFive' 3
 8

 Ok. Works. But on a non-commutative operation like division, we get:
 Prelude let x = (/) 20.0
 Prelude x 10
 2.0
 Prelude let y = (/20.0)
 Prelude y 10
 0.5

 So a curried infix operator fixes the first argument and a sectioned
 infix operator fixes the second argument?

 Regards,
 Karthick

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




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


Re: [Haskell-cafe] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread Karthick Gururaj
On Thu, Mar 3, 2011 at 8:00 PM, Paul Sujkov psuj...@gmail.com wrote:
 Hi,
 you can always check the types using GHCi prompt:
 *Prelude :i (,)
 data (,) a b = (,) a b -- Defined in GHC.Tuple
 instance (Bounded a, Bounded b) = Bounded (a, b)
   -- Defined in GHC.Enum
 instance (Eq a, Eq b) = Eq (a, b) -- Defined in Data.Tuple
 instance Functor ((,) a) -- Defined in Control.Monad.Instances
 instance (Ord a, Ord b) = Ord (a, b) -- Defined in Data.Tuple
 instance (Read a, Read b) = Read (a, b) -- Defined in GHC.Read
 instance (Show a, Show b) = Show (a, b) -- Defined in GHC.Show
 that's for a tuple. You can see that tuple has an instance for the Ord
 class.
 *Prelude :i ()
 data () = () -- Defined in GHC.Unit
 instance Bounded () -- Defined in GHC.Enum
 instance Enum () -- Defined in GHC.Enum
 instance Eq () -- Defined in Data.Tuple
 instance Ord () -- Defined in Data.Tuple
 instance Read () -- Defined in GHC.Read
 instance Show () -- Defined in GHC.Show
 and that's for a unit type.
 [snip]
Ah, thanks! I didn't know about :i, tried only :t () which didn't give
very interesting information.

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


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread Michal Konečný
On Thu, Mar 3, 2011 at 9:05 AM, Hauschild, Klaus (EXT)
klaus.hauschild@siemens.com wrote:
 whats your Haskell IDE of choise? Currently I use leksah. Is the EclipseFP
 Plugin for Eclipse a real alternative?

I use EclipseFP 2.0.2 on a few fairly large projects and am overall very happy 
with it despite a few flaws, eg:

- it currently signals an error in source code files with non-latin-1 unicode 
characters 
- it does not build projects that include C files
- I find it fairly slow on very large projects as it continuously rebuilds 
them as you type, but it is not as slow as this kind of approach may seem to 
imply

I especially appreciate:
- how well it highlights compiler errors 
- the outline of a module

I do not use code completion beyond the generic Alt-/, so I do not have an 
opinion on how well this is supported in eclipsefp.

Michal
-- 
|o| Michal Konecny mikkone...@gmail.com
|o|http://www-users.aston.ac.uk/~konecnym/
|o|office: (+42) (0)121 204 3462 
|o| PGP key http://www-users.aston.ac.uk/~konecnym/ki.aow


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


[Haskell-cafe] ANN: hmpfr-0.3.2 (requires integer-simple, supports mpfr 3.0.0)

2011-03-03 Thread Michal Konečný
Dear all,

I am pleased to announce hmpfr-0.3.2, a new version of Aleš Bizjak's bindings 
to the MPFR arbitrary precision floating point arithmetic library.  The 
changes in this version are quite small but significant:

- support for MPFR 3.0.0 as well as MPFR 2.4.*
- dependency on integer-simple instead of integer-gmp

The latter is most significant because unfortunately it makes it rather more 
difficult to install hmpfr.   Currently almost all binary distributions of ghc 
have integer-gmp compiled in to provide the Integer type via the standard GMP 
library.  Also haskell platform 2010.2.0.0 assumes that ghc has been compiled 
with integer-gmp although it makes no specific use of it.  Instructions on how 
to compile ghc and haskell platform with integer-simple instead of integer-gmp 
are on:

http://code.google.com/p/hmpfr/wiki/GHCWithoutGMP

The rationale for this change is the fact that despite much effort hmpfr is 
very unreliable on ghc that includes integer-gmp due to ghc deallocating GMP 
data that was allocated by MPFR at unpredictable times.

Aleš and I hope that hmpfr can return to using integer-gmp once the proposal 

http://hackage.haskell.org/trac/ghc/wiki/ReplacingGMPNotes#BinaryDropinReplacementforGMP

to replace gmp with a modified gmp in ghc is implemented and made the default.

Best regards,
Michal
-- 
|o| Michal Konecny mikkone...@gmail.com
|o|http://www-users.aston.ac.uk/~konecnym/
|o|office: (+42) (0)121 204 3462 
|o| PGP key http://www-users.aston.ac.uk/~konecnym/ki.aston


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] A practical Haskell puzzle

2011-03-03 Thread Brandon Moore
 From: Yitzchak Gale g...@sefer.org

 Brandon Moore wrote:
  This code produces and uses a table of all
   allowed combinations. I think this makes it easier
  to understand why the  code works (and is H98).
  It's just as easy to make a direct version  that
  produces one requested composition in linear time,
  so I  haven't worried whether lazy evaluation of this
  table works  nicely.
 
 Given that you are allowing serializing and deserializing
 at  every step, you're right that it's not hard to do it
 in Haskell 98. I'm not  convinced that you gain
 anything by building that big table  though.
 
 Anyway, my idea was to try to find a solution that
 does not  require the runtime cost of serializing and
 deserializing at every step just  to solve a type problem.
 Sorry I didn't make that more clear in my  statement
 of the problem.

My solution does not serialize and deserialize between every
pair of layers. The functions in the table have the form

  show . layer4 . layer3 . layer2 . read

not

  show . layer4 . read . show . layer3 . read . show . layer2 . read

I assume the first is fine, otherwise why mention serialization functions.

The code can also be transformed to avoid the table construction and
produce the requested function in linear time, but the intermediate
types seem much more confusing.

Brandon


  

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


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread Andrew Coppin

On 03/03/2011 07:12 AM, Eugene Kirpichov wrote:


However, now I actually use vim - but that's because I'm scared of
trying to install Leksah on Windows (maybe it isn't hard, I haven't
tried) and because I'm only doing rather tiny things with Haskell at
the moment.


FWIW, last time I tried, installing Leksah on Windows consisted of 
downloading a compiled EXE file and double-clicking it. It was literally 
that complex.


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


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread Simon Heath
Emacs.  haskell-mode is also rather slicker than most emacs major
modes I've seen; it recognizes syntax as you type, does the right
thing with indentation levels, and so on.

-- 
Simon Heath                       icefo...@gmail.com
Follow your heart, and keep on rocking.  http://alopex.li/

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


Re: [Haskell-cafe] A practical Haskell puzzle

2011-03-03 Thread Yitzchak Gale
Brandon Moore wrote:
 My solution does not serialize and deserialize between every
 pair of layers.

Ahhh, I see! Sorry I didn't look closely enough the first time.

Yes, this is a very nice Haskell 98 solution!

 This code produces and uses a table of all
 allowed combinations. I think this makes it easier
 to understand why the code works (and is H98).

I'm not sure I understand why that is so.

 It's just as easy to make a direct version  that
 produces one requested composition in linear time,
 so I haven't worried whether lazy evaluation of this
 table works nicely.

Well, for the table solution to really qualify, that would
need to work out. Otherwise, I'm not sure it's much
better than just building that many boilerplate definitions
in some automated way and compiling them.

Could you please elaborate a bit more on what you mean
by the direct version?

Thanks,
Yitz

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


Re: [Haskell-cafe] A simple attoparsec question

2011-03-03 Thread Malcolm Wallace


On 1 Mar 2011, at 21:58, Evan Laforge wrote:


 parseConstant = Reference $ try parseLocLabel
 | PlainNum $ decimal
 | char '#' * fmap PlainNum hexadecimal
 | char '\'' * (CharLit $ notChar '\n') * char '\''
 | try $ (char '' * (StringLit . B.pack $
   manyTill (notChar '\n') (char '')))
 ? constant

The problem is, that attoparsec just silently fails on this kind of
strings and tries other parsers afterwards, which leads to strange
results. Is there a way to force the whole parser to fail, even if
there's an alternative parser afterwards?


I _think_ what the original poster is worried about is that, having  
consumed an initial portion of a constant, e.g. the leading # or ' or  
, if the input does not complete the token sequence in a valid way,  
then the other alternatives are tried anyway (and hopelessly).  This  
can lead to very poor error messages.


The technique advocated by the polyparse library is to explicitly  
annotate the knowledge that when a certain sequence has been seen  
already, then no other alternative can possibly match.  The combinator  
is called 'commit'.  This locates the errors much more precisely.


For instance, (in some hybrid of polyparse/attoparsec combinators)


 parseConstant = Reference $ try parseLocLabel
 | PlainNum $ decimal
 | char '#' * commit (fmap PlainNum hexadecimal)
 | char '\'' * commit ((CharLit $ notChar '\n') *  
char '\'')

 | char '' * commit ((StringLit . B.pack $
   manyTill (notChar '\n') (char '')))
 ? constant



Regards,
Malcolm


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


Re: [Haskell-cafe] ANN: theoremquest-0.0.0

2011-03-03 Thread Henning Thielemann
Daniel Peebles schrieb:
 Have you tried it? It's completely addictive (and takes up a big chunk
 of my free time).

+1  after completing some missions in PVS. :-)


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


[Haskell-cafe] ANN: Version 0.14 of dataenc, version 0.5 of omnicodec

2011-03-03 Thread Magnus Therning
I've just uploaded a new version of dataenc to hackage[1].

It contains a large change to the API.  The old, rather simplistic,
lazy API has been removed.  It has been replaced by an API based on
incremental encoding/decoding.  This should make the library easier to
use together with left-fold enumerators such as enumerator[2] and
iteratee[3].

It's accompanied by a release of omnicodec[4] which makes use of the
modified API of dataenc.

/M

[1] http://hackage.haskell.org/package/dataenc
[2] http://hackage.haskell.org/package/enumerator
[3] http://hackage.haskell.org/package/iteratee
[4] http://hackage.haskell.org/package/omnicodec
-- 
Magnus Therning  OpenPGP: 0xAB4DFBA4 
email: mag...@therning.org   jabber: mag...@therning.org
twitter: magthe   http://therning.org/magnus

Most software today is very much like an Egyptian pyramid with
millions of bricks piled on top of each other, with no structural
integrity, but just done by brute force and thousands of slaves.
 -- Alan Kay


pgpDpdK33McAv.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread Alexander Solla
On Wed, Mar 2, 2011 at 10:09 PM, Karthick Gururaj 
karthick.guru...@gmail.com wrote:

 Hello,

 I'm learning Haskell from the extremely well written (and well
 illustrated as well!) tutorial - http://learnyouahaskell.com/chapters.
 I have couple of questions from my readings so far.

 In typeclasses - 101
 (http://learnyouahaskell.com/types-and-typeclasses#typeclasses-101),
 there is a paragraph that reads:
 Enum members are sequentially ordered types - they can be enumerated.
 The main advantage of the Enum typeclass is that we can use its types
 in list ranges. They also have defined successors and predecesors,
 which you can get with the succ and pred functions. Types in this
 class: (), Bool, Char, Ordering, Int, Integer, Float and Double.

 What is the () type? Does it refer to a tuple? How can tuple be
 ordered, let alone be enum'd?


Any set can be put into an order.  That's the well-ordering principle.
 Basically, the most natural order for pairs is the lexicographical order.
 There are instances of the form:

instance (Ord a, Ord b) = Ord (a,b)

in GHC.Enum (if you're using GHC).  You can also create Enum instances for
pairs, but at least one of the sides must be bounded.  Otherwise, the
enumeration will have an uncomputable order-type (something like the order
type of the rationals). Check out http://en.wikipedia.org/wiki/Order_type if
you're interested in what all that order type stuff means.

I wrote  an instance for this very purpose the other day:


-- An intuitive way to think about this is in terms of tables. Given
datatypes
--
-- @
-- data X = A | B | C | D deriving ('Bounded', 'Enum', 'Eq', 'Ord', 'Show')
-- data Y = E | F | G deriving ('Bounded', 'Enum', 'Eq', 'Ord', 'Show')
-- @
--
-- we can form the table
--
-- @
-- (A, E)   (A, F)   (A, G)
-- (B, E)   (B, F)   (B, G)
-- (C, E)   (C, F)   (C, G)
-- (D, E)   (D, F)   (D, G)
-- @
--
-- in a natural lexicographical order.  We simply require that there be a
finite
-- number of columns, and allow an unbounded number of rows (in so far as
the
-- lazy evaluation mechanism allows them).  In even more practical terms, we
require
-- a finite number of columns because we use that number to perform
arithmetic.

instance ( Bounded b
 , Enum a
 , Enum b
 ) = Enum (a, b) where
  toEnum k = let n = 1 + fromEnum (maxBound :: b) -- Enums are 0
indexed, but we want to
 a = toEnum ((k `div` n)) -- divide by
the number of elements in a row to find the row and
 b = toEnum ((k `mod` n)) -- get the
remainder to find the column.
  in (a,b)

  fromEnum (a, b) = let n = 1 + fromEnum (maxBound :: b)
i = fromEnum a
j = fromEnum b
 in (i*n + j)

-- | This instance of 'Enum' is defined in terms of the previous instance.
 We
-- use the natural equivalence of the types @(a,b,c)@ and @(a,(b,c))@ and
use
-- the previous definition.  Again, notice that all elements but the first
must
-- be bounded.
instance ( Bounded b
 , Bounded c
 , Enum a
 , Enum b
 , Enum c
 ) = Enum (a, b, c) where
   fromEnum (a, b, c) = fromEnum (a, (b,c))
   toEnum k = let (a, (b, c)) = toEnum k
   in (a, b,  c)






 So tuples are in Ord type class atleast. What is the ordering logic?


Lexicographical.  Dictionary order.

Another question, on the curried functions - specifically for infix
 functions. Suppose I need a function that takes an argument and adds
 five to it. I can do:
 Prelude let addFive = (+) 5
 Prelude addFive 4
 9

 The paragraph: Infix functions can also be partially applied by using
 sections. To section an infix function, simply surround it with
 parentheses and only supply a parameter on one side. That creates a
 function that takes one parameter and then applies it to the side
 that's missing an operand: describes a different syntax. I tried that
 as well:

 Prelude let addFive' = (+5)
 Prelude addFive' 3
 8

 Ok. Works. But on a non-commutative operation like division, we get:
 Prelude let x = (/) 20.0
 Prelude x 10
 2.0
 Prelude let y = (/20.0)
 Prelude y 10
 0.5

 So a curried infix operator fixes the first argument and a sectioned
 infix operator fixes the second argument?


I guess, except you can section infix operators the other way:

 let twentyover = (20 /)
 twentyover 5
4.0
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread Michael Xavier
I use vim (CLI not gvim). Any productivity I lose without the niceties of
Leksah are probably made up for with the gains from being a vim user for
years.
-- 
Michael Xavier
http://www.michaelxavier.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread Richard O'Keefe
By the way, tuples *can* be members of Enum if you make them so.
Try

instance (Enum a, Enum b, Bounded b) = Enum (a,b)
  where
toEnum n = (a, b)
   where a = toEnum (n `div` s)
 b = toEnum (n `mod` s)
 p = fromEnum (minBound `asTypeOf` b)
 q = fromEnum (maxBound `asTypeOf` b)
 s = q - p + 1
fromEnum (a, b) = fromEnum a * s + fromEnum b
  where p = fromEnum (minBound `asTypeOf` b)
q = fromEnum (maxBound `asTypeOf` b)
s = q - p + 1


data T1 = A | B | C deriving (Enum, Eq, Bounded, Show)
data T2 = D | E | F deriving (Enum, Eq, Bounded, Show)

t1 = [(A,D) .. (B,F)]

I can't think of an approach that doesn't require all but one of
the tuple elements to have Bounded types.  There are of course
all sorts of ways to enumerate tuples; this one is compatible
with the Ord instance.



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


Re: [Haskell-cafe] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread Alexander Solla
On Thu, Mar 3, 2011 at 1:58 PM, Richard O'Keefe o...@cs.otago.ac.nz wrote:


 I can't think of an approach that doesn't require all but one of
 the tuple elements to have Bounded types.


It's not possible.  Such an enumeration could potentially have an
uncomputable order-type, possibly equal to the order-type of the rationals.
 (In other words, there could be countably infinitely many elements between
any two elements)

It's possible to define a computational system where you can do arithmetic
on countable ordinals, but it has the expressive power of Turing machines
with oracles (where an oracle is a thing that correctly guesses the right
answer for a computation that does not halt in finite time (consider a
sequence approaching pi as a limit).   We can re-interpret the oracle's
guess as passing to a limit ordinal.  In any case, TMs+ oracles are strictly
stronger than just TMs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: hmpfr-0.3.2 (requires integer-simple, supports mpfr 3.0.0)

2011-03-03 Thread Edward Kmett
Woohoo!

I tried to fix up the hmpfr bindings myself before the
integer-simple/integer-gmp split was done, but it was impossible given the
way GHC hooks into the gmp allocator. The main issue appears to be the fact
that as mpfr has matured it has come to do more internal allocation to
handle corner cases that it was handling incorrectly, and as these are not
on slabs of memory you explicitly allocated, the GMP allocation hook causes
them to vanish willy nilly.

I'm glad I can finally pick up some of my interval arithmetic/taylor model
code again. =)

I have a half-dozen or so packages that were blocked by this.

-Edward Kmett

2011/3/3 Michal Konečný m...@konecny.aow.cz

 Dear all,

 I am pleased to announce hmpfr-0.3.2, a new version of Aleš Bizjak's
 bindings
 to the MPFR arbitrary precision floating point arithmetic library.  The
 changes in this version are quite small but significant:

 - support for MPFR 3.0.0 as well as MPFR 2.4.*
 - dependency on integer-simple instead of integer-gmp

 The latter is most significant because unfortunately it makes it rather
 more
 difficult to install hmpfr.   Currently almost all binary distributions of
 ghc
 have integer-gmp compiled in to provide the Integer type via the standard
 GMP
 library.  Also haskell platform 2010.2.0.0 assumes that ghc has been
 compiled
 with integer-gmp although it makes no specific use of it.  Instructions on
 how
 to compile ghc and haskell platform with integer-simple instead of
 integer-gmp
 are on:

 http://code.google.com/p/hmpfr/wiki/GHCWithoutGMP

 The rationale for this change is the fact that despite much effort hmpfr is
 very unreliable on ghc that includes integer-gmp due to ghc deallocating
 GMP
 data that was allocated by MPFR at unpredictable times.

 Aleš and I hope that hmpfr can return to using integer-gmp once the
 proposal


 http://hackage.haskell.org/trac/ghc/wiki/ReplacingGMPNotes#BinaryDropinReplacementforGMP

 to replace gmp with a modified gmp in ghc is implemented and made the
 default.

 Best regards,
 Michal
 --
 |o| Michal Konecny mikkone...@gmail.com
 |o|http://www-users.aston.ac.uk/~konecnym/
 |o|office: (+42) (0)121 204 3462
 |o| PGP key http://www-users.aston.ac.uk/~konecnym/ki.aston

 ___
 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] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread Daniel Fischer
On Thursday 03 March 2011 23:25:48, Alexander Solla wrote:
 On Thu, Mar 3, 2011 at 1:58 PM, Richard O'Keefe o...@cs.otago.ac.nz 
wrote:
  I can't think of an approach that doesn't require all but one of
  the tuple elements to have Bounded types.
 
 It's not possible. 

Meaning: It's not possible while respecting the order.
Ignoring the order, it's of course possible (finite products of countable 
sets are countable).

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


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread Daniel Fischer
On Thursday 03 March 2011 22:14:34, Michael Xavier wrote:
 I use vim (CLI not gvim).

I use kate.

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


[Haskell-cafe] ANN: cabal-dev-0.7.4.0

2011-03-03 Thread Rogan Creswick
We're happy to announce that cabal-dev-0.7.4.0 is now on hackage.  We
strongly suggest that everyone upgrade to this release, since this
release specifically addresses changes in Cabal-1.10 and newer, which
the latest cabal-install now uses.

The ticket for the bug is here, for anyone interested:
https://github.com/creswick/cabal-dev/issues/2

--Rogan



smime.p7s
Description: S/MIME Cryptographic Signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] groupBy huh?

2011-03-03 Thread Jacek Generowicz

Hi Cafe,

It seems that I don't understand what groupBy does.

I expect it to group together elements as long as adjacent ones  
satisfy the predicate, so I would expect ALL four of the following to  
give one group of 3 and a group of 1.


Prelude :m + Data.List
Prelude Data.List groupBy () abcb
[abcb]
Prelude Data.List groupBy () abca
[abc,a]
Prelude Data.List groupBy () [1,2,3,2]
[[1,2,3,2]]
Prelude Data.List groupBy () [1,2,3,1]
[[1,2,3],[1]]

What am I missing?

Thanks.


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


Re: [Haskell-cafe] Haskell IDE

2011-03-03 Thread Markus Läll
I have been using Notepad++ -- it has proper (I think) syntaks highlighting
and in the latest version now has line wrapping a la kate: broken lines
start at the indent level of the first one.

--
Markus Läll

On Fri, Mar 4, 2011 at 1:14 AM, Daniel Fischer 
daniel.is.fisc...@googlemail.com wrote:

 On Thursday 03 March 2011 22:14:34, Michael Xavier wrote:
  I use vim (CLI not gvim).

 I use kate.

 ___
 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] groupBy huh?

2011-03-03 Thread Marc Weber
Excerpts from Jacek Generowicz's message of Fri Mar 04 00:18:07 + 2011:
 Prelude Data.List groupBy () [1,2,3,2]
 [[1,2,3,2]]
This is wired. However if you think about the algorithm always using the
first element of a list and comparing it against the next elements you
get

1  2 ok, same group
1  3 dito
1  2 dito
Thus you get [[1,2,3,2]]

Marc Weber

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


Re: [Haskell-cafe] groupBy huh?

2011-03-03 Thread Daniel Fischer
On Friday 04 March 2011 01:18:07, Jacek Generowicz wrote:
 Hi Cafe,
 
 It seems that I don't understand what groupBy does.
 
 I expect it to group together elements as long as adjacent ones
 satisfy the predicate, so I would expect ALL four of the following to
 give one group of 3 and a group of 1.
 
 Prelude :m + Data.List
 Prelude Data.List groupBy () abcb
 [abcb]
 Prelude Data.List groupBy () abca
 [abc,a]
 Prelude Data.List groupBy () [1,2,3,2]
 [[1,2,3,2]]
 Prelude Data.List groupBy () [1,2,3,1]
 [[1,2,3],[1]]
 
 What am I missing?
 

That groupBy expects an equivalence relation (iirc, that was documented 
some time, seems to be gone, there's only a hint left at the docs for group 
equality test). It tests subsequent elements against the first of the 
group, not adjacent elements.

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


Re: [Haskell-cafe] groupBy huh?

2011-03-03 Thread Jacek Generowicz

On 2011 Mar 4, at 01:39, Marc Weber wrote:

Excerpts from Jacek Generowicz's message of Fri Mar 04 00:18:07  
+ 2011:

Prelude Data.List groupBy () [1,2,3,2]
[[1,2,3,2]]
This is wired. However if you think about the algorithm always using  
the

first element of a list and comparing it against the next elements you
get

1  2 ok, same group
1  3 dito
1  2 dito
Thus you get [[1,2,3,2]]



OK, that works, but it seems like a strange choice ...


On 2011 Mar 4, at 01:47, Daniel Fischer wrote:


On Friday 04 March 2011 01:18:07, Jacek Generowicz wrote:


What am I missing?



That groupBy expects an equivalence relation


... Bingo! Now it makes sense.

(iirc, that was documented some time, seems to be gone, there's only  
a hint left at the docs for group

equality test).


Hmph. In my opinion, explicitly including the words equivalence  
relation would immensely improve the documentation.



Thank you for you clarifications, gentlemen.


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


Re: [Haskell-cafe] groupBy huh?

2011-03-03 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 3/3/11 20:09 , Jacek Generowicz wrote:
 1  2 ok, same group
 1  3 dito
 1  2 dito
 Thus you get [[1,2,3,2]]
 
 OK, that works, but it seems like a strange choice ...

Stability is often valued in functions like this:  the order of elements is
not altered.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]allber...@gmail.com
system administrator  [openafs,heimdal,too many hats]kf8nh
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.11 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAk1wPPIACgkQIn7hlCsL25WF3ACfZrwM2OxutJZgadhaSCcpjoEv
Bg4AnA+V/H3tfCovwwnw8qrlaw5I92C4
=WJev
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread Markus

What about having the order by diagonals, like:

0 1 3
2 4
5

and have none of the pair be bounded?

--
Markus Läll



On 4 Mar 2011, at 01:10, Daniel Fischer daniel.is.fisc...@googlemail.com 
 wrote:



On Thursday 03 March 2011 23:25:48, Alexander Solla wrote:

On Thu, Mar 3, 2011 at 1:58 PM, Richard O'Keefe o...@cs.otago.ac.nz

wrote:

I can't think of an approach that doesn't require all but one of
the tuple elements to have Bounded types.


It's not possible.


Meaning: It's not possible while respecting the order.
Ignoring the order, it's of course possible (finite products of  
countable

sets are countable).

___
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] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread Daniel Fischer
On Friday 04 March 2011 03:24:34, Markus wrote:
 What about having the order by diagonals, like:
 
 0 1 3
 2 4
 5
 
 and have none of the pair be bounded?
 

I tacitly assumed product order (lexicographic order).

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


Re: [Haskell-cafe] groupBy huh?

2011-03-03 Thread Joachim Breitner
Hi,

Am Freitag, den 04.03.2011, 01:18 +0100 schrieb Jacek Generowicz:
 It seems that I don't understand what groupBy does.
 
 I expect it to group together elements as long as adjacent ones  
 satisfy the predicate, so I would expect ALL four of the following to  
 give one group of 3 and a group of 1.
 
 Prelude :m + Data.List
 Prelude Data.List groupBy () abcb
 [abcb]
 Prelude Data.List groupBy () abca
 [abc,a]
 Prelude Data.List groupBy () [1,2,3,2]
 [[1,2,3,2]]
 Prelude Data.List groupBy () [1,2,3,1]
 [[1,2,3],[1]]
 
 What am I missing?

this comes up repeatedly. Also see
http://hackage.haskell.org/trac/ghc/ticket/1408

Greetings,
Joachim

-- 
Joachim nomeata Breitner
  mail: m...@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C
  JID: nome...@joachim-breitner.de | http://www.joachim-breitner.de/
  Debian Developer: nome...@debian.org


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] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread Karthick Gururaj
There are so many responses, that I do not know where to start..

I'm top-posting since that seems best here, let me know if there are
group guidelines against that.

Some clarifications in order on my original post:
a. I ASSUMED that '()' refers to tuples, where we have atleast a pair.
This is from my Haskell ignorance, so let us forget that for now.
b. Also, when I said: tuples can not be ordered, let alone be enum'd -
I meant: there is no reasonable way of ordering tuples, let alone enum
them.

That does not mean we can't define them:
1. (a,b)  (c,d) if ac
2. (a,b)  (c,d) if bd
3. (a,b)  (c,d) if a^2 + b^2  c^2 + d^2
4. (a,b)  (c,d) if a*b  c*d

If we can imagine (a,b) as a point in the xy plane, (1) defines
ordering based on which point is more to the right of y axis, (2)
based on which point is more above x axis, (3) on which point is
farther from origin and (4) on which rectangle made of origin and
the point as diagonally opposite vertices has more area. Which of
these is a reasonable definition? The set of complex numbers do not
have a default ordering, due to this very issue.

For enumerating them, we *can* go along the diagonal as suggested. But
why that and not something else? By the way - enumerating them along
the diagonal introduces a new ordering between tuples.

When we do not have a reasonable way of ordering, I'd argue to not
have anything at all - let the user decide based on his/her
application of the tuple.

As a side note, the cardinality of rational numbers is the same as
those of integers - so both are equally infinite.

Regards,
Karthick


On Fri, Mar 4, 2011 at 8:42 AM, Daniel Fischer
daniel.is.fisc...@googlemail.com wrote:
 On Friday 04 March 2011 03:24:34, Markus wrote:
 What about having the order by diagonals, like:

 0 1 3
 2 4
 5

 and have none of the pair be bounded?


 I tacitly assumed product order (lexicographic order).

 ___
 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] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread Richard O'Keefe

On 4/03/2011, at 5:49 PM, Karthick Gururaj wrote:
 I meant: there is no reasonable way of ordering tuples, let alone enum
 them.

There are several reasonable ways to order tuples.
 
 That does not mean we can't define them:
 1. (a,b)  (c,d) if ac

Not really reasonable because it isn't compatible with equality.
 2. (a,b)  (c,d) if bd
 3. (a,b)  (c,d) if a^2 + b^2  c^2 + d^2
 4. (a,b)  (c,d) if a*b  c*d

Ord has to be compatible with Eq, and none of these are.
Lexicographic ordering is in wide use and fully compatible
with Eq.
 Which of
 these is a reasonable definition?

 The set of complex numbers do not
 have a default ordering, due to this very issue.

No, that's for another reason.  The complex numbers don't have
a standard ordering because when you have a ring or field and
you add an ordering, you want the two to be compatible, and
there is no total order for the complex numbers that fits in
the way required.
 
 When we do not have a reasonable way of ordering, I'd argue to not
 have anything at all

There is nothing unreasonable about lexicographic order.
It makes an excellent default.
 
 
 As a side note, the cardinality of rational numbers is the same as
 those of integers - so both are equally infinite.

Ah, here we come across the distinction between cardinals and
ordinals.  Two sets can have the same cardinality but not be
the same order type.  (Add 1 to the first infinite cardinal
and you get the same cardinal back; add 1 to the first infinite
ordinal and you don't get the same ordinal back.)


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


Re: [Haskell-cafe] Project structure

2011-03-03 Thread wren ng thornton

On 3/3/11 3:33 AM, Hauschild, Klaus (EXT) wrote:

Hi Haskellers,

is there a recommended structure for Haskell projects. I like the Maven way 
(http://maven.apache.org/guides/introduction/introduction-to-the-standard-directory-layout.html)
 for Java projects. How to separate productive from test code, how to separate 
source code from other resources?



My standard layout is:

_darcs/
LICENSE
README
TODO
VERSION
Setup.hs
foo.cabal
dist/
src/
test/

where _darcs is autogenerated by darcs, and dist is autogenerated by 
cabal-install. The README and TODO files are optional of course. The src 
and test directories contain parallel hierarchies of source code so that 
the src can be compiled and distributed without exposing dependencies on 
QuickCheck, SmallCheck, HUnit, etc.


If the project is multilanguage then I'll have ./src/hs/, ./src/c, 
./src/java, etc and the ./build.xml or whatever is standard for 
compiling the other languages plus a Makefile to run all the various 
build tools. Often this means adding ./bin, ./lib, ./doc, etc as the 
output destinations for those other tools.


--
Live well,
~wren

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


Re: [Haskell-cafe] groupBy huh?

2011-03-03 Thread wren ng thornton

On 3/3/11 7:18 PM, Jacek Generowicz wrote:

Hi Cafe,

It seems that I don't understand what groupBy does.

I expect it to group together elements as long as adjacent ones satisfy
the predicate, so I would expect ALL four of the following to give one
group of 3 and a group of 1.

Prelude :m + Data.List
Prelude Data.List groupBy () abcb
[abcb]
Prelude Data.List groupBy () abca
[abc,a]
Prelude Data.List groupBy () [1,2,3,2]
[[1,2,3,2]]
Prelude Data.List groupBy () [1,2,3,1]
[[1,2,3],[1]]

What am I missing?


The behavior is that it's comparing subsequent elements to the first 
element of the current chunk. I'm not sure how often that'd be a 
desirable behavior compared to the one you and I would expect. Of 
course, the API only specifies the behavior of groupBy on equality-like 
predicates IIRC. So technically either behavior is permissible...


This should be FAQed on the documentation a bit better.

--
Live well,
~wren

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


Re: [Haskell-cafe] groupBy huh?

2011-03-03 Thread wren ng thornton

On 3/3/11 8:14 PM, Brandon S Allbery KF8NH wrote:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 3/3/11 20:09 , Jacek Generowicz wrote:

1  2 ok, same group
1  3 dito
1  2 dito
Thus you get [[1,2,3,2]]


OK, that works, but it seems like a strange choice ...


Stability is often valued in functions like this:  the order of elements is
not altered.


Making it stable and also comparing adjacent elements is entirely doable.

--
Live well,
~wren

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


Re: [Haskell-cafe] Learn You a Haskell for Great Good - a few doubts

2011-03-03 Thread wren ng thornton

On 3/3/11 2:58 AM, Antti-Juhani Kaijanaho wrote:

On Thu, Mar 03, 2011 at 12:29:44PM +0530, Karthick Gururaj wrote:

Thanks - is this the same unit that accompanies IO in IO () ? In
any case, my question is answered since it is not a tuple.


It can be viewed as the trivial 0-tuple.


Except that this is problematic since Haskell doesn't have 1-tuples 
(which would be distinct from plain values in that they have an extra 
bottom).


In an idealized world, yes, unit can be thought of as the nullary 
product which serves as left- and right-identity for the product 
bifunctor. Unfortunately, Haskell's tuples aren't quite products.[1]



[1] To be fair, a lot of thought went into choosing for them to be the 
way they are. The way they are generally matches the semantics we 
desire, but this is one of the places where they don't. The only way to 
fix this is to have two different product types, which is problematic 
for the obvious reasons.


--
Live well,
~wren

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


[Haskell-cafe] Thoughts on program annotations.

2011-03-03 Thread Jason Dusek
  Hi List,

  I am working on a Bash config generation system. I've decided
  to factor out the Bash AST and pretty printer, here in a
  pre-release state:

https://github.com/solidsnack/bash

  One thing I'd like to support is generic annotations, so that
  at a future time I can add (and render) comments, mark
  subscripts with what privilege (package install, sudo) they
  require or otherwise characterize the script outside its
  lexical structure. I ended up making my statement type a
  Functor with a Foldable instance.

  Given that every statement has an annotation, it seemed better
  to me to use mutually recursive datatypes, using one datatype
  to capture annotatedness, like this:

--  From 
https://github.com/solidsnack/bash/blob/c718de36d349efc9ac073a2c7082742c45606769/hs/Language/Bash/Syntax.hs

data Annotated t = Annotated t (Statement t)
data Statement t = SimpleCommand Expression [Expression]
 | ...
 | IfThen (Annotated t) (Annotated t)
 | ...

  I wonder what folks think of this approach? It does mean I end
  up with all leaf-level annotations being potentially without
  annotations; this allows for relatively generic definitions,
  on the one hand; but forces type annotations at the use-site
  in many cases. It also means I have mutually recursive Functor
  and Foldable instances.

  Another option for annotations would be a sort of tree of
  zippers pointing in to the statement tree; this seems horrible
  at first glance since it leaves open the question of how the
  annotations are associated with their nodes in the first
  place. However, it does have the nice feature of simplifying
  the type of statements and also is just much more modular
  feeling.

  What does the list think?

--
Jason Dusek
Linux User #510144 | http://counter.li.org/

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


Re: [Haskell-cafe] groupBy huh?

2011-03-03 Thread Jacek Generowicz


On 2011 Mar 4, at 02:14, Brandon S Allbery KF8NH wrote:


-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 3/3/11 20:09 , Jacek Generowicz wrote:

1  2 ok, same group
1  3 dito
1  2 dito
Thus you get [[1,2,3,2]]


OK, that works, but it seems like a strange choice ...


Stability is often valued in functions like this:  the order of  
elements is

not altered.


I'm failing to see how the behaviour I expected would change the order  
of elements: the elements would still come out in exactly the same  
order, it is just the boundaries between the groups would be in  
different places.


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


Re: [Haskell-cafe] Thoughts on program annotations.

2011-03-03 Thread wren ng thornton

On 3/4/11 1:32 AM, Jason Dusek wrote:

   Hi List,

   I am working on a Bash config generation system. I've decided
   to factor out the Bash AST and pretty printer, here in a
   pre-release state:

 https://github.com/solidsnack/bash


Awesome!


   Given that every statement has an annotation, it seemed better
   to me to use mutually recursive datatypes, using one datatype
   to capture annotatedness, like this:

 --  From 
https://github.com/solidsnack/bash/blob/c718de36d349efc9ac073a2c7082742c45606769/hs/Language/Bash/Syntax.hs

 data Annotated t = Annotated t (Statement t)
 data Statement t = SimpleCommand Expression [Expression]
  | ...
  | IfThen (Annotated t) (Annotated t)
  | ...

   I wonder what folks think of this approach?


This is the same basic approach used by Tim Sheard:

http://web.cecs.pdx.edu/~sheard/papers/JfpPearl.ps
http://web.cecs.pdx.edu/~sheard/papers/generic.ps

and I think it works pretty well for this kind of problem. One change 
I'd make is to use something like this definition instead:


data Annotated a
= NewAnn   a (Statement a)
| MergeAnn a (Statement a)

where the annotation of MergeAnn is merged with the previous annotation 
up the tree (via mappend), thus allowing for annotations to be inherited 
and modified incrementally based on the Monoid instance; whereas the 
NewAnn constructor uses the annotation directly, overriding any 
contextual annotations. This can be helpful to reduce the amount of 
duplication in the AST, though how helpful will depend on how you plan 
to use/generate the ASTs.


--
Live well,
~wren

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


Re: [Haskell-cafe] Thoughts on program annotations.

2011-03-03 Thread Max Bolingbroke
On 4 March 2011 06:32, Jason Dusek jason.du...@gmail.com wrote:
    --  From 
 https://github.com/solidsnack/bash/blob/c718de36d349efc9ac073a2c7082742c45606769/hs/Language/Bash/Syntax.hs

    data Annotated t = Annotated t (Statement t)
    data Statement t = SimpleCommand Expression [Expression]
                     | ...
                     | IfThen (Annotated t) (Annotated t)
                     | ...

I use this a variant of approach quite extensively and it works well
for me. My scheme is:

data Statement t = SimpleCommand Expression [Expression]
 | ...
 | IfThen (t (Statement t)) (t (Statement t))
 | ...

This is a slightly more efficient representation because it lets you
unpack the t field of your Annotated data constructor. For example,
what would in your system would be:

type MyStatement = Statement (Int, Int)

Would in my system be:

data Ann s = Ann Int Int s
type MyStatement = Statement Ann

i.e. instead of allocating both a Statement and a (,) at each level we
allocate just a Ann at each level.

In this system you will probably find it convenient to have a
typeclass inhabited by each possible annotation type:

class Copointed t where
  extract :: t a - a

instance Copointed Ann where
  extract (Ann _ _ x) = x

Anyway, this is only a minor efficiency concern -- your scheme looks
solid to me as well.

Cheers,
Max

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