[Haskell-cafe] Fibonacci Heap without using Monad

2010-12-30 Thread larry.liuxinyu
Hi,

I checked the current Fibonacci Queue in Hackage DB:
http://hackage.haskell.org/packages/archive/pqueue-mtl/1.0.7/doc/html/src/Data-Queue-FibQueue.html#FQueue

And a history email for Okasaki in 1995:
http://darcs.haskell.org/nofib/gc/fibheaps/orig

The hardest part is how to consolidate all unordered binomial trees in
deleteMin.
In imperative implementation, there is a elegant algorithm introduced
in Chapter 20 of CLRS[1].

How to achieve it in Functional way is the key point of solve this
problem.

If we have a list of trees with rank [2, 1, 1, 4, 8, 1, 1, 2, 4], we
need first meld the trees with same rank, and recursively doing that
until there are no two trees with same rank. Here is a simple function
can do this:

consolidate:: (Num a)=[a] - [a]
consolidate xs = foldl meld [] xs where
meld :: (Num a)=[a] - a - [a]
meld [] x = [x]
meld (x':xs) x = if x == x' then meld xs (x+x')
 else x:x':xs

Generalize the `+` to link and `==` to compare rank yields the
solution.

Below are my literate source code with some description. For the
details of Binomial heap, please refer to Okasaki's ``Purely
Functional data structures''[2].

-- Definition

-- Since Fibonacci Heap can be achieved by applying lazy strategy
-- to Binomial heap. We use the same definition of tree as the
-- Binomial heap. That each tree contains:
--   a rank (size of the tree)
--   the root value (the element)
--   and the children (all sub trees)

data BiTree a = Node { rank :: Int
 , root :: a
 , children :: [BiTree a]} deriving (Eq, Show)


-- Different with Binomial heap, Fibonacci heap is consist of
-- unordered binomial trees. Thus in order to access the
-- minimum value in O(1) time, we keep the record of the tree
-- which holds the minimum value out off the other children trees.
-- We also record the size of the heap, which is the sum of all ranks
-- of children and minimum tree.

data FibHeap a = E | FH { size :: Int
, minTree :: BiTree a
, trees :: [BiTree a]} deriving (Eq, Show)

-- Auxiliary functions

-- Singleton creates a leaf node and put it as the only tree in the
heap

singleton :: a - FibHeap a
singleton x = FH 1 (Node 1 x []) []

-- Link 2 trees with SAME rank R to a new tree of rank R+1, we re-use
the code
--   for Binomial heaps

link :: (Ord a) = BiTree a - BiTree a - BiTree a
link t1@(Node r x c1) t2@(Node _ y c2)
| xy = Node (r+1) x (t2:c1)
| otherwise = Node (r+1) y (t1:c2)

-- Insertion, runs in O(1) time.

insert :: (Ord a) = FibHeap a - a - FibHeap a
insert h x = merge h (singleton x)

-- Merge, runs in O(1) time.

-- Different from Binomial heap, we don't consolidate the sub trees
-- with the same rank, we delayed it later when performing delete-
Minimum.

merge:: (Ord a) = FibHeap a - FibHeap a - FibHeap a
merge h E = h
merge E h = h
merge h1@(FH sz1 minTr1 ts1) h2@(FH sz2 minTr2 ts2)
| root minTr1  root minTr2 = FH (sz1+sz2) minTr1 (minTr2:ts2+
+ts1)
| otherwise = FH (sz1+sz2) minTr2 (minTr1:ts1++ts2)

-- Find Minimum element in O(1) time

findMin :: (Ord a) = FibHeap a - a
findMin = root . minTree

-- deleting, Amortized O(lg N) time

-- Auxiliary function

-- Consolidate unordered Binomial trees by meld all trees in same rank
--  O(lg N) time

consolidate :: (Ord a) = [BiTree a] - [BiTree a]
consolidate ts = foldl meld [] ts where
meld [] t = [t]
meld (t':ts) t = if rank t' == rank t then meld ts (link t t')
 else t:t':ts

-- Find the tree which contains the minimum element.
-- Returns the minimum element tree and the left trees as a pair
--   O(lg N) time

extractMin :: (Ord a) = [BiTree a] - (BiTree a, [BiTree a])
extractMin [t] = (t, [])
extractMin (t:ts) = if root t  root t' then (t, ts)
else (t', t:ts')
where
  (t', ts') = extractMin ts

-- delete function

deleteMin :: (Ord a) = FibHeap a - FibHeap a
deleteMin (FH _ (Node _ x []) []) = E
deleteMin h@(FH sz minTr ts) = FH (sz-1) minTr' ts' where
(minTr', ts') = extractMin $ consolidate (children minTr ++ ts)

-- Helper functions

fromList :: (Ord a) = [a] - FibHeap a
fromList xs = foldl insert E xs

-- general heap sort function, can be re-used for any heap

heapSort :: (Ord a) = [a] - [a]
heapSort = hsort . fromList where
hsort E = []
hsort h = (findMin h):(hsort $ deleteMin h)

-- test

testFromList = fromList [16, 14, 10, 8, 7, 9, 3, 2, 4, 1]

testHeapSort = heapSort [16, 14, 10, 8, 7, 9, 3, 2, 4, 1]

Below are the test results in GHC.

*FibonacciHeap testFromList
FH {size = 10, minTree = Node {rank = 1, root = 1, children = []},
trees = [Node {rank = 1, root = 2, children = []},Node {rank = 1, root
= 4, children = []},Node {rank = 1, root = 3, children = []},Node
{rank = 1, root = 7, children = []},Node {rank = 1, root = 9, children
= []},Node {rank = 1, root = 8, children = []},Node {rank = 1, root =
10, children = []},Node {rank = 1, root 

Re: [Haskell-cafe] Fibonacci Heap without using Monad

2010-12-30 Thread larry.liuxinyu
Hi,

In CLRS, there are algorithms about DECREASE-KEY and DELETE-NODE.
However, in the Functional approach, I didn't find corresponding solution.
One approach may just mark the node as `deleted' and when pops the top 
element from the heap, we repeat it until find a unmarked node.

--
LIU
https://sites.google.com/site/algoxy/home
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lambda Calculus: Bound and Free formal definitions

2010-12-30 Thread Hans Aberg

On 30 Dec 2010, at 03:05, Mark Spezzano wrote:

... regarding formal definitions of FREE and BOUND variables he  
gives Defn 5.2 as


It is the occurrence of a variable that is free or bound. An  
occurrence of a variable is bound if it is in the scope of something  
that binds it; otherwise it is free.



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


Re: [Haskell-cafe] Lambda Calculus: Bound and Free formal definitions

2010-12-30 Thread David Sabel

Hi,
 the definition in the book is a syntactic one, you are not allowed to 
beta-reduce when applying the definition.

In  particular

E = E1 E2 = (\x.xy)(\z.z)
The definition speaks about the term
(\x.xy)(\z.z) and not about (\z.z)y

and the definition does not speak about occurences of variables, it implicitely 
defines
the _set_ of bound variables and the _set_ of free variables of term.

Both sets needn't be disjoint, for example
In (\x.x) x
x is a free as well as a bound variable.

Regards,
 David


Am 30.12.2010 04:50, schrieb Mark Spezzano:

Hi all,

Thanks for your comments

Maybe I should clarify...

For example,

5.2 FREE:

If E1 = \y.xy then x is free
If E2 = \z.z then x is not even mentioned

So E = E1 E2 = x (\z.z) and x is free as expected
So E = E2 E1 = \y.xy and x is free as expected

5.3 BOUND:
=
If E1 = \x.xy then x is bound
If E2 = \z.z then is not even mentioned

So E = E1 E2 = (\x.xy)(\z.z) = (\z.z)y -- Error: x is not bound but should be 
by the rule of 5.3
So E = E2 E1 = (\z.z)(\x.xy) = (\x.xy) then x is bound.

Where's my mistake in the second-to-last example? Shouldn't x be bound 
(somewhere/somehow)?

Thanks,

Mark


On 30/12/2010, at 1:52 PM, Mark Spezzano wrote:


Duh, Sorry. Yes, there was a typo

the second one should read

If E is a combination E1 E2 then X is bound in E if and only if X is bound in 
E1 or is bound in E2.

Apologies for that oversight!

Mark


On 30/12/2010, at 1:21 PM, Antoine Latter wrote:


Was there a typo in your email? Because those two definitions appear
identical. I could be missing something - I haven't read that book.

Antoine

On Wed, Dec 29, 2010 at 9:05 PM, Mark Spezzano
mark.spezz...@chariot.net.au  wrote:

Hi,

Presently I am going through AJT Davie's text An Introduction to Functional 
Programming Systems Using Haskell.

On page 84, regarding formal definitions of FREE and BOUND variables he gives 
Defn 5.2 as

The variable X is free in the expression E in the following cases

a)omitted

b) If E is a combination E1 E2 then X is free in E if and only if X is free in 
E1 or X is free in E2

c)omitted

Then in Defn 5.3 he states

The variable X is bound in the expression E in the following cases

a)omitted

b) If E is a combination E1 E2 then X is free in E if and only if X is free in 
E1 or X is free in E2.

c)omitted

Now, are these definitions correct? They seem to contradict each otherand 
they don't make much sense on their own either (try every combination of E1 and 
E2 for bound and free and you'll see what I mean). If it is correct then please 
give some examples of E1 and E2 showing exactly why. Personally I think that 
there's an error in the book.

You can see the full text on Google Books (page 84)

Thanks for reading!

Mark Spezzano


___
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 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] Lambda Calculus: Bound and Free formal definitions

2010-12-30 Thread Lauri Alanko
On Thu, Dec 30, 2010 at 02:20:34PM +1030, Mark Spezzano wrote:
 5.3 BOUND:
 =
 If E1 = \x.xy then x is bound
 If E2 = \z.z then is not even mentioned
 
 So E = E1 E2 = (\x.xy)(\z.z) = (\z.z)y -- Error: x is not bound but
 should be by the rule of 5.3

Your final = here is beta equality. Were expecting the bound
property to be preserved by beta? As you observed, it is not true. Did
the book claim otherwise?

As for the correctness of the actual definitions
http://books.google.com/books?id=OPFoJZeI8MECpg=PA84, 5.2. seems
correct although sloppily named (it should say X occurs free in E or
X has a free occurrence in E instead of X is free in). 5.3. seems
to define a property that would properly be named there is a binder
for X in E. Note that this is different from e.g. X has a bound
occurrence in E.


Lauri

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


Re: [Haskell-cafe] Data.Typeable TypeRep Ord instance.

2010-12-30 Thread Serguey Zefirov
2010/12/30 Andreas Baldeau andr...@baldeau.net:
 instance Ord TypeRep where
    compare t1 t2 =
        compare
            (unsafePerformIO (typeRepKey t1))
            (unsafePerformIO (typeRepKey t2))

I think it would suffice. Thank you for a tip.

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


Re: [Haskell-cafe] V.I.P.s and the associativity of merge'

2010-12-30 Thread Heinrich Apfelmus

Leon Smith wrote:

Ok,  after mulling over the issues that Will Ness has brought up in
the last few days [1],  I think I have a partial explanation for the
apparent tension between Will's observations and Heinrich Apfelmus's
Implicit Heaps article [2],  which both concern the implementation of
mergeAll [3].

[1] http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/84666
[2] http://apfelmus.nfshost.com/articles/implicit-heaps.html
[3] 

http://hackage.haskell.org/packages/archive/data-ordlist/0.4.4/doc/html/Data-List-Ordered.html#v:mergeAll


[...]

This raises the question,  is there some
combination of the shape of the merge' tree and some input for which
using VIPs dramatically changes the efficiency of a mergeAll
operation?   I suspect the answer is yes,  though I don't know for
sure at this point in time.

However,  I do tacitly believe that the current tree that mergeAll
uses doesn't exhibit this property for any input,   and so I have
simplified the implementations of mergeAll and unionAll in the latest
version of data-ordlist-0.4.4 by avoiding the use of VIPs.   This has
the nice side benefit of modestly improving performance when the
elements of the result are highly biased towards the first list.


Will Ness
For those who remember the discussion about this about a year ago, it turns out 
there was a simpler version after all lurking somewhere in there (or is it 
_out_?).


primes = 2: primes' 
   where

primes' = 3: 5: [7,9..] `minus` tfold
  [ [p*p,p*p+2*p..] | p - primes' ]   
tfold ((x:xs):t)= x : xs `union` tfold (pairs t)

pairs ((x:xs):ys:t) = (x: union xs ys) : pairs t


Unfortunately, it turns out that this program is clear, shorter ... and 
subtly wrong. :)


Here an example where the VIP merge would give a different result

bad = tfold $ (1:10:undefined) : (2:3:5:undefined) : (4:undefined) :
  error bad

We have

ghci bad
[1,2*** Exception: bad

but the VIP version would give at least

ghci bad
[1,2,3,4*** Exception: bad / Prelude: undefined

In other words, this new program already tries to compare the number 3 
to the fourth list when it is still clear that only the first three 
lists are relevant.



Note that this doesn't necessarily mean that the program does not work 
for prime numbers, but *proving* correctness is now considerably more 
difficult because you need estimates about the growth and distribution 
of prime numbers. The VIP version always works as long as there are 
infinitely many primes.


Also, since unnecessary comparisons are performed, it is no longer clear 
whether the time and space complexity stays the same. (Which is not as 
bad as it sounds, since we didn't know them well in the first place 
anyway). More worryingly, changing the tree shape now affects correctness.




Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com



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


[Haskell-cafe] Deep concatenation [Was: Incorrectly inferring type [t]]

2010-12-30 Thread oleg

William Murphy wrote:
 I've spent a lot of time trying to write a version of concat, which
 concatenates lists of any depth:

It is a little bit more involved, but quite possible. The code is not
much longer than the one you wrote (essentially, three lines: one
class and two instance declarations). Here is the complete code:


{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE OverlappingInstances #-}

module DeepFlat where


class DeepFlat a b | a - b where
dflat :: [a] - [b]

-- If we flatten a list of lists
instance DeepFlat a b = DeepFlat [a] b where
dflat = concatMap dflat

-- If we are given a list of non-lists
instance a ~ b = DeepFlat a b where
dflat = id

test1 = dflat abracadabra
-- abracadabra

test2 = dflat [abra,cadabra]

test3 = dflat [[ab,ra],[cad,abra]]
test4 = dflat [[[a,b],[ra]],[[cad,abra]]]




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


Re: [Haskell-cafe] Incorrectly inferring type [t]

2010-12-30 Thread Henning Thielemann


On Wed, 29 Dec 2010, william murphy wrote:


Hi All,

I've spent a lot of time trying to write a version of concat, which 
concatenates lists of any
depth:
So:
concat'' [[[1,2],[3,4]],[[5]]]   would return: [1,2,3,4,5]


You can nicely solve this problem in Haskell 98 using a Tree data 
structure. Data.Tree might help and also has a 'flatten' function.


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


Re: [Haskell-cafe] ; in do

2010-12-30 Thread Larry Evans
On 12/29/10 22:40, Daryoush Mehrtash wrote:
 Why do people  put  ; in do {}, or , in data fields,  at the 
 beginning of the line? 
 -- 
It reflects the parse tree better by putting the
combining operators (e.g. ';' and ',') at the left
and their operands (or combined subtrees) indented
to the right.  IOW, this formating style rotates
the parse tree:

   o_
 /  \
/\
   s1s2

for operator o_ and subtrees, s1 and s2,
-90 degrees and replaces the connecting edges with
indentation:

   s1
o_ s2

now, it surrounds that with the begin(b_) and end(e_)
delimiters:

b_ s1
o_ s2
e_

For example, in the case of a tuple with arguments,
a1 and a2, this would appear:

( a1
, a2
)

This also improves readability in a similar way that
bulleted list items in a text document improve readability.
For example:

* s1
* s2

is easier to read than:

  s1
  s2

because the reader knows that * begins an item and he
only has to search a given column for the beginning
of the next item.

However, some people object to this style because
it requires too much vertical space as compared
to:

( a1, a2 )

HTH

-regards,
 Larry


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


Re: [Haskell-cafe] ; in do

2010-12-30 Thread Henning Thielemann


On Thu, 30 Dec 2010, Antoine Latter wrote:


I started for cleaner diffs and easier editing - I can add/remove a
line at the end without editing any other line. Eventually I grew to
like the look of it.


That's not true. As long as the comma is used as separator one line can 
affect an adjacent one. If the comma is written on the end of a line, then 
removing the last line means altering the line before. If the comma is at 
front of a line, then removing the first line requires altering the second 
one.


Really different is only the usage of the comma as terminator. Actually 
this is possible in import and export statements, but not in constructor 
enumerations.


http://www.haskell.org/haskellwiki/Terminator_vs._separator

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


[Haskell-cafe] Formatting function types

2010-12-30 Thread Lauri Alanko
On Thu, Dec 30, 2010 at 07:04:11AM -0600, Larry Evans wrote:
 On 12/29/10 22:40, Daryoush Mehrtash wrote:
  Why do people  put  ; in do {}, or , in data fields,  at the 
  beginning of the line? 
  -- 
 It reflects the parse tree better by putting the
 combining operators (e.g. ';' and ',') at the left
 and their operands (or combined subtrees) indented
 to the right.

I will take this opportunity to mention again a related pet peeve of
mine that I originally griped about ages ago:

http://www.mail-archive.com/haskell-cafe@haskell.org/msg02231.html

Even nowadays, Haddock deliberately generates the following layout for
long function types:

openTempFile
:: FilePath
- String
- IO (FilePath, Handle)

The layout draws special attention to the first argument type, whereas
the other argument types are indistinguishable from the return
type. The following is much clearer:

openTempFile :: 
FilePath -
String -
IO (FilePath, Handle)

(Possibly with the arrows aligned.)

I can't understand how the arrows first convention still lingers so
strongly when it is (to me) so obviously wrong and misleading. Please,
folks, at least pay a thought to what different indentation and line
continuation styles express before adopting one.


Lauri

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


Re: [Haskell-cafe] Formatting function types

2010-12-30 Thread Henning Thielemann


On Thu, 30 Dec 2010, Lauri Alanko wrote:


Even nowadays, Haddock deliberately generates the following layout for
long function types:

openTempFile
   :: FilePath
   - String
   - IO (FilePath, Handle)

The layout draws special attention to the first argument type, whereas
the other argument types are indistinguishable from the return
type. The following is much clearer:

openTempFile ::
   FilePath -
   String -
   IO (FilePath, Handle)

(Possibly with the arrows aligned.)


+1


GHC also formats type signatures in errors and warnings in the misleading 
way.


In case of Haddock comments I understand that the comment must be close to 
the argument type. That is


openTempFile
   FilePath -- ^ filename, of course  -
   String -
   IO (FilePath, Handle)

would not work. But {- ^ filename -} would work.

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


Re: [Haskell-cafe] ; in do

2010-12-30 Thread Antoine Latter
On Thu, Dec 30, 2010 at 8:15 AM, Henning Thielemann
lemm...@henning-thielemann.de wrote:

 On Thu, 30 Dec 2010, Antoine Latter wrote:

 I started for cleaner diffs and easier editing - I can add/remove a
 line at the end without editing any other line. Eventually I grew to
 like the look of it.

 That's not true. As long as the comma is used as separator one line can
 affect an adjacent one. If the comma is written on the end of a line, then
 removing the last line means altering the line before. If the comma is at
 front of a line, then removing the first line requires altering the second
 one.


By 'end' I meant 'last line' - I suppose a list does have two ends :-)

 Really different is only the usage of the comma as terminator. Actually this
 is possible in import and export statements, but not in constructor
 enumerations.

 http://www.haskell.org/haskellwiki/Terminator_vs._separator


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


Re: [Haskell-cafe] Formatting function types

2010-12-30 Thread Antoine Latter
On Thu, Dec 30, 2010 at 8:33 AM, Lauri Alanko l...@iki.fi wrote:
 On Thu, Dec 30, 2010 at 07:04:11AM -0600, Larry Evans wrote:
 On 12/29/10 22:40, Daryoush Mehrtash wrote:
  Why do people  put  ; in do {}, or , in data fields,  at the
  beginning of the line?
  --
 It reflects the parse tree better by putting the
 combining operators (e.g. ';' and ',') at the left
 and their operands (or combined subtrees) indented
 to the right.

 I will take this opportunity to mention again a related pet peeve of
 mine that I originally griped about ages ago:

 http://www.mail-archive.com/haskell-cafe@haskell.org/msg02231.html

 Even nowadays, Haddock deliberately generates the following layout for
 long function types:

 openTempFile
    :: FilePath
    - String
    - IO (FilePath, Handle)


Aesthetics is a funny thing. I prefer writing my type signatures
arrow-first if they grow too long.

Antoine

 The layout draws special attention to the first argument type, whereas
 the other argument types are indistinguishable from the return
 type. The following is much clearer:

 openTempFile ::
    FilePath -
    String -
    IO (FilePath, Handle)

 (Possibly with the arrows aligned.)

 I can't understand how the arrows first convention still lingers so
 strongly when it is (to me) so obviously wrong and misleading. Please,
 folks, at least pay a thought to what different indentation and line
 continuation styles express before adopting one.


 Lauri

 ___
 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] What's the motivation for η rules?

2010-12-30 Thread Conor McBride

Hi

Thus invoked...

On 28 Dec 2010, at 23:29, Luke Palmer wrote:


Eta conversion corresponds to extensionality; i.e. there is nothing
more to a function than what it does to its argument.

Suppose f x = g x for all x.  Then using eta conversion:

f = (\x. f x) = (\x. g x) = g

Without eta this is not possible to prove.  It would be possible for
two functions to be distinct (well, not provably so) even if they do
the same thing to every argument -- say if they had different
performance characteristics.  Eta is a controversial rule of lambda
calculus -- sometimes it is omitted, for example, Coq does not use it.
It tends to make things more difficult for the compiler -- I think
Conor McBride is the local expert on that subject.


...I suppose I might say something.

The motivation for various conversion rules depends quite a lot on one's
circumstances. If the primary concern is run-time computation, then
beta-rules (elimination construct consumes constructor) and definitional
expansion (sometimes delta), if you have definition, should do all the
work you need. I'm just wondering how to describe such a need. How about
this property (reminiscent of some results by Herman Geuvers).

Let = be the conversion relation, with whatever rules you've chucked in,
and let -- be beta+delta reduction, with --* its reflexive-transitive
closure. Suppose some closed term inhabiting a datatype is convertible
with a constructor form

  t = C s1 .. sn

then we should hope that

  t --* C r1 .. rn   with  ri = si, for i in 1..n

That is: you shouldn't need to do anything clever (computing backwards,
eta-conversion) to get a head-normal form from a term which is kind
enough to have one. If this property holds, then the compiler need only
deliver the beta-delta behaviour of your code. Hurrah!

So why would we ever want eta-rules? Adding eta to an *evaluator* is
tedious, expensive, and usually not needed in order to deliver values.
However, we might want to reason about programs, perhaps for purposes
of optimization. Dependent type theories have programs in types, and
so require some notion of when it is safe to consider open terms equal
in order to say when types match: it's interesting to see how far one
can chuck eta into equality without losing decidability of conversion,
messing up the Geuvers property, or breaking type-preservation.

It's a minefield, so tread carefully. There are all sorts of bad
interactions, e.g. with subtyping (if - subtyping is too weak,
(\x - f x) can have more types than f), with strictness (if
p = (fst p, snd p), then (case p of (x, y) - True) = True, which
breaks the Geuvers property on open terms), with reduction (there
is no good way to orientate the unit type eta-rule, u = (), in a
system of untyped reduction rules).

But the news is not all bad. It is possible to add some eta-rules
without breaking the Geuvers property (for functions it's ok; for
pairs and unit it's ok if you make their patterns irrefutable). You
can then decide the beta-eta theory by postprocessing beta-normal
forms with type-directed eta-expansion (or some equivalent
type-directed trick). Epigram 2 has eta for functions, pairs,
and logical propositions (seen as types with proofs as their
indistinguishable inhabitants). I've spent a lot of time banging my
head off these issues: my head has a lot of dents, but so have the
issues.

So, indeed, eta-rules make conversion more extensional, which is
unimportant for closed computation, but useful for reasoning and for
comparing open terms. It's a fascinating, maddening game trying to
add extensionality to conversion while keeping it decidable and
ensuring that open computation is not too strict to deliver values.

Hoping this is useful, suspecting that it's TMI

Conor


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


Re: [Haskell-cafe] Formatting function types

2010-12-30 Thread Christopher Done
On 30 December 2010 15:44, Antoine Latter aslat...@gmail.com wrote:

 On Thu, Dec 30, 2010 at 8:33 AM, Lauri Alanko l...@iki.fi wrote:
  Even nowadays, Haddock deliberately generates the following layout for
  long function types:
 
  openTempFile
 :: FilePath
 - String
 - IO (FilePath, Handle)
 

 Aesthetics is a funny thing. I prefer writing my type signatures
 arrow-first if they grow too long.


Me too:

fooBar :: Foo a
   = Bar a
   - Mu a
   - Zot ()

Though in Lisk I don't have to think much about this:

(:: foo-bar (= ('foo a) (- ('bar a) ('mu a) ('zot ()

(:: foo-bar
(= ('foo a)
(- ('bar a)
('mu a)
('zot ()
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Not in scope: type constructor or class `Map'

2010-12-30 Thread michael rice
Not sure what's going on here. Doesn't like line 5, the type statement. And 
what's with the semicolons in that line and in function main?

Michael

=

From: 
http://www.haskell.org/ghc/docs/6.10.3/html/libraries/mtl/Control-Monad-Reader.html

import Control.Monad.Reader
import qualified Data.Map as Map
import Data.Maybe

type Bindings = Map String Int;

-- Returns True if the count variable contains correct bindings size.
isCountCorrect :: Bindings - Bool
isCountCorrect bindings = runReader calc_isCountCorrect bindings

-- The Reader monad, which implements this complicated check.
calc_isCountCorrect :: Reader Bindings Bool
calc_isCountCorrect = do
    count - asks (lookupVar count)
    bindings - ask
    return (count == (Map.size bindings))

-- The selector function to  use with 'asks'.
-- Returns value of the variable with specified name.
lookupVar :: String - Bindings - Int
lookupVar name bindings = fromJust (Map.lookup name bindings)

sampleBindings = Map.fromList [(count,3), (1,1), (b,2)]

main = do
    putStr $ Count is correct for bindings  ++ (show sampleBindings) ++ : ;
    putStrLn $ show (isCountCorrect sampleBindings);

==

Prelude :l monad5
[1 of 1] Compiling Main ( monad5.hs, interpreted )

monad5.hs:5:16: Not in scope: type constructor or class `Map'
Failed, modules loaded: none.




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


Re: [Haskell-cafe] A question regarding cmdargs package

2010-12-30 Thread Sönke Hahn
 That i18n is a fantastic argument - and one that really means cmdargs
 has no choice but to support all the attributes on help/version.

Is it possible to change the groupname for the implicit help and version 
options? I have defined some options with groupname development flags, but I 
would want to have another groupname for help and version. (Or -- even 
better -- have them included in the Common flags section. I toyed around 
with something like 'helpArg [groupname Something]', but without success.

Thanks,
Sönke

(Using System.Console.CmdArgs.Implicit from cmdargs-0.6.5.)

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


Re: [Haskell-cafe] Not in scope: type constructor or class `Map'

2010-12-30 Thread Eric Stansifer
Because Data.Map is imported qualified, any symbols in it (including
Map) needs to be qualified:

type Bindings = Map.Map String Int


A standard idiom is to do import like so:

import qualified Data.Map as Map
import Map (Map)

so that the Map symbol itself does not need qualification.

Eric

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


Re: [Haskell-cafe] Not in scope: type constructor or class `Map'

2010-12-30 Thread Pedro Vasconcelos
On Thu, 30 Dec 2010 08:01:01 -0800 (PST)
michael rice nowg...@yahoo.com wrote:

 Not sure what's going on here. Doesn't like line 5, the type
 statement. And what's with the semicolons in that line and in
 function main?

 
 import Control.Monad.Reader
 import qualified Data.Map as Map
 import Data.Maybe
 
 type Bindings = Map String Int;
.
The right hand side should be Map.Map String Int; alternatively
add an unqualified import above for just the Map type:

 import Data.Map(Map)

The semicolon is optional---the layout rule will insert it if you leave
it out.


Pedro

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


Re: [Haskell-cafe] Formatting function types

2010-12-30 Thread Larry Evans
On 12/30/10 08:17, Henning Thielemann wrote:

 On Thu, 30 Dec 2010, Lauri Alanko wrote:

 Even nowadays, Haddock deliberately generates the following layout for
 long function types:

 openTempFile
:: FilePath
- String
- IO (FilePath, Handle)

 The layout draws special attention to the first argument type, whereas
 the other argument types are indistinguishable from the return
 type.

Lauri, I assume then that you want to draw special attention to
the return type instead of the first argument type.

The following is much clearer:

 openTempFile ::
FilePath -
String -
IO (FilePath, Handle)

 (Possibly with the arrows aligned.)

So, with this operator postfix formatting, the special
attention to the return type is achieved by *not* suffixing it
with -.  However, to see that it's not suffixed with -, your
eyes have to scan to the right for the whole line until you don't
find the -.  Oh, but wait, if the return type is an elaborate
type expression, that takes up more than say, 60 spaces, then I
would want to format it over more than one line.  Yes, that would
be rare, but possible.  Now you'd have to scan not 1 but 2 lines
to find (or rather not find) the -. OK, but then why not just
find the last argument and forget about finding the missing
postfix -?  Well, in that case, the operator prefix formatting
would serve just as well.

The attachment contains ret_{post,pre} declaration which
provide a concrete example.  Maybe I'm just used to the prefix
formatting, but I do find ret_pre easier to read than the
ret_post.  I find it more readable because I just have to search,
in a given column, for the last -, and then I know the following
is the return type.


 +1


 GHC also formats type signatures in errors and warnings in the
 misleading way.

 In case of Haddock comments I understand that the comment must be close
 to the argument type.

Henning, I guess you're saying Haddock puts - first on the line
in order to make the comment as close as possible to the argument type.

 That is

 openTempFile
FilePath -- ^ filename, of course  -
String -
IO (FilePath, Handle)

 would not work. But {- ^ filename -} would work.

So, Haddock would format this(after adding comments for other args) as:

[1]:
  openTempFile
 :: FilePath -- ^ filename, of course
 - String -- ^ comment for 2nd arg.
 - IO (FilePath, Handle) -- ^ comment for 3ird arg

However, you and Lauri would prefer (IIUC):

[2]:
  openTempFile::
 FilePath {- ^ filename, of course -} -
 String {- ^ comment for 2nd arg. -} -
 IO (FilePath, Handle) -- ^ comment for 3ird arg

or, to retain the same comment types:

[3]:
  openTempFile::
 FilePath -- ^ filename, of course
 -
 String -- ^ comment for 2nd arg.
 -
 IO (FilePath, Handle) -- ^ comment for 3ird arg

OK, but then there's more vertical space used, so maybe [2]
is better; however, [2] separates the operator, - from it's
operands by the the comment.  Maybe you could justify this by
saying the operator is not important for readability; however,
in my reply to Lauri, I indicated it was easier to find the
last argument if the operators were prefixed, as was illustrated
by the ret_{post,pre} declarations in the attachment.  Likewise,
I find it easier to find the last argument with [1] rather than
either [2] or [3].

-regards,
 Larry



module Format where

--{return attention

  ret_post ::
Int -
( Int
, Int
) --more than 1 line arg
-
( Int
, Int
) --more than 1 line return type

  ret_pre
:: Int
- ( Int 
   , Int
   ) --more than 1 line arg
- ( Int
   , Int
   ) --more than 1 line return type

--}return attention

--{comments
  com_post :: 
Int {-arg1-} - 
Int {-arg2-}

  com_pre
:: Int --arg1
- Int --arg2

--}comments

  ret_post x _ = (x,x)
  ret_pre x _ = (x,x)
  com_post x = x
  com_pre x = x


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


Re: [Haskell-cafe] Not in scope: type constructor or class `Map'

2010-12-30 Thread michael rice
Thanks, all.

Just tried

type Bindings = Map.Map String Int

and it also seems to work.

Michael

 --- On Thu, 12/30/10, Pedro Vasconcelos p...@dcc.fc.up.pt wrote:

From: Pedro Vasconcelos p...@dcc.fc.up.pt
Subject: Re: [Haskell-cafe] Not in scope: type constructor or class `Map'
To: haskell-cafe@haskell.org
Date: Thursday, December 30, 2010, 11:17 AM

On Thu, 30 Dec 2010 08:01:01 -0800 (PST)
michael rice nowg...@yahoo.com wrote:

 Not sure what's going on here. Doesn't like line 5, the type
 statement. And what's with the semicolons in that line and in
 function main?

 
 import Control.Monad.Reader
 import qualified Data.Map as Map
 import Data.Maybe
 
 type Bindings = Map String Int;
.
The right hand side should be Map.Map String Int; alternatively
add an unqualified import above for just the Map type:

 import Data.Map(Map)

The semicolon is optional---the layout rule will insert it if you leave
it out.


Pedro

___
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] ; in do

2010-12-30 Thread Albert Y. C. Lai

On 10-12-29 11:40 PM, Daryoush Mehrtash wrote:

Why do people  put ; in do {}, or , in data fields,  at the
beginning of the line?


There was a time I did this to help the auto-indenter.

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


[Haskell-cafe] record types and unique names

2010-12-30 Thread Aaron Gray
Given a Haskell record type :-

data Test
= Test {
name :: String,
value :: Int
}

test = Test {
name = test,
value = 1
}

main :: IO ()
main = do
putStrLn (name test)

Are name and value in the global name space, as the following gives an
error Multiple declarations of `name' :-

name :: String - String
name s = s

Is there any way round this ?

Many thanks in advance,

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


Re: [Haskell-cafe] A question regarding cmdargs package

2010-12-30 Thread Neil Mitchell
Hi Sönke,

helpArg [groupname Something] should work, but it sounds like it
doesn't. I've raised a bug:
http://code.google.com/p/ndmitchell/issues/detail?id=392

I'll probably have this fixed in about a week.

Thanks, Neil

On Thu, Dec 30, 2010 at 4:05 PM, Sönke Hahn sh...@cs.tu-berlin.de wrote:
 That i18n is a fantastic argument - and one that really means cmdargs
 has no choice but to support all the attributes on help/version.

 Is it possible to change the groupname for the implicit help and version
 options? I have defined some options with groupname development flags, but I
 would want to have another groupname for help and version. (Or -- even
 better -- have them included in the Common flags section. I toyed around
 with something like 'helpArg [groupname Something]', but without success.

 Thanks,
 Sönke

 (Using System.Console.CmdArgs.Implicit from cmdargs-0.6.5.)


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


Re: [Haskell-cafe] record types and unique names

2010-12-30 Thread Markus Läll
Yes, they are in the global scope, and from what I gather: they are just
regular functions, created by special syntax.

There are a few obvious solutions (some of which you might have thought
yourself :-):
 - rename the accessor or the other function, or
 - put the data declaration or the other function in another module and
import qualified, or
 - write a typeclass with a 'name' function and fit the non-accessor
function 'name' somehow into that...

I think the best approach is the modular one, but this really depends on
what you are doing.

--
Markus Läll

On Thu, Dec 30, 2010 at 7:01 PM, Aaron Gray aaronngray.li...@gmail.comwrote:

 Given a Haskell record type :-

 data Test
 = Test {
 name :: String,
 value :: Int
 }

 test = Test {
 name = test,
 value = 1
 }

 main :: IO ()
 main = do
 putStrLn (name test)

 Are name and value in the global name space, as the following gives an
 error Multiple declarations of `name' :-

 name :: String - String
 name s = s

 Is there any way round this ?

 Many thanks in advance,

 Aaron


 ___
 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] record types and unique names

2010-12-30 Thread Aaron Gray
On 30 December 2010 17:23, Markus Läll markus.l...@gmail.com wrote:

 Yes, they are in the global scope, and from what I gather: they are just
 regular functions, created by special syntax.

 There are a few obvious solutions (some of which you might have thought
 yourself :-):
  - rename the accessor or the other function, or
  - put the data declaration or the other function in another module and
 import qualified, or
  - write a typeclass with a 'name' function and fit the non-accessor
 function 'name' somehow into that...

 I think the best approach is the modular one, but this really depends on
 what you are doing.


Okay looks like name mangling with the datatypes name is in order then.
Something like :-

data Test
= Test {
testName :: String,
testValue :: Int
}

Thanks,

Aaron

--
 Markus Läll

 On Thu, Dec 30, 2010 at 7:01 PM, Aaron Gray aaronngray.li...@gmail.comwrote:

 Given a Haskell record type :-

 data Test
 = Test {
 name :: String,
 value :: Int
 }

 test = Test {
 name = test,
 value = 1
 }

 main :: IO ()
 main = do
 putStrLn (name test)

 Are name and value in the global name space, as the following gives an
 error Multiple declarations of `name' :-

 name :: String - String
 name s = s

 Is there any way round this ?

 Many thanks in advance,

 Aaron


 ___
 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] record types and unique names

2010-12-30 Thread aditya siram
I don't think record field disambiguation what you're after. My apologies.
-deech

On Thu, Dec 30, 2010 at 11:20 AM, aditya siram aditya.si...@gmail.com wrote:
 Take a look at the record field disambiguation [1] extension to GHC.
 It sounds like what you're looking for.
 -deech
 [1] 
 http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/syntax-extns.html#disambiguate-fields

 On Thu, Dec 30, 2010 at 11:01 AM, Aaron Gray aaronngray.li...@gmail.com 
 wrote:
 Given a Haskell record type :-
     data Test
         = Test {
             name :: String,
             value :: Int
         }
     test = Test {
             name = test,
     value = 1
         }
     main :: IO ()
     main = do
         putStrLn (name test)
 Are name and value in the global name space, as the following gives an
 error Multiple declarations of `name' :-
     name :: String - String
     name s = s
 Is there any way round this ?
 Many thanks in advance,
 Aaron

 ___
 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] Formatting function types

2010-12-30 Thread Lauri Alanko
On Thu, Dec 30, 2010 at 10:39:29AM -0600, Larry Evans wrote:
 Lauri, I assume then that you want to draw special attention to
 the return type instead of the first argument type.

Only to the fact that the return type is of a different nature than
the argument types, and that all the argument types are of the same
nature. (More technically, the argument types occur in negative
positions within the function type, whereas the return type occurs in
a positive position.)

 So, with this operator postfix formatting, the special
 attention to the return type is achieved by *not* suffixing it
 with -.

Partly, but more by the fact that it is the last item in the list. Of
course there are ways to make it even more prominent, e.g. by
inserting an empty line before it. The arrows are not really essential
for readability, although they can help a bit if they are aligned:

openTempFile ::
FilePath -
String   -
IO (FilePath, Handle)

 OK, but then why not just find the last argument and forget about
 finding the missing postfix -?  Well, in that case, the operator
 prefix formatting would serve just as well.

Except that it falsely suggests that the last argument types are of a
similar nature as the return type. Here's what went in my head when I
first read Haskell code:

openTempFile ::
   FilePath -- All right, this first part is probably the argument.
- String -- this comes after the arrow, so this must be the return type.
- IO (FilePath, Handle) -- And then we have another return type? Huh?

It took me quite a while to understand that - associates to the
right, because the layout so strongly suggested otherwise. Obviously,
with time one can get used to anything, but I still stand by my
opinion that the above convention is inherently misleading.

 [1]:
   openTempFile
  :: FilePath -- ^ filename, of course
  - String -- ^ comment for 2nd arg.
  - IO (FilePath, Handle) -- ^ comment for 3ird arg

3rd arg? This is just the sort of lapse that the above syntax induces.

 [2]:
   openTempFile::
  FilePath {- ^ filename, of course -} -
  String {- ^ comment for 2nd arg. -} -
  IO (FilePath, Handle) -- ^ comment for 3ird arg

This is admittedly ugly. I'd prefer:

openTempFile ::
FilePath --- ^ foo
String -  -- ^ bar
IO (FilePath, Handle)  -- ^ baz

If Haddock doesn't support an intervening - between the type and the
documentation comment, it probably should.

(Personally, I don't like end-of-line comments because they quickly run
out of space and extending them to multiple lines is awkward. So maybe
even better would be:

openTempFile ::
FilePath -
-- ^ foo
String -
-- ^ bar
IO (FilePath, Handle)
-- ^ baz

But this is no longer relevant to the issue at hand.)


Lauri

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


Re: [Haskell-cafe] record types and unique names

2010-12-30 Thread aditya siram
Take a look at the record field disambiguation [1] extension to GHC.
It sounds like what you're looking for.
-deech
[1] 
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/syntax-extns.html#disambiguate-fields

On Thu, Dec 30, 2010 at 11:01 AM, Aaron Gray aaronngray.li...@gmail.com wrote:
 Given a Haskell record type :-
     data Test
         = Test {
             name :: String,
             value :: Int
         }
     test = Test {
             name = test,
     value = 1
         }
     main :: IO ()
     main = do
         putStrLn (name test)
 Are name and value in the global name space, as the following gives an
 error Multiple declarations of `name' :-
     name :: String - String
     name s = s
 Is there any way round this ?
 Many thanks in advance,
 Aaron

 ___
 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] A question regarding cmdargs package

2010-12-30 Thread Neil Mitchell
Hi Sönke,

I've just released cmdargs-0.6.6 which supports helpArgs [groupname Something]

Thanks, Neil

On Thu, Dec 30, 2010 at 5:09 PM, Neil Mitchell ndmitch...@gmail.com wrote:
 Hi Sönke,

 helpArg [groupname Something] should work, but it sounds like it
 doesn't. I've raised a bug:
 http://code.google.com/p/ndmitchell/issues/detail?id=392

 I'll probably have this fixed in about a week.

 Thanks, Neil

 On Thu, Dec 30, 2010 at 4:05 PM, Sönke Hahn sh...@cs.tu-berlin.de wrote:
 That i18n is a fantastic argument - and one that really means cmdargs
 has no choice but to support all the attributes on help/version.

 Is it possible to change the groupname for the implicit help and 
 version
 options? I have defined some options with groupname development flags, but 
 I
 would want to have another groupname for help and version. (Or -- even
 better -- have them included in the Common flags section. I toyed around
 with something like 'helpArg [groupname Something]', but without success.

 Thanks,
 Sönke

 (Using System.Console.CmdArgs.Implicit from cmdargs-0.6.5.)



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


Re: [Haskell-cafe] record types and unique names

2010-12-30 Thread Aaron Gray
On 30 December 2010 17:29, aditya siram aditya.si...@gmail.com wrote:

 I don't think record field disambiguation what you're after. My apologies.
 -deech


Interesting never the less.

Thanks,

Aaron


  On Thu, Dec 30, 2010 at 11:20 AM, aditya siram aditya.si...@gmail.com
 wrote:
  Take a look at the record field disambiguation [1] extension to GHC.
  It sounds like what you're looking for.
  -deech
  [1]
 http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/syntax-extns.html#disambiguate-fields
 
  On Thu, Dec 30, 2010 at 11:01 AM, Aaron Gray aaronngray.li...@gmail.com
 wrote:
  Given a Haskell record type :-
  data Test
  = Test {
  name :: String,
  value :: Int
  }
  test = Test {
  name = test,
  value = 1
  }
  main :: IO ()
  main = do
  putStrLn (name test)
  Are name and value in the global name space, as the following gives
 an
  error Multiple declarations of `name' :-
  name :: String - String
  name s = s
  Is there any way round this ?
  Many thanks in advance,
  Aaron
 
  ___
  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] Formatting function types

2010-12-30 Thread Ketil Malde
Antoine Latter aslat...@gmail.com writes:

 openTempFile
:: FilePath
- String
- IO (FilePath, Handle)

My main discomfort with this is not the result type, but that the first
argument appears different from the rest.  I much prefer having the ::
be attached to the identifier. FWIW.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Formatting function types

2010-12-30 Thread Henning Thielemann


On Thu, 30 Dec 2010, Lauri Alanko wrote:


Except that it falsely suggests that the last argument types are of a
similar nature as the return type. Here's what went in my head when I
first read Haskell code:

openTempFile ::
  FilePath -- All right, this first part is probably the argument.
   - String -- this comes after the arrow, so this must be the return type.
   - IO (FilePath, Handle) -- And then we have another return type? Huh?

It took me quite a while to understand that - associates to the
right, because the layout so strongly suggested otherwise. Obviously,
with time one can get used to anything, but I still stand by my
opinion that the above convention is inherently misleading.


I see it the same way. The arrow-prefix notation suggests left 
associativity for (-). Combining lines beginning from the bottom, e.g.


  - IO (FilePath, Handle)

or

  - String
  - IO (FilePath, Handle)

does not make sense, thus the layout suggests to consider block prefixes, 
e.g.


 FilePath

and

 FilePath
  - String

and

 FilePath
  - String
  - IO (FilePath, Handle)

but these three are completely unrelated types.

On the other hand the line

   FilePath -

suggests: read on, this is only the first argument of something bigger, 
it is not a top-level FilePath declaration. The second line


   String -

suggests: This is still not the result, just another argument. And so 
on.


Since in this formatting prefix blocks like

   FilePath -
   String -

make no sense, the layout suggests right associativity of (-).


[2]:
  openTempFile::
 FilePath {- ^ filename, of course -} -
 String {- ^ comment for 2nd arg. -} -
 IO (FilePath, Handle) -- ^ comment for 3ird arg


This is admittedly ugly. I'd prefer:

openTempFile ::
   FilePath --- ^ foo
   String -  -- ^ bar
   IO (FilePath, Handle)  -- ^ baz

If Haddock doesn't support an intervening - between the type and the
documentation comment, it probably should.


Haddock must respect the inner structure of types, since in the future (or 
is it already there?) you might be able to comment more parts of a type 
and then the position of comments is essential. E.g.


arrow ::
   A   {- ^ arrow argument -}
   :~ {- ^ our ingenious arrow -}
   B   {- ^ arrow result -}

foo ::
   Applicative f =
   f (A {- ^ first arg -} - B {- ^ second arg -} - C {- ^ result -})

pair :: (A {- ^ first element -}, B {- ^ second element -})


Maybe Haddock should have expected comments _before_ commented types.

openTempFile ::
   -- ^ foo
   FilePath -
   -- ^ bar
   String -
   -- ^ baz
   IO (FilePath, Handle)


openTempFile ::
   {- ^ foo -}   FilePath -
   {- ^ bar -}   String -
   {- ^
   The result type is especially difficult to explain
   and thus needs two lines.
   -}
 IO (FilePath, Handle)


(Personally, I don't like end-of-line comments because they quickly run
out of space and extending them to multiple lines is awkward. So maybe
even better would be:

openTempFile ::
   FilePath -
   -- ^ foo
   String -
   -- ^ bar
   IO (FilePath, Handle)
   -- ^ baz

But this is no longer relevant to the issue at hand.)


I also do not like multi-line comments composed from single-line comments. 
Haddock parses them and they are used in a lot of libraries. But I find it 
cumbersome to prefix every line with double-dash.


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


Re: [Haskell-cafe] Fibonacci Heap without using Monad

2010-12-30 Thread larry.liuxinyu
Hi,

Sorry for there is a bug in my previous post.

The example consolidate function for number should be like this:

consolidate xs = foldl meld [] xs where
meld [] x = [x]
meld (x':xs) x | x == x' = meld xs (x+x')
   | x  x'  = x:x':xs
   | otherwise = x': meld xs x

The bug happens in my previous mail like below.

before fixing
consolidate [2, 1, 1, 32, 4, 8, 1, 1, 2, 4]
[16,4,32,4]

after fixing--
consolidate [2, 1, 1, 32, 4, 8, 1, 1, 2, 4]
[8, 16, 32]

Therefore, the consolidate function for unordered binomial trees should be 
modified as the following respectively.

consolidate :: (Ord a) = [BiTree a] - [BiTree a]
consolidate ts = foldl meld [] ts where
meld [] t = [t]
meld (t':ts) t | rank t == rank t' = meld ts (link t t')
   | rank t   rank t' = t:t':ts
   | otherwise = t' : meld ts t

I am sorry for this mistake.

The updated source code can be found from here:
https://sites.google.com/site/algoxy/otherheaps/otherheaps.zip

Happy new year.

--
Larry, LIU

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


Re: [Haskell-cafe] V.I.P.s and the associativity of merge'

2010-12-30 Thread Will Ness
Heinrich Apfelmus apfelmus at quantentunnel.de writes:

 
 Leon Smith wrote:
 
  [1] http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/84666
  [2] http://apfelmus.nfshost.com/articles/implicit-heaps.html
  [3] 
 http://hackage.haskell.org/packages/archive/data-ordlist/0.4.4/doc/html/Data-
List-Ordered.html#v:mergeAll
 
 
 Will Ness
  
  primes = 2: primes' 
 where
  primes' = 3: 5: [7,9..] `minus` tfold
[ [p*p,p*p+2*p..] | p - primes' ]   
  tfold ((x:xs):t)= x : xs `union` tfold (pairs t)
  pairs ((x:xs):ys:t) = (x: union xs ys) : pairs t
 
 Unfortunately, it turns out that this program is clear, shorter ... and 
 subtly wrong. :)
 
 Here an example where the VIP merge would give a different result
 
  bad = tfold $ (1:10:undefined) : (2:3:5:undefined) : (4:undefined) :
error bad
 
 We have
 
  ghci bad
  [1,2*** Exception: bad
 
 but the VIP version would give at least
 
  ghci bad
  [1,2,3,4*** Exception: bad / Prelude: undefined
 



The reason to *not* have the lazy patterns in foldTree for primes, as Daniel 
Fischer discovered back then, is that they give it a space leak. Case in point -
 http://ideone.com/DLHp2 : 
 

- 1M primes:  2M primes: --- 3M: --- ideone #:
- no-VIPs:
smart fold: 1.90s- 4.8MB  4.42s- 4.8MB  7.40s- 4.8MB  r3bdL
- VIPs:
smart fold: 1.95s- 4.8MB  4.53s- 4.8MB  7.45s- 4.8MB  4ACpe
simple  fold: 2.04s- 4.8MB  4.76s- 4.8MB  7.86s- 4.8MB  av9XR
lazy  pats: 2.44s-20.1MB  5.70s-21.1MB  9.85s-42.6MB  DLHp2
 
Also, having 
 
   tfold ((x:xs):t) = x : xs `merge` tfold (pairs t)
 where pairs ((x:xs):ys:t) = (x : merge xs ys) : pairs t
 
   hfold  xs = serve . foldTree  mergeP . map vip $ xs
   hfold' xs = serve . foldTree' mergeP . map vip $ xs
 
   foldTree f ~(x:xs) = x `f` foldTree f (pairs xs)
 where pairs ~(x: ~(y:ys)) = f x y : pairs ys
 
   foldTree' f (x:xs) = x `f` foldTree' f (pairs xs)
 where pairs (x: (y:ys)) = f x y : pairs ys
 
and
 
   bad = (1:10:error 1) : (2:3:5:error 2) : (4:error 4) 
   : error bad
   bad2 = (1:10:error 1) : (2:3:5:error 2) : (4:error 4)
   : (5:error 5) : (6:error 6)
   : (7:error 7) 
   : error bad2

we get
 
   *Main hfold bad
   [1,2,3,4*** Exception: bad
   *Main hfold' bad
   [1,2,3,4*** Exception: bad
   *Main tfold bad
   [1,2*** Exception: bad
 
   *Main hfold bad2
   [1,2,3,4*** Exception: 4
   *Main hfold' bad2
   [1,2,3,4*** Exception: bad2
   *Main tfold bad2
   [1,2*** Exception: bad2
 
so hfold' too appears to be over-eager to-the-right, although still more 
productive than tfold.



 Regards,
 Heinrich Apfelmus
 
 --
 http://apfelmus.nfshost.com
 





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


Re: [Haskell-cafe] Formatting function types

2010-12-30 Thread Chung-chieh Shan
Lauri Alanko l...@iki.fi wrote in article 
20101230133355.gb...@melkinpaasi.cs.helsinki.fi in 
gmane.comp.lang.haskell.cafe:
 The following is much clearer:
 
 openTempFile :: 
 FilePath -
 String -
 IO (FilePath, Handle)
 
 (Possibly with the arrows aligned.)
 
 I can't understand how the arrows first convention still lingers so
 strongly when it is (to me) so obviously wrong and misleading.

What about chains of $ in terms?  (Both - in types and $ in terms
associate to the right.  What about + - * / in terms, which associate to
the left?)

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
Where is Galt's Gulch?


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