[Haskell-cafe] GHC, names of inferred type variables

2008-09-27 Thread Shiqi Cao
Hi,

Error messages from GHC contain inferred type variables, is there
anyway to find out which term an inferred type variable is for(if the
term exists)?

Thanks,

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


Re: [Haskell-cafe] TH error

2008-09-27 Thread Anton van Straaten

Tim Newsham wrote:

I'm goofing with TH and I have my program mostly done:

http://hpaste.org/10713

If I have the $(deriveBinary ''MyData) line commented out it
prints out what looks to me like correct code.  I can even paste
it into a program and it compiles.  


Pasting the text output can miss errors in the underlying AST, which 
seems to be what's happening here.


If you examine the AST that's produced by:

  putStrLn $(deriveBinary ''MyData = lift . show)

...you can search for occurrences of x_ and see how they're being 
constructed.  The erroneous ones in this case are of the form:


  (ConE x_)

...which explains the error message, Illegal data constructor name, 
because this is trying to reference a variable as though it were a 
constructor.  I assume the ConE should really be a VarE.  The fix to the 
program is obvious but I'll leave that as an exercise just in case it's 
not.  :)


Anton

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


[Haskell-cafe] Re: Red-Blue Stack

2008-09-27 Thread apfelmus
Josef Svenningsson wrote:
 Stephan Friedrichs wrote:

 My question is: Is there a case, where finding a persistent
 solution that performs equally well is *impossible* rather than just
 harder? I mean might there be a case where (forced) persistence (as we
 have in pure Haskell) is a definite disadvantage in terms of big-O
 notation? Do some problems even move from P to NP in a persistent setting?

 The only result I'm aware of is that of Nicholas Pippenger where he
 shows that there are algorithms which are slower by a factor of log n
 if one is not allowed to use mutation:
 http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.36.670

Note however that Pippenger is forced to make the additional assumption
that the computation is online, i.e. that it operates on an infinite list

   data Inf a = a : (Inf a)

   doPerms :: Int - [Int] - Inf a - Inf a
   doPerms ~= \n ps - concat . map (perm ps) . group n

I am not aware of any result that was able to lift this restriction.

In section 3, Pippenger essentially discusses that every ephemeral data
structure that needs T(n) can be made persistent in T(n)*log T(n) time,
basically by making the storage explicit, i.e. simulating RAM with a
pure array like a binary tree. So, we can at least say that problems in
P will stay there.

 Interestingly enough, this particular result does not carry over to
 Haskell. The particular algorithm that he uses can actually be
 implemented optimally using lazy evaluation, as show in the following
 paper:
 http://progtools.comlab.ox.ac.uk/members/oege/publications/jfp97
 
 So a pure strict language is less efficient than a strict language
 with mutation and a pure lazy language. Although intuitively a pure
 lazy language should also be less efficient than a strict language
 with mutation I'm not aware of any such results.

Yes, lazy evaluation makes persistent data structures much easier,
sometimes even possible. It only gives amortized times, though.


Regards,
apfelmus

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


Re: [Haskell-cafe] Hmm, what license to use?

2008-09-27 Thread Magnus Therning
Wolfgang Jeltsch wrote:
 Am Freitag, 26. September 2008 09:24 schrieb Magnus Therning:
   
 Recently I received an email with a question regarding the licensing
 of a module I've written and uploaded to Hackage.  I released it under
 LGPL.  The sender wondered if I would consider re-licensing the code
 under BSD (or something similar) that would remove the need for users
 to provide linkable object files so that users can re-link programs
 against newer/modified versions of my library.
 

 Since GHC does cross-package inlining, code of your library is directly 
 included (not just linked) into code that uses the library.  So I think that 
 every code that uses your library will have to be released und the GPL or 
 LGPL which is a very bad situation.

 People, don’t release Haskell libraries under the LGPL!
   

That would be serious indeed, but before changing my ways I'd need more
information to back up your statement.  Could someone confirm that code
from one installed module can be inlined into another?

AFAIU you are saying that the linker is reaching into the module's .a
file, pulling out the .o file, and then reaching into that .o file to
pull out an individual function's ASM code.  I believe that's a bit more
than regular C linkers would do.

/M

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnus@therning.org Jabber: magnus@therning.org
http://therning.org/magnus

Haskell is an even 'redder' pill than Lisp or Scheme.
 -- PaulPotts




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


Re[2]: [Haskell-cafe] Hmm, what license to use?

2008-09-27 Thread Bulat Ziganshin
Hello Magnus,

Saturday, September 27, 2008, 3:48:27 PM, you wrote:

 AFAIU you are saying that the linker is reaching into the module's .a
 file, pulling out the .o file, and then reaching into that .o file to
 pull out an individual function's ASM code.  I believe that's a bit more
 than regular C linkers would do.

compiled haskell module represented in ghc as a .hi+.o files,
installed libraries as a .a plus a set of .h files (you may find lots
of .hi in your ghc installation)

afaiu, .hi files contains parts f source haskell code in some
partially compiled form. ability to perform inter-module and
inter-library inlining is a key to efficiency of ghc-compiled
programs, specially for polymorphic functions. when you use such
functions as head, you are definitely got them inlined



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Red-Blue Stack

2008-09-27 Thread Thomas Davie


On 25 Sep 2008, at 06:11, Matthew Eastman wrote:


Hey guys,

This is probably more of a question about functional programming  
than it is about Haskell, but hopefully you can help me out. I'm new  
to thinking about things in a functional way so I'm not sure what  
the best way to do some things are.


I'm in a data structures course right now, and the assignments for  
the course are done in Java. I figured it'd be fun to try and  
implement them in Haskell as well.


The part of the assignment I'm working on is to implement a  
RedBlueStack, a stack where you can push items in as either Red or  
Blue. You can pop Red and Blue items individually, but the stack has  
to keep track of the overall order of items.


i.e. popping Blue in [Red, Red, Blue, Red, Blue] would give [Red,  
Red, Blue]


I wanted to add my own 2p to this discussion.  I'm not dead certain I  
understand what is meant by the statement above, so I'm going to make  
a guess that when we pop an item, the top item on the stack should end  
up being the next item of the same colour as we popped.


In this interprettation, here's what I think is an O(1) implementation:

data RBStack a = Empty
   | More RBColour a (RBStack a) (RBStack a)

data RBColour = Red | Blue

rbPush :: Colour - a - RBStack a - RBStack a
rbPush c x Empty = Elem c x Empty Empty
rbPush c x e@(More c' v asCs nextNonC)
  | c == c'   = More c x e nextNonC
  | otherwise = More c x nextNonC e

rbPop :: Colour - RBStack a - RBStack a
rbPop c Empty = error Empty Stack, can't pop
rbPop c (More c' v asCs nextNonC)
  | c == c'   = asCs
  | otherwise = rbPop c nextNonC

The idea is that an RBStack contains its colour, an element, and two  
other stacks -- the first one is the substack we should get by popping  
an element of the same colour.  The second substack is the substack we  
get by looking for the next item of the other colour.


When we push, we compare colours with the top element of the stack,  
and we swap around the same coloured/differently coloured stacks  
appropriately.


When we pop, we jump to the first element of the right colour, and  
then we jump to the next element of the same colour.


I hope I haven't missed something.

Bob

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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Andrew Coppin

David Menendez wrote:


I wouldn't say that. It's important to remember that Haskell class
Monad does not, and can not, represent *all* monads, only (strong)
monads built on a functor from the category of Haskell types and
functions to itself.

Data.Set is a functor from the category of Haskell types *with
decidable ordering* and *order-preserving* functions to itself. That's
not the same category, although it is closely related.
  


I nominate this post for the September 2008 Most Incomprehensible Cafe 
Post award! :-D


Seriously, that sounded like gibberish. (But then, you're talking to 
somebody who can't figure out the difference between a set and a class, 
so...)


All I know is that sometimes I write stuff in the list monad when the 
result really ought to be *sets*, not lists, because


1. there is no senamically important ordering

2. there should be no duplicates

But Haskell's type system forbids me. (It also forbids me from making 
Set into a Functor, actually... so no fmap for you!)




PS. Text is unpredictable, so just in case... If this post sounds like a 
flame, it isn't meant to be. ;-)


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


Re: [Haskell-cafe] Red-Blue Stack

2008-09-27 Thread Matthew Eastman


Matthew Brecknell wrote:


Matthew Eastman said:
i.e. popping Blue in [Red, Red, Blue, Red, Blue] would give [Red,  
Red,

Blue]


Hmm, did you mean [Red,Blue] or [Red,Red,Red,Blue]? Judging by your
implementation of remUseless, I'm guessing the latter.


Yes, I meant the latter. Popping Blue in [Red, Red, Blue, Red, Blue]  
should give [Red, Red, Red, Blue]. Sorry for the confusion, I  
shouldn't be writing emails at midnight I guess!



apfelmus wrote:


...

Our lists won't store any elements at all!

newtype List a = Length Int   deriving (Eq,Show,Num)

Instead, we're only storing the length of the list, so that

 empty list   corresponds to   0
 tail corresponds to   n-1
 ++   corresponds to   +

...

Regards,
apfelmus


Wow! That's a really clever way to think about a list. The way that  
you push blue elements is pretty interesting too, switching the  
positions of the lists and doing a regular push. Very insightful posts.


I'm slowly reading through Okasaki's thesis now, I'm not sure how much  
of it I'm understanding but it seems pretty interesting. I had no idea  
that functional (I suppose persistent is the correct word) data  
structures were so different from ephemeral ones.



Thomas Davie wrote:

In this interprettation, here's what I think is an O(1)  
implementation:


...

rbPop :: Colour - RBStack a - RBStack a
rbPop c Empty = error Empty Stack, can't pop
rbPop c (More c' v asCs nextNonC)
 | c == c'   = asCs
 | otherwise = rbPop c nextNonC
...



Your pop doesn't seem to be in O(1) since you have to walk through the  
nextNonC stack if the colours don't match.


Thanks for the help everyone,
Matt___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Red-Blue Stack

2008-09-27 Thread Thomas Davie


Thomas Davie wrote:

In this interprettation, here's what I think is an O(1)  
implementation:


...

rbPop :: Colour - RBStack a - RBStack a
rbPop c Empty = error Empty Stack, can't pop
rbPop c (More c' v asCs nextNonC)
 | c == c'   = asCs
 | otherwise = rbPop c nextNonC
...



Your pop doesn't seem to be in O(1) since you have to walk through  
the nextNonC stack if the colours don't match.


Yep, this is still O(1) though, as you can guarentee that nextNonC  
will start with something of the correct colour.  Thus the worst case  
here is that we walk once to the nextNonC element, and then do a  
different O(1) operation.


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


[Haskell-cafe] Re: Hmm, what license to use?

2008-09-27 Thread Simon Marlow

Magnus Therning wrote:

Wolfgang Jeltsch wrote:

Am Freitag, 26. September 2008 09:24 schrieb Magnus Therning:
  

Recently I received an email with a question regarding the licensing
of a module I've written and uploaded to Hackage.  I released it under
LGPL.  The sender wondered if I would consider re-licensing the code
under BSD (or something similar) that would remove the need for users
to provide linkable object files so that users can re-link programs
against newer/modified versions of my library.

Since GHC does cross-package inlining, code of your library is directly 
included (not just linked) into code that uses the library.  So I think that 
every code that uses your library will have to be released und the GPL or 
LGPL which is a very bad situation.


People, don’t release Haskell libraries under the LGPL!
  


That would be serious indeed, but before changing my ways I'd need more
information to back up your statement.  Could someone confirm that code
from one installed module can be inlined into another?


When optimisation is turned on, you have virtually no control over how 
much code GHC will copy from one module to another, which is why several 
people (me included) have expressed concerns about the use of an 
unmodified LGPL with Haskell code in the past.  I believe at one stage 
we even asked for clarification from the FSF, but I don't recall getting 
an answer.


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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Brandon S. Allbery KF8NH

On 2008 Sep 27, at 9:24, Andrew Coppin wrote:

David Menendez wrote:

I wouldn't say that. It's important to remember that Haskell class
Monad does not, and can not, represent *all* monads, only (strong)
monads built on a functor from the category of Haskell types and
functions to itself.

Data.Set is a functor from the category of Haskell types *with
decidable ordering* and *order-preserving* functions to itself.  
That's

not the same category, although it is closely related.


I nominate this post for the September 2008 Most Incomprehensible  
Cafe Post award! :-D


Seriously, that sounded like gibberish. (But then, you're talking to  
somebody who can't figure out the difference between a set and a  
class, so...)


That response required a certain amount of category theory to grok.

When you have a typeclass, the constraints (that is, the (Foo a =)  
contexts) on it are the exact constraints on members of the class.   
You can't add more or leave some out.


Set and Map both require an additional constraint over those of  
Functor and Monad:  (Ord a =).  Since you can't add constraints on  
top of a typeclass, you can't make them members of Functor or Monad.   
(Unless you use some Oleg-style hackery.)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Re: Hmm, what license to use?

2008-09-27 Thread Brandon S. Allbery KF8NH

On 2008 Sep 27, at 11:59, Simon Marlow wrote:

Magnus Therning wrote:

Wolfgang Jeltsch wrote:

Am Freitag, 26. September 2008 09:24 schrieb Magnus Therning:

Recently I received an email with a question regarding the  
licensing
of a module I've written and uploaded to Hackage.  I released it  
under
LGPL.  The sender wondered if I would consider re-licensing the  
code
under BSD (or something similar) that would remove the need for  
users

to provide linkable object files so that users can re-link programs
against newer/modified versions of my library.

Since GHC does cross-package inlining, code of your library is  
directly included (not just linked) into code that uses the  
library.  So I think that every code that uses your library will  
have to be released und the GPL or LGPL which is a very bad  
situation.


People, don’t release Haskell libraries under the LGPL!

That would be serious indeed, but before changing my ways I'd need  
more
information to back up your statement.  Could someone confirm that  
code

from one installed module can be inlined into another?


When optimisation is turned on, you have virtually no control over  
how much code GHC will copy from one module to another, which is why  
several people (me included) have expressed concerns about the use  
of an unmodified LGPL with Haskell code in the past.  I believe at  
one stage we even asked for clarification from the FSF, but I don't  
recall getting an answer.


As for confirmation, try ghc --dump-iface on a .hi file, often you  
will see GHC Core in the .hi

so that it can be inlined in modules importing it.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Brandon S. Allbery KF8NH

On 2008 Sep 27, at 12:41, Andrew Coppin wrote:
I'm not sure how that qualifies set as not really a true monad  
anyway - but then, I don't know what a monad is, originally. I only  
know what it means in Haskell.


I think you read him backwards:  Map and Set are category-theory  
(true) monads, but they can't be Haskell Monads because Haskell  
isn't expressive enough to represent more than a subset of category- 
theoretical monads.


Also... Who or what is an Oleg, and why do I keep hearing about  
it? ;-)


Oleg Kiselyov.  http://okmij.org/ftp/
He's somewhat legendary in the Haskell community for his ability to  
make Haskell do what people think it can't, and his tendency to  
program at the type level instead of at the value level like most  
people.  :)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:

On 2008 Sep 27, at 12:41, Andrew Coppin wrote:
I'm not sure how that qualifies set as not really a true monad 
anyway - but then, I don't know what a monad is, originally. I only 
know what it means in Haskell.


I think you read him backwards:  Map and Set are category-theory 
(true) monads, but they can't be Haskell Monads because Haskell 
isn't expressive enough to represent more than a subset of 
category-theoretical monads.


Ah, OK. That makes more sense then...

What (if anything) do we do about that?

I'm not actually bothered about every possible monad being representable 
as such in Haskell. I'd just like Set to work. ;-)



Also... Who or what is an Oleg, and why do I keep hearing about it? ;-)


Oleg Kiselyov.  http://okmij.org/ftp/
He's somewhat legendary in the Haskell community for his ability to 
make Haskell do what people think it can't, and his tendency to 
program at the type level instead of at the value level like most 
people.  :)


Ah - so the Prolog programs as type signatures thing is *his* fault?! ;-)

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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Andrew Coppin

Albert Y. C. Lai wrote:

Andrew Coppin wrote:
If I understand this correctly, to solve this problem you need either 
Functional Dependencies or Associated Types. Is that correct?


A motivating example in papers on FD is exactly typeclasses for 
containers. Okasaki puts this into practice in the Edison library. 
Despite its comprehensiveness, elegance, and the Okasaki name brand, 
it did not become mainstream. I don't know why.


Can anybody actually demonstrate concretely how FDs and/or ATs would 
solve this problem? (I.e., enable you to write a class that any 
container can be a member of, despite constraints on the element types.)


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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Antoine Latter
On Sat, Sep 27, 2008 at 12:23 PM, Andrew Coppin
[EMAIL PROTECTED] wrote:

 Can anybody actually demonstrate concretely how FDs and/or ATs would solve
 this problem? (I.e., enable you to write a class that any container can be a
 member of, despite constraints on the element types.)


Sure!  Using type-families:

 class Container c where
type Elem c
insert :: Elem c - c - c

 instance Container [a] where
type Elem [a] = a
insert = (:)

 instance Container ByteString where
type Elem ByteString = Word8
insert = BS.cons

 instance Ord a = Container (Set a) where
type Elem (Set a) = a
insert = Set.insert

In GHCi:

 :t insert
insert :: forall c. (Container c) = Elem c - c - c

Now the hard part is coming up with a proper API and class hierarchy.

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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Matthieu Sozeau


Le 27 sept. 08 à 15:24, Andrew Coppin a écrit :


David Menendez wrote:


I wouldn't say that. It's important to remember that Haskell class
Monad does not, and can not, represent *all* monads, only (strong)
monads built on a functor from the category of Haskell types and
functions to itself.

Data.Set is a functor from the category of Haskell types *with
decidable ordering* and *order-preserving* functions to itself.  
That's

not the same category, although it is closely related.



I nominate this post for the September 2008 Most Incomprehensible  
Cafe Post award! :-D


Seriously, that sounded like gibberish. (But then, you're talking to  
somebody who can't figure out the difference between a set and a  
class, so...)


All I know is that sometimes I write stuff in the list monad when  
the result really ought to be *sets*, not lists, because


1. there is no senamically important ordering

2. there should be no duplicates

But Haskell's type system forbids me. (It also forbids me from  
making Set into a Functor, actually... so no fmap for you!)


Think about it this way: fmap is supposed to be an homomorphism on the  
functor's structure, it just changes the type of the holes in the  
structure. To implement such map function in Set (not debating if Set  
should require Ord or not here!) and keep the structure invariants,  
the function you give to map should be order-preserving. Actually,  
Set.map accepts any function but it must construct the new Set using a  
fold behind the scenes because otherwise the function may break the  
internal balancing invariants. But map_monotonous is there for the  
case where it does respect the orders and the map can be done much  
more naturally and efficiently.


There's simply no way to state that a function must be monotonous  
using haskell's limited type system. except by using a new datatype  
that represents only the order-preserving functions between any two  
types A and B (is that even possible?). So you only see the [Ord]  
constraint getting in the way of defining a functor on Sets, but it's  
more profound than that, the functions themselves don't fit exactly.


Otherwise, to implement Sets correctly I think you need at least [Eq]  
(and give [Eq] preserving functions to fmap).
You can certainly declare a new EqFunctor (f : * - *) where eqfmap :  
Eq a, Eq b = (a - b) - f a - f b and assume that functions are  
[Eq]-preserving there (similarly with [Ord]).


Hope this helps,
-- Matthieu___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] The container problem

2008-09-27 Thread Bulat Ziganshin
Hello Andrew,

Saturday, September 27, 2008, 9:23:47 PM, you wrote:

 Can anybody actually demonstrate concretely how FDs and/or ATs would
 solve this problem? (I.e., enable you to write a class that any 
 container can be a member of, despite constraints on the element types.)

you may find comprehensive explanation in ghc user manual, it's
chapter about FDs use this as motivating example :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Red-Blue Stack

2008-09-27 Thread apfelmus
Thomas Davie wrote:

 Matthew Eastman wrote:

 The part of the assignment I'm working on is to implement a
 RedBlueStack, a stack where you can push items in as either Red or
 Blue. You can pop Red and Blue items individually, but the stack has
 to keep track of the overall order of items.

 i.e. popping Blue in [Red, Red, Blue, Red, Blue] would give [Red, Red,
 Blue]
 
 I wanted to add my own 2p to this discussion.  I'm not dead certain I
 understand what is meant by the statement above, so I'm going to make a
 guess that when we pop an item, the top item on the stack should end up
 being the next item of the same colour as we popped.
 
 In this interpretation, here's what I think is an O(1) implementation:
 
 data RBStack a = Empty
| More RBColour a (RBStack a) (RBStack a)
 
 data RBColour = Red | Blue
 
 rbPush :: Colour - a - RBStack a - RBStack a
 rbPush c x Empty = More c x Empty Empty
 rbPush c x e@(More c' v asCs nextNonC)
   | c == c'   = More c x e nextNonC
   | otherwise = More c x nextNonC e
 
 rbPop :: Colour - RBStack a - RBStack a
 rbPop c Empty = error Empty Stack, can't pop
 rbPop c (More c' v asCs nextNonC)
   | c == c'   = asCs
   | otherwise = rbPop c nextNonC
 
 The idea is that an RBStack contains its colour, an element, and two
 other stacks -- the first one is the substack we should get by popping
 an element of the same colour.  The second substack is the substack we
 get by looking for the next item of the other colour.
 
 When we push, we compare colours with the top element of the stack, and
 we swap around the same coloured/differently coloured stacks appropriately.
 
 When we pop, we jump to the first element of the right colour, and then
 we jump to the next element of the same colour.
 
 I hope I haven't missed something.

This looks O(1) but I don't understand your proposal enough to say that
it matches what Matthew had in mind.

Fortunately, understanding can be replaced with equational laws :) So, I
think Matthew wants the following specification: A red-blue stack is a
data structure

  data RBStack a

with three operations

  data Color = Red | Blue

  empty :: RBStack a
  push  :: Color - a - RBStack a - RBStack a
  pop   :: Color - RBStack a - RBStack a
  top   :: RBStack a - Maybe (Color, a)

subject to the following laws

 -- pop removes elements of the same color
  pop Red  . push Red  x = id
  pop Blue . push Blue x = id

 -- pop doesn't interfere with elements of the other color
  pop Blue . push Blue x = push Blue x . pop Red
  pop Red  . push Red  x = push Red  x . pop Blue

 -- top returns the last color pushed or nothing otherwise
  (top . push c x) stack = Just (c,x)
   top empty = Nothing

 -- pop on the empty stack does nothing
 pop c empty = empty

These laws uniquely determine the behavior of a red-blue stack.

Unfortunately, your proposal does not seem to match the second group of
laws:

   (pop Blue . push Red r . push Blue b) Empty
  = pop Blue (push Red r (More Blue b Empty Empty))
  = pop Blue (More Red r Empty (More Blue b Empty Empty))
  = pop Blue (More Blue b Empty Empty)
  = Empty

but

  = (push Red r . pop Blue . push Blue b) Empty
  = push Red r (pop Blue (More Blue b Empty Empty))
  = push Red r Empty
  = More Red r Empty Empty

The red element got lost in the first case.


Regards,
apfelmus

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


[Haskell-cafe] ATs [The container problem]

2008-09-27 Thread Andrew Coppin

Antoine Latter wrote:

Sure!  Using type-families:

  

class Container c where
   type Elem c
   insert :: Elem c - c - c



  

instance Container [a] where
   type Elem [a] = a
   insert = (:)



  

instance Container ByteString where
   type Elem ByteString = Word8
   insert = BS.cons



  

instance Ord a = Container (Set a) where
   type Elem (Set a) = a
   insert = Set.insert



  


That's more or less how I was hoping it works. (Was unsure of the actual 
syntax, and the documentation is rather terse.)


So there's a class called Container that has a _type_ that is 
_associated_ with it, representing the type of the elements? And you can 
set that type to be either a type variable or an explicit type?



Now the hard part is coming up with a proper API and class hierarchy.
  


So... exactly like in every OOP language in existence then? ;-)

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


[Haskell-cafe] FDs [The container problem]

2008-09-27 Thread Andrew Coppin

Bulat Ziganshin wrote:

Hello Andrew,

Saturday, September 27, 2008, 9:23:47 PM, you wrote:

  

Can anybody actually demonstrate concretely how FDs and/or ATs would
solve this problem? (I.e., enable you to write a class that any 
container can be a member of, despite constraints on the element types.)



you may find comprehensive explanation in ghc user manual, it's
chapter about FDs use this as motivating example :)
  


Section 8.6.2, Functional Dependencies: There should be more 
documentation, but there isn't (yet). Yell if you need it.


Yeah, that's real helpful. :-P But hey, there's an academic paper... *sigh*

Ooo, wait a sec, section 8.6.2.2. That helps...

Mmm, OK. Now can somebody explain the FDs cause problems part?

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


Re: [Haskell-cafe] Re: Red-Blue Stack

2008-09-27 Thread Thomas Davie


On 27 Sep 2008, at 20:16, apfelmus wrote:


Thomas Davie wrote:


Matthew Eastman wrote:


The part of the assignment I'm working on is to implement a
RedBlueStack, a stack where you can push items in as either Red or
Blue. You can pop Red and Blue items individually, but the stack has
to keep track of the overall order of items.

i.e. popping Blue in [Red, Red, Blue, Red, Blue] would give [Red,  
Red,

Blue]


I wanted to add my own 2p to this discussion.  I'm not dead certain I
understand what is meant by the statement above, so I'm going to  
make a
guess that when we pop an item, the top item on the stack should  
end up

being the next item of the same colour as we popped.

In this interpretation, here's what I think is an O(1)  
implementation:


data RBStack a = Empty
  | More RBColour a (RBStack a) (RBStack a)

data RBColour = Red | Blue

rbPush :: Colour - a - RBStack a - RBStack a
rbPush c x Empty = More c x Empty Empty
rbPush c x e@(More c' v asCs nextNonC)
 | c == c'   = More c x e nextNonC
 | otherwise = More c x nextNonC e

rbPop :: Colour - RBStack a - RBStack a
rbPop c Empty = error Empty Stack, can't pop
rbPop c (More c' v asCs nextNonC)
 | c == c'   = asCs
 | otherwise = rbPop c nextNonC

The idea is that an RBStack contains its colour, an element, and two
other stacks -- the first one is the substack we should get by  
popping
an element of the same colour.  The second substack is the substack  
we

get by looking for the next item of the other colour.

When we push, we compare colours with the top element of the stack,  
and
we swap around the same coloured/differently coloured stacks  
appropriately.


When we pop, we jump to the first element of the right colour, and  
then

we jump to the next element of the same colour.

I hope I haven't missed something.


This looks O(1) but I don't understand your proposal enough to say  
that

it matches what Matthew had in mind.

Fortunately, understanding can be replaced with equational laws :)  
So, I

think Matthew wants the following specification: A red-blue stack is a
data structure

 data RBStack a

with three operations

 data Color = Red | Blue

 empty :: RBStack a
 push  :: Color - a - RBStack a - RBStack a
 pop   :: Color - RBStack a - RBStack a
 top   :: RBStack a - Maybe (Color, a)

subject to the following laws

-- pop removes elements of the same color
 pop Red  . push Red  x = id
 pop Blue . push Blue x = id

-- pop doesn't interfere with elements of the other color
 pop Blue . push Blue x = push Blue x . pop Red
 pop Red  . push Red  x = push Red  x . pop Blue

-- top returns the last color pushed or nothing otherwise
 (top . push c x) stack = Just (c,x)
  top empty = Nothing

-- pop on the empty stack does nothing
pop c empty = empty

These laws uniquely determine the behavior of a red-blue stack.

Unfortunately, your proposal does not seem to match the second group  
of

laws:

  (pop Blue . push Red r . push Blue b) Empty
 = pop Blue (push Red r (More Blue b Empty Empty))
 = pop Blue (More Red r Empty (More Blue b Empty Empty))
 = pop Blue (More Blue b Empty Empty)
 = Empty

but

 = (push Red r . pop Blue . push Blue b) Empty
 = push Red r (pop Blue (More Blue b Empty Empty))
 = push Red r Empty
 = More Red r Empty Empty

The red element got lost in the first case.


I don't think my proposal even meets the first set of laws -- I  
interpretted the question differently.


pop Red . push Red 1 (More Blue 2 Empty (More Red 3 Empty Empty)) ==  
More Red 3 Empty Empty


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


[Haskell-cafe] TH code for deriving Binary and NFData instances

2008-09-27 Thread Tim Newsham

Here's some TH code for automatically deriving Data.Binary
and Control.Parallel.Strategies.NFData instances:

http://www.thenewsh.com/~newsham/store/DeriveBinary.hs

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Symposium videos

2008-09-27 Thread Don Stewart

Malcolm.Wallace:
 Guerilla videos of the Haskell Symposium 2008 presentations.  Enjoy.

Now on haskell.org,

http://haskell.org/haskellwiki/Video_presentations/Haskell_Symposium_2008

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


[Haskell-cafe] Re: Haddock + Hoogle == Javadoc on steroids

2008-09-27 Thread Simon Michael

Taking this to haskell-cafe..

http://joyful.com/repos/darcs-sm/api-doc is a mashup of haddock, hoogle
and hscolour (and darcsweb, darcs-graph - see http://joyful.com/repos).

It's rough but quite useful - a few minutes here gave me a much better
understanding of the big picture of darcs code. By alternating shift 
enter in the contents pane I could browse quickly through all modules.

Improvement: one could do a lot of useful magic with javascript. But it
would be more powerful to improve the tools, eg I'd like if haddock had
frames/no-frames built in and hoogle could be made to work in either
case. I haven't had time to work on this, currently I hard-code the
target in hoogle and munge the haddock output slightly (see recent patch
in darcs-unstable).

As you say it would be great to keep improving this area and baking it
into our tools and infrastructure. Highly accessible and efficient docs
and code browsing tools help a lot!


On Sep 27, 2008, at 1:49 PM, Jason Dagit wrote:

Simon,

I'm wondering if you could find a way to make it trivial for people using 
cabal to combine haddock and hoogle the way you have for darcs?

Some ideas:
1) Depend entirely on cabal for the auto setup of things
2) Provide the framed interface on your webpage also has a layout in emacs (so 
people can use either web or emacs)
3) Package it so that people just 'cabal install hoodock  hoddock ./src' and 
then they are done for 90% of cases
4) Provide demos for darcs and something else large like GHC

What do you think?  If you need help with it, I'm sure there are tons of people 
on Haskell-Cafe that would really dig this and help you with it.

Thanks, I love it!
Jason


Thanks!

-Simon

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


Re: [Haskell-cafe] The container problem

2008-09-27 Thread Ariel J. Birnbaum
 I'm not actually bothered about every possible monad being representable
 as such in Haskell. I'd just like Set to work. ;-)

What would work mean in this case? I see two different meanings:

1. Use monadic operations (mapM, guard) on Sets. 

 How would you decide which operations are allowed and which aren't? A 
possible answer would be: if you can add an implicit Ord constraint for every 
argument of m (where m is constrained to be a Monad), you can instantiate m 
as Set. So
  sequence :: (Monad m) = [m a] - m [a]
would work since [a] is an instance of Ord whenever a is but
  ap :: (Monad m) = m (a - b) - m a - m b
wouldn't since we can't have a (meaningful) Ord instance for a - b even if a 
and b are themselves instances.

 Such a mechanism is, of course, broken.

 Consider the following alternative definition for liftM2:
   liftM2 :: (Monad m) = (a - b - c) - m a - m b - m c
   liftM2 f ma mb mc = return f `ap` ma `ap` mb `ap` mc
   -- deliberately avoiding Applicative and Functor

 While the type of liftM2 indicates it should work (and the definition found 
on GHC actually does), in this case it would utterly break at the return f 
and the aps. In other words, one can't rely on the type alone to know 
whether a monadic operation is applicable to Set. In OOP, I think they'd call 
this a violation of Liskov's Substitution Principle.

2. Make the nice monadic syntax work for sets.

 In this case I'd restate the problem as not being able to extend Haskell's 
syntax within your program (a problem shared by most non-Lisp languages). 
While TH provides a fairly decent solution in this respect, it's still far 
from Lisp's flexibility. In this respect, does anyone know how the Liskell 
project is doing? The site and mailing list seem pretty silent...

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


Re: [Haskell-cafe] Re: Red-Blue Stack

2008-09-27 Thread jean verdier
I'm a haskell beginner so the following code might not meet haskell
coding standards. I think that it is a correct O(1) implementation.
Sorry if i simply recoded an already posted solution that i did not
understand correctly.

--- code -
module Main where

data Col a
  = Red a
  | Blue a

data RBStack a = 
  RBS [Col Int]  -- order
  [a]-- blues
  [a]-- reds 

empty = RBS [] [] []

push (Blue e) (RBS [][] [])   
  = RBS [Blue 1]  [e][]
push (Blue e) (RBS ((Blue n):ns) bs rs)   
  = RBS ((Blue (n+1)):ns) (e:bs) rs
push (Blue e) (RBS nsbs rs)   
  = RBS ((Blue 1):ns) (e:bs) rs
push (Red e)  (RBS [][] [])   
  = RBS [Red 1]   [] [e]
push (Red e)  (RBS ((Red n):ns)  bs rs)   
  = RBS ((Red (n+1)):ns)  bs (e:rs)
push (Red e)  (RBS nsbs rs)   
  = RBS ((Red 1):ns)  bs (e:rs)

popBlue (RBS [] _ _)
  = error no blue, empty stack
popBlue (RBS [Red _] _ _)   
  = error no blue
popBlue (RBS ((Red nr):(Blue 1):[]) [b] rs) 
  = RBS [Red nr]   [] rs
popBlue (RBS ((Red nr):(Blue 1):(Red nr'):s) (b:bs) rs) 
  = RBS ((Red (nr+nr')):s) bs rs
popBlue (RBS ((Red nr) :(Blue nb):s) (b:bs) rs) 
  = RBS ((Red nr):(Blue (nb-1)):s) bs rs
popBlue (RBS ((Blue 1):s) (b:bs) rs)
  = RBS s  bs rs
popBlue (RBS ((Blue nb):s) (b:bs) rs)   
  = RBS (Blue (nb-1):s)bs rs

popRed (RBS [] _ _) 
  = error no red, empty stack
popRed (RBS [Blue _] _ _)   
  = error no red
popRed (RBS ((Blue nb):(Red 1):[]) bs [r])  
  = RBS [Blue nb]  bs []
popRed (RBS ((Blue nb):(Red 1):(Blue nb'):s) bs (r:rs)) 
  = RBS ((Blue (nb+nb')):s)bs rs
popRed (RBS ((Blue nb):(Red nr):s) bs (r:rs))   
  = RBS ((Blue nb):(Red (nr-1)):s) bs rs
popRed (RBS ((Red 1):s) bs (r:rs))  
  = RBS s  bs rs
popRed (RBS ((Red nr):s) bs (r:rs)) 
  = RBS (Red (nr-1):s) bs rs

pop (RBS [] _ _)   = error empty stack
pop rbs@(RBS ((Red _):_) _ _)  = popRed rbs
pop rbs@(RBS ((Blue _):_) _ _) = popBlue rbs

pp (RBS [] [] []) = 
pp (RBS ((Red 1):s) bs (r:rs)) 
  = r  ++ (pp (RBS s bs rs))
pp (RBS ((Red n):s) bs (r:rs)) 
  = r  ++ (pp (RBS ((Red (n-1)):s) bs rs))
pp (RBS ((Blue 1):s) (b:bs) rs) 
  = b  ++ (pp (RBS s bs rs))
pp (RBS ((Blue n):s) (b:bs) rs) 
  = b  ++ (pp (RBS ((Blue (n-1)):s) bs rs))

altPushRed  0 = empty
altPushRed  n = push (Red n) (altPushBlue (n-1))
altPushBlue 0 = empty
altPushBlue n = push (Blue n) (altPushRed (n-1))

main = do
  let s = altPushRed 4
  s1 = popBlue $ popBlue $ s
  s2 = popRed $ popRed $ s
  s3 = pop $ pop $ s
  putStrLn (s  =  ++ (pp s))
  putStrLn (s1 =  ++ (pp s1))
  putStrLn (s2 =  ++ (pp s2))
  putStrLn (s3 =  ++ (pp s3))


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


Re: [Haskell-cafe] TH code for deriving Binary and NFData instances

2008-09-27 Thread Tim Newsham

Here's some TH code for automatically deriving Data.Binary
and Control.Parallel.Strategies.NFData instances:

   http://www.thenewsh.com/~newsham/store/DeriveBinary.hs


Saizan pointed me to:
http://www-users.cs.york.ac.uk/~ndm/derive/

which does most of what DeriveBinary.hs does (and lots more).

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe