Re: [Haskell-cafe] ANNOUNCE: lens-family-th 0.1.0.0

2012-07-07 Thread roconnor

On Fri, 6 Jul 2012, Dan Burton wrote:


Following the announcement of lens-family, I'm pleased to announce 
lens-family-th 0.1.0.0, a Template Haskell library supplying macros to generate
lens-family lenses for fields of data types declared with record syntax.

Be warned that currently, type signatures are *not* generated alongside the 
lens definitions. Type inference should correctly determine the type of the
generated lenses, but I have structured the library code so that in the future, 
type signatures can also be generated. Patches welcome!

http://hackage.haskell.org/package/lens-family-th


I cannot help but wonder if it is better to *not* generate type signatures 
(or at least have an option not to).


At the moment one can write:


import Lens.Family2.Stock
import Lens.Family2.TH

data Foo a = Foo { _bar :: Int, _baz :: a }
   deriving (Show, Read, Eq, Ord)
$(mkLenses ''Foo)

-- | My documentation for the 'bar' lens.
bar :: Lens (Foo a) Int

-- | My documentation for the 'baz' lens.
baz :: LensFamily (Foo a) (Foo a') a a'


I don't know if it is possible to add haddock to functions whose type 
signatures are generated by template haskell.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''

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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: lens-family-th 0.1.0.0

2012-07-07 Thread roconnor
I don't know if it is possible to add haddock to functions whose type 
signatures are generated by template haskell.


Could the documentation be an argument of mkLenses?


Does haddock run on the template-haskell expanded code?

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''

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


[Haskell-cafe] ANNOUNCE: lens-family 0.0.0

2012-07-06 Thread roconnor
I'm pleased to announce the first release of lens-family-core and 
lens-family.


This package provide first class(†) functional references. In addition to 
the usual operations of getting, setting and composition, plus integration 
with the state monad, lens families provide some unique features:


* Polymorphic updating
* Cast projection functions to read-only lenses
* Cast semantic editor combinators to modify-only lenses

(†) For optimal first-class support use the lens-family package with rank 
2 / rank N polymorphism. Lens.Family.Clone allows for first-class support 
of lenses for those who require Haskell 98.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell showcase in 5 minutes

2012-02-27 Thread roconnor
In less than 5 minutes I can solve NP-Complete problems in restaurant 
orders:


http://www.reddit.com/comments/24p2c/xkcd_does_anyone_else_feel_compelled_to_solve_this/c24pc5

On Mon, 27 Feb 2012, Arnaud Bailly wrote:


Hello Cafe,

I will be (re)presenting Haskell in a Batlle Language event Wednesday 
evening: A fun and interactive contest where various programming language champions try 
to attract as much
followers as possible in 5 minutes.

Having successfully experimented the power of live coding in a recent Haskell 
introduction for the Paris Scala User Group, I would like to do the same but 
given the time frame I need a
simpler example than the music synthesizer program.

So I would like to tap in the collective wisdom looking for some concise, 
eye-opening, mind-shaking and if possible fun example of what one can achieve 
in Haskell. Things that sprung to
my mind are rather dull: prime factors, fibonacci numbers.

Thanks in advance,
Arnaud




--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''

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


Re: [Haskell-cafe] ANNOUNCE: partial-lens 0.0.1

2011-12-21 Thread roconnor

On Wed, 21 Dec 2011, Erik Hesselink wrote:


How does this relate to the Maybe lenses in fclabels [1]?

Erik

[1] 
http://hackage.haskell.org/packages/archive/fclabels/1.0.4/doc/html/Data-Label-Maybe.html


It appears to be somewhere between similar and the same.

*** Comparison of API

Data.Label.Maybe.get corresponds to Data.Lens.Partial.getPL

Data.Label.Maybe.set roughly corresponds to Data.Lens.Partial.trySetPL 
except that trySetPL will bail out early if the reference is null.  We can 
match the signature of set more precisely by:


Data.Label.Maybe.set l v r ~ Data.Lens.Partial.trySetPL l r * pure v

Data.Label.Maybe.modify would correspond to Data.Lens.Partial.tryModPL if 
I had implemented it ... which maybe I ought to.


Data.Label.Maybe.embed corresponds to a composition of totalLens and 
maybeLens.  More specifically


Data.Label.Maybe.embed l ~ Data.Lens.Partial.maybeLens . 
Data.Lens.Partial.totalLens l

Data.Label.MaybeM.gets roughly corresponds to 
Data.Lens.Partial.Lazy.accessPlus except that accessPlus is particular to 
StateT because partial-lens is a Haskell 98 compliant package.  I need to 
write partial-lens-fd which will contain a function precisely 
corresponding to Data.Label.MaybeM.gets


I don't have Data.Label.MaybeM.asks, because there was no corresponding 
functionality in data-lens.  We should probably add a version of this.


*** Comparison of representation

The usual differences between data-lens and fclabels applies to 
partial-lens as well.  The representation for data-lens and 
partial-lens allows modify to be done with one case analysis on a record 
since the getter and setters are combined into one coalgebra whereas in 
fclabels two case analysis must be done: one for the getter and one for 
the setter.  When chains of lenses are composed, I'm told the differences 
become more apparent.


In partial-lens, the combination of getter and setter into a single 
coalgebraic operations means that the getter and setter are statically 
forced to return Nothing on the same record; but this is not enforced with 
the fclabels representation.


That said, perhaps the MaybeLens from fclabels is trying to do something 
different.  I don't know what laws you expect to hold for the getter and 
setters of a maybe lens since it isn't documented (actually I appear to 
have also forgotten to document the coalgebra laws for a comonad in my 
package) so perhaps MaybeLens are intended to be more general than partial 
lenses.


For example maybe a user wants to make it illegal to set the birth date to 
be greater than the death date in a record.  In this case getting the 
birth date will succeed, but setting will fail if the provided birth date 
out of bounds.  This is possible to write using MaybeLens, but is 
impossible with partial lenses since with partial-lenses either the 
reference is null, meaning getting and setting both fail, or it is not 
null which means that getting and setting both succeed.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''

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


[Haskell-cafe] ANNOUNCE: partial-lens 0.0.1

2011-12-20 Thread roconnor
Do you miss null references from your old imperative programming days? 
Wish that the worlds best imperative language had null references?  Now 
your wishes have come true with the new partial-lens package!


partial-lens augment edwardk's data-lens package with partial lens. 
Partial lenses are like regular lenses but have the possibility of not 
referencing anything.  In other words, null references are possible.  One 
notable different with null references from this package is that you can 
set them without getting a run-time error.  Instead setting a null 
reference is a no-op; however it is possible to determine if setting 
failed from the return value of the assignment operation.


Actually I don't have any applications for partial lenses myself, so if 
you find this library useful, please let me know.  I wrote this mostly 
because we know what partial lenses are in theory (they are the coalgebras 
of the (Identity :+: Store b) comonad) but I wanted to see what a real 
library would look like.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''

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


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-20 Thread roconnor

On Tue, 20 Sep 2011, Alexander Solla wrote:




On Tue, Sep 20, 2011 at 1:22 PM, Jake McArthur jake.mcart...@gmail.com wrote:
  On Tue, Sep 20, 2011 at 3:48 PM, Chris Smith cdsm...@gmail.com wrote:
   But it would be the *wrong* thing to use as a desugaring for list range
   notation.  List ranges are very unlikely to be useful or even meaningful
   for most such enumerations (what is [ Red, Green .. LightPurple]?); and
   conversely, as we've seen in this thread, list ranges *are* useful in
   situations where they are not a suitable way of enumerating all values
   of a type.

This makes me wonder if maybe the reason this discussion is happening
at all is that we don't have a well-defined meaning for what Enum
*is*.


Enum is the class that represents enumerable types.  In other words, the class 
of things that can be injected into the natural numbers.  These types
inherit an order from the natural numbers, ordering by images under this 
injection.

Now, we might not like that order, and it might not agree with an Ord instance, 
but it exists.


For what it's worth, at some point in time I was sketching a proposal to 
split the Enum class into two classes because I felt that two distinct 
ideas were being conflated.  Unfortunately this was years ago and I have 
forgotten what the details I was thinking.  Perhaps someone can 
reconstruct a proposal along these lines.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Pointed, but not Applicative

2011-08-31 Thread roconnor

On Sat, 27 Aug 2011, Sönke Hahn wrote:


Hi!

I was reading through the Typeclassopedia ([1]) and I was wondering which 
type could be an instance of Pointed, but not of Applicative. But I can't 
think of one. Any ideas?


(Identity :+: Store s) is a comonad that is also instance of Pointed, but 
I do not believe it is an instance Applicative.


newtype SemiStore s a = (Identity :+: Store s) a

instance Pointed (SemiStore s) where
  pure a = Inl (Identity a)

Coalgebras of the (Identity :+: Store s) comonad form the type of partial 
lenses so this isn't just an academic functor.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Pointed, but not Applicative

2011-08-31 Thread roconnor

On Wed, 31 Aug 2011, rocon...@theorem.ca wrote:


On Sat, 27 Aug 2011, Sönke Hahn wrote:


Hi!

I was reading through the Typeclassopedia ([1]) and I was wondering which 
type could be an instance of Pointed, but not of Applicative. But I can't 
think of one. Any ideas?


(Identity :+: Store s) is a comonad that is also instance of Pointed, but I 
do not believe it is an instance Applicative.


newtype SemiStore s a = (Identity :+: Store s) a

instance Pointed (SemiStore s) where
 pure a = Inl (Identity a)

Coalgebras of the (Identity :+: Store s) comonad form the type of partial 
lenses so this isn't just an academic functor.


Sorry I left out the newtype wrappers:

newtype SemiStore s a = SemiStore ((Identity :+: Store s) a)

instance Pointed (SemiStore s) where
  pure = SemiStore . Inl . Identity

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Categorical description of systems with dependent types

2010-12-02 Thread roconnor

On Thu, 2 Dec 2010, Petr Pudlak wrote:


Hi,

recently, I was studying how cartesian closed categories can be used to 
describe typed functional languages. Types are objects and morphisms are 
functions from one type to another.


Since I'm also interested in systems with dependent types, I wonder if there 
is a categorical description of such systems. The problem (as I see it) is 
that the codomain of a function depends on a value passed to the function.


I'd happy if someone could give me some pointers to some papers or other 
literature.


Voevodsky talks about the category of contexts in 
http://www.mefeedia.com/watch/31778282, which I understand is described 
in more detail in Semantics of type theory : correctness, completeness, 
and independence results by Thomas Streicher.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''

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


[Haskell-cafe] ANNOUNCE: Multiplate 0.0.1

2010-11-19 Thread roconnor
Multiplate is a lightweight generic library for mutually recursive data 
types that won't make Conor lose his lunch.


Multiplate is an alternative extension of the Uniplate/Compos core design 
to support mutually recursive datatypes in a way that is as powerful as 
Compos, almost as easy to use as Uniplate, and more portable than both of 
them.


Multiplate does not require you to rewrite your data type, does not 
require run-time reflection, does not require GADTs, and does not even 
require multi-parameter type classes. It only requires rank 3 
polymorphism.


http://hackage.haskell.org/package/multiplate-0.0.1

A more detailed paper is forthcoming, but the library is available to try 
right now.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-12 Thread roconnor

On Thu, 11 Nov 2010, Dan Doel wrote:


 intensional equality: two values are provably equal if they evaluate to the
 same normal form

 extensional equality: this incorporates non-computational rules, like the
 point-wise equality of functions.

Now, in a type theory where equality is intensional, I cannot prove:

 (forall x. f x = g x) - f = g

However, both these equalities (and others in between and on either side) are
*compatible*, in that I cannot disprove the above theorem in an intensional
theory.

What seq and serialize do is break from extensional equality, and allow us to
disprove the above (perhaps not for seq within a hypothetical theory, since
the invalidating case involves non-termination, but certainly for serialize).
And that's a big deal, because extensional equality is handy for the above
reasoning about programs.


As you are well aware in Coq, and in Agda we don't have an extensionality 
axiom; however this is not a problem because we simply use setoid equality 
to capture extenional reasoning and prove that in every specific case 
where we want to use extensioanl reasoning it is sound to do so.


Now suppose I add the following consitent axiom to Coq:

Axiom Church-Turing :
  forall f:Nat - Nat, exists e:Nat, forall n:Nat, {e}(n) = f(n)

This well-studied axiom is effectively what serialize is realizing[1]. 
Now, have I broken my old Coq proofs by adding this axiom?  No, of course 
not, because it is a consistent axioms and my proofs didn't use it.  My 
proofs were alreay explicity proving that extentional substitution was 
sound in those cases I was using it.


The same will be true for reasoning in Haskell.  Before serialization we 
knew that extensional substitution was sound, but after adding 
serialization we are now obligated to prove in the individual cases that 
extensional subsitution is sound and/or add extentionally preconditions to 
our proofs.  So no big deal; people have already been doing this in Coq 
and Agda for years.


[1]Actaully the realizer for serialize is *weaker* that this axioms.  The 
realizer for serialize would be (Nat - Nat) - IO Nat instead of (Nat - 
Nat) - Nat, so should have less impact that the Church-Turing axiom.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] an evil type hangs GHC

2010-11-12 Thread roconnor

See http://www.haskell.org/pipermail/haskell/2006-September/018497.html

On Fri, 12 Nov 2010, Petr Pudlak wrote:


On Fri, Nov 12, 2010 at 07:52:53PM +0100, Petr Pudlak wrote:
Hi, I was playing with the following example I found in D.A.Turner's paper 
Total Functional Programming:



data Bad a = C (Bad a - a)

bad1 :: Bad a - a
bad1 b@(C f) = f b

bad2 :: a
bad2 = bad1 (C bad1)


To my surprise, instead of creating a bottom valued function (an infinite 
loop), I managed to send the GHC compiler (ver. 6.12.1) to an infinite 
loop. Could anybody suggest an explanation? Is this a GHC bug? Or is this 
Bad data type so evil that type checking fails?


   Thanks,
   Petr


PS: The following code compiles, the difference is just in modifying bad2 
to include an argument:



data Bad a = C (Bad a - a)

bad1 :: Bad a - a
bad1 b@(C f) = f b

bad2 :: (a - a) - a
bad2 f = bad1 (C $ f . bad1)


[BTW, bad2 has the type of the Y combinator and indeed works as expected:


factorial :: (Int - Int) - Int - Int
factorial _ 0 = 1
factorial r n = n * (r (n-1))

main :: IO ()
main = print $ map (bad2 factorial) [1..10]


... so one can get general recursion just by crafting such a strange data 
type.]




--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What do you call Applicative Functor Morphism?

2010-11-06 Thread roconnor

On Sat, 6 Nov 2010, Sebastian Fischer wrote:


Hello,

I'm curious and go a bit off topic triggered by your statement:

On Nov 6, 2010, at 12:49 PM, rocon...@theorem.ca wrote:


An applicative functor morphism is a polymorphic function,
eta : forall a. A1 a - A2 a between two applicative functors A1 and A2 
that preserve pure and *


I recently wondered: why morphism and not homomorphism?


Morphisms can be more general than homomorphisms.  But in this case I mean 
the morphisms which are homomorphisms.  I was too lazy to write out the 
whole word.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] What do you call Applicative Functor Morphism?

2010-11-05 Thread roconnor

An applicative functor morphism is a polymorphic function,
eta : forall a. A1 a - A2 a between two applicative functors A1 and A2 
that preserve pure and *:


eta (pure c) = pure c
eta (f * x) = eta f * eta x

What do you guys call such a thing?  My leading candidate is idomatic 
transformation.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with haskell types

2010-07-30 Thread roconnor

I was one of the people on #haskell discussing this with Anupam.

Note that that when you remove the signature of d, the result complies and 
ghci will state the inferred type of d is exactly the signature that you 
are not allowed to write.


In my opinion, this is a bug in the Haskell 98 report where it says

``If the programmer supplies explicit type signatures for more than one 
variable in a declaration group, the contexts of these signatures must be 
identical up to renaming of the type variables.


The problem is that we cannot give a type signature to d with exactly the 
constraints of d_test because d doesn't have any type variable in its type 
signature.


At the very least the Haskell report should allow type checking to proceed 
if everything in a declaration group has a signature even if the 
signatures don't have identical constraints.


A trac ticket is needed for Haskell 2011, if one doesn't already exist.

On Sat, 31 Jul 2010, Anupam Jain wrote:


Hi,
I am having trouble getting a small program to compile. The helpful folks at 
#haskell created a version of the
program that does compile 
- http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28406#a28408 but it is not very 
clear
to them (and to me) why the original program wouldn't type compile in the first 
place.

Here's the program that refuses to compile -

module Delme () where

data DecisionState = A | B | C | D

d_test :: Eq b = b - b - DecisionState - DecisionState - ()
d_test test testVal trueState falseState =
if (test == testVal)
 then d trueState
 else d falseState

d :: DecisionState - ()
d A = d_test True True B C
d B = d_test 1 2 C D
d C = d_test True False A B
d D = ()
I get an error like -

Delme.hs:13:0:
    Contexts differ in length
      (Use -XRelaxedPolyRec to allow this)
    When matching the contexts of the signatures for
      d_test :: forall b.
                (Eq b) =
                b - b - DecisionState - DecisionState - ()
      d :: DecisionState - ()
    The signature contexts in a mutually recursive group should all be identical
    When generalising the type(s) for d_test, d

Putting in the extension does get the program to type check but the original 
program should have type compiled
in the first place.

The ironic thing we discovered is that if we remove the type declaration for 
'd', the program type checks, and
GHC then derives the exact same type which we removed!

Can some of the smarter people in the room please shed more light on this?

-- Anupam





--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-16 Thread roconnor

On Fri, 14 May 2010, Derek Elkins wrote:


You did it wrong.  All you did was Church encode the Either type.
Your bind is still doing a case-analysis.  All you have to do is use
ContT r (Either e).  The bind implementation for ContT is completely
independent of the underlying monad.  It doesn't even require the m in
ContT r m to be a functor, let alone a monad.  Therefore the ContT
bind doesn't do any case-analysis because it doesn't know anything
about the underlying monad.  One way to look at what is happening is
to compare it to Andrzej Filiniski's work in Representing Monads and
Representing Layered Monads.


What I don't get is that the bind operation for ContT and ErrCPS look so 
similar to me


ContT (stripping off the newtype constructor/destructors):
m = k  = \c - m (\a - k a c)

ErrCPS (stripping off the newtype constructor/destructors):
m = f = \err good - m err (\x - f x err good)

I don't get why one is slow but not the other?

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: US Patent for the idea ...

2010-04-17 Thread roconnor

On Fri, 16 Apr 2010, jerzy.karczmarc...@info.unicaen.fr wrote:


Somebody finally decided to ridiculise the system. If you want a good laugh,
see the patent 6,368,227. The search site is here:


As I recall some (patent?) laywer was simply teaching his kid how the 
patent process worked, so the worked through a real life example.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-15 Thread roconnor

On Thu, 15 Apr 2010, Maciej Piechotka wrote:


Are

f 0 = 1
f n = f (n - 1) + f (n - 2)

and

g 0 = 1
g n | n  0 = g (n - 1) + g (n - 2)
| n  0 = g (n + 2) - g (n + 1)

The same (morally) function?

Are:

f x = 2*x

and

f x = undefined

The same function


Try using the (x == y) == (f x = g y) test yourself.

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-15 Thread roconnor

On Wed, 14 Apr 2010, Ashley Yakeley wrote:


On 2010-04-14 14:58, Ashley Yakeley wrote:

On 2010-04-14 13:59, rocon...@theorem.ca wrote:


There is some notion of value, let's call it proper value, such that
bottom is not one.

In other words bottom is not a proper value.

Define a proper value to be a value x such that x == x.

So neither undefined nor (0.0/0.0) are proper values

In fact proper values are not just subsets of values but are also
quotients.

thus (-0.0) and 0.0 denote the same proper value even though they are
represented by different Haskell values.


The trouble is, there are functions that can distinguish -0.0 and 0.0.
Do we call them bad functions, or are the Eq instances for Float and
Double broken?


I'd call them disrespectful functions, or maybe nowadays I might call them
improper functions.  The good functions are respectful functions or
proper functions.

Proper functions are functions that are proper values i.e. f == f  which
is defined to mean that (x == y) == f x == f y (even if this isn't a 
decidable relation).



Worse, this rules out values of types that are not Eq.


Hmm, I guess I'm carrying all this over from the world of dependently 
typed programming where we have setoids and the like that admit equality 
relations that are not necessarily decidable.  In Haskell only the 
decidable instances of equality manage to have a Eq instance.  The other 
data types one has an (partial) equivalence relation in mind but it goes 
unwritten.


But in my dependently typed world we don't have partial values so there 
are no bottoms to worry about; maybe these ideas don't carry over 
perfectly.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread roconnor

On Wed, 14 Apr 2010, Ashley Yakeley wrote:


Joe Fredette wrote:

this is bounded, enumerable, but infinite.


The question is whether there are types like this. If so, we would need a new 
class:


 class Finite a where
   allValues :: [a]

 instance (Finite a,Eq b) = Eq (a - b) where
p == q = fmap p allValues == fmap q allValues


As ski noted on #haskell we probably want to extend this to work on 
Compact types and not just Finite types


instance (Compact a, Eq b) = Eq (a - b) where ...

For example (Int - Bool) is a perfectly fine Compact set that isn't 
finite and (Int - Bool) - Int has a decidable equality in Haskell (which 
Oleg claims that everyone knows ;).


I don't know off the top of my head what the class member for Compact 
should be.  I'd guess it should have a member search :: (a - Bool) - a 
with the specificaiton that p (search p) = True iff p is True from some a. 
But I'm not sure if this is correct or not.  Maybe someone know knows more 
than I do can claify what the member of the Compact class should be.


http://math.andrej.com/2007/09/28/seemingly-impossible-functional-programs/

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread roconnor

On Wed, 14 Apr 2010, Ashley Yakeley wrote:


On 2010-04-14 03:41, rocon...@theorem.ca wrote:

For example (Int - Bool) is a perfectly fine Compact set that isn't
finite


Did you mean Integer - Bool? Int - Bool is finite, but large.


Yes, I meant Integer - Bool.

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: instance Eq (a - b)

2010-04-14 Thread roconnor

On Wed, 14 Apr 2010, Ashley Yakeley wrote:


On 2010-04-14 13:03, Alexander Solla wrote:

If you're willing to accept that distinct functions can represent the
same moral function, you should be willing to accept that different
bottoms represent the same moral value.


Bottoms should not be considered values. They are failures to calculate 
values, because your calculation would never terminate (or similar 
condition).


Let's not get muddled too much in semantics here.

There is some notion of value, let's call it proper value, such that 
bottom is not one.


In other words bottom is not a proper value.

Define a proper value to be a value x such that x == x.

So neither undefined nor (0.0/0.0) are proper values

In fact proper values are not just subsets of values but are also 
quotients.


thus (-0.0) and 0.0 denote the same proper value even though they are 
represented by different Haskell values.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: DDC compiler and effects; better than Haskell?

2009-08-13 Thread roconnor

On Thu, 13 Aug 2009, rocon...@theorem.ca wrote:

Actually you need five versions: The pure version, the pre-order traversal, 
the post-order traversal, the in-order traversal, and the reverse in-order 
traversal.  And that is just looking at syntax.  If you care about your 
semantics you could potentially have more (or less).


Minor technical correction.  The four syntactic traversals are: pre-order, 
post-order, reverse pre-order, and reverse-post order.  The in-order and 
reverse in-order are examples of other semantic traversals specific to 
binary tree like structures.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: DDC compiler and effects; better than Haskell?

2009-08-12 Thread roconnor

On Wed, 12 Aug 2009, Peter Verswyvelen wrote:


I kind of agree with the DDC authors here; in Haskell as soon as a
function has a side effect, and you want to pass that function to a
pure higher order function, you're stuck, you need to pick the monadic
version of the higher order function, if it exists. So Haskell doesn't
really solve the modularity problem, you need two versions of each
higher order function really,


Actually you need five versions: The pure version, the pre-order 
traversal, the post-order traversal, the in-order traversal, and the 
reverse in-order traversal.  And that is just looking at syntax.  If you 
care about your semantics you could potentially have more (or less).


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking to check on some capabilities of Data.Colour

2009-08-06 Thread roconnor

On Thu, 6 Aug 2009, Jeff Heard wrote:


I was wondering if Data.Colour supported Double-valued colour
components  1.0 or less than 0.  I'm looking to create an HDR image
processing library, and Haskell has one of the most extensive and
correct colour models around, thanks to Russell.  With 16bpcc or
32bpcc images, however, I need to be sure to be able to correctly
calculate colour values that fall outside the usual [0.0,1.0] gamut.
Does Data.Colour support this functionality?


Data.Colour supports values outside the range [0,1] for most computations. 
Components are clamped when extracting to Bounded component types such as 
Word8 (see toSRGBBounded).  There may also some issues with negaive values 
when converting to non-linear coordinate systems via a transfer function. 
This is an area I haven't thought to much about, so there could be a few 
bugs lurking here.  If found they should be fixed, assuming right 
behaviour can be found.




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



--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking to check on some capabilities of Data.Colour

2009-08-06 Thread roconnor

On Thu, 6 Aug 2009, rocon...@theorem.ca wrote:


On Thu, 6 Aug 2009, Jeff Heard wrote:


I was wondering if Data.Colour supported Double-valued colour
components  1.0 or less than 0.  I'm looking to create an HDR image
processing library, and Haskell has one of the most extensive and
correct colour models around, thanks to Russell.  With 16bpcc or
32bpcc images, however, I need to be sure to be able to correctly
calculate colour values that fall outside the usual [0.0,1.0] gamut.
Does Data.Colour support this functionality?


Data.Colour supports values outside the range [0,1] for most computations.


To be slightly more techinical, I want add that Data.Colour.Colour is 
abstract and its interface cares nothing about [0,1].  Gammut issue only 
arise when converting the abstract data type to and from concrete 
coordinates, and which colours are outside [0,1]*[0,1]*[0,1] is coorinate 
system dependent.  Since Data.Colour.Colour is abstract and coordinate 
system indepenent, it cannot (or at least should not) care about such 
issues for oprations that deal only with abstract colours (operations such 
as blending, etc.)


Components are clamped when extracting to Bounded component types such as 
Word8 (see toSRGBBounded).  There may also some issues with negaive values 
when converting to non-linear coordinate systems via a transfer function. 
This is an area I haven't thought to much about, so there could be a few 
bugs lurking here.  If found they should be fixed, assuming right 
behaviour can be found.




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






--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-09 Thread roconnor

Max Rabkin wrote:

On Sat, Jul 4, 2009 at 8:38 PM, Andrew
Coppinandrewcoppin at btinternet.com wrote:


A few reasons:

1. I never knew it existed. ;-)



A good reason. However, it's good to do a quick search over Hackage
before uploading (or before writing) so you know what's out there.

Also, if you hadn't used an AC- prefix, you'd have had a name
collision. Is there a particular reason why you want your name in the
package name rather than just the author field?



I find it amazing that you independently chose to spell colour with a `u'. 
It makes me feel better about my choice.



2. It's mind-blowingly complex.



Colour *is* complex. Which is why I'm so glad Russell O'Connor did all
the hard work for me :)



Well, no, because now I'm going to have to spend a few hours trying to
find out what CIE is before I can even use that library.

I think really it's just aimed at a different problem. It looks like
it's trying to specify actual real-world colours. [It's news to me that
this isn't fundamentally impossible...] I'm only trying to specify
colours on a computer screen. And as we all know, computer screens
aren't calibrated in any way, and the same RGB value looks different on
each display. But then, I'm only trying to write a fractal generator, so
CIE specifications are somewhat overkill here. ;-)


You can use by lib without worrying about the CIE.  You can use my library 
without ever importing or using the word CIE.  However, the CIE stuff is 
there for those who need it.


Perhaps I (maybe with some help) need to make a tutorial on the haskell 
wiki to try to make it less intimidating.



3. It doesn't appear to provide arithmetic over colours.



It provides darken, blend and addition (though addition is called
mappend rather than (+)). signum, abs and fromInteger don't make a
huge amount of sense for colours.



Yeah, I implemented signum and so forth for colours and vectors, but
they're not particularly meaningful... [Insert remark here about
Haskell's numeric class hierachy.]

So mappend gives you colour addition [with the perplexing comments about
gamut, presumably some kind of small mammal?], but there's no
subtraction? No multiplication? No linear blending?


Linear blending is done by the affineCombo function.

I think the darken function will do what you mean by multiplication

Colour subtraction can be done by adding (using mappend) a colour that has 
been darkend by a factor of (-1).  I don't believe there is any demand for 
a colour subtraction fuction, so I don't have a name for it.


I suppose these sorts of questions can be put nicely into a short tutorial 
on the wiki.


4. It's parameterised over the component type; my library is hard-coded 

to

specific types for speed.



My feeling would be to trust the specializer until it lets me down.
Has it let you down in the past?



Heh, my colour library includes a custom floor implementation that talks
to the GHC primops directly because calling floor is too slow...

[In case that sounds like idle talk, I had a program go from 10 seconds
to less than 1 second just by using this function. There's a few tickets
about it on the GHC Trac.]


Certainly speed is an issue that I haven't tackled yet since I don't know 
too much about how to optimized Haskell code.  I was thinking of 
sprinkling in some SPECIALIZE pragmas and maybe adding some RULES to make 
operations more effecient.  For example we could have a rule to rewrite 
floor to some sort of GHC specific fast floor function. (Although that 
rule probably deserves to be in some sort of more general location).


Any help in this direction would be appricated (perferably while keeping 
things as portable as possible).


This all being said, the major problem my code solves is doing blending in 
a linear colour space. This necessarily make converting to non-linear sRGB 
for output much slower. So for people who want speed over proper blending, 
then probably AC-Colour is the package they need to reach for.


Essentially the two packages do fill different niches!


BTW, the EasyRaster package looks useful.



I haven't looked at EasyRaster yet, but I got excited when I saw it 
announced. :)


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Colour tutorial (Was: AC-Vector, AC-Colour and AC-EasyRaster-GTK)

2009-07-09 Thread roconnor

On Thu, 9 Jul 2009, rocon...@theorem.ca wrote:

You can use by lib without worrying about the CIE.  You can use my library 
without ever importing or using the word CIE.  However, the CIE stuff is 
there for those who need it.


Perhaps I (maybe with some help) need to make a tutorial on the haskell wiki 
to try to make it less intimidating.


Okay, I threw together a quick introduction at 
http://www.haskell.org/haskellwiki/Colour.  Any changes, comments, 
corrections, and addtions are welcome.  It's a wiki!


The word CIE does occur at all in the document.

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Removing mtl from the Haskell Platform

2009-05-12 Thread roconnor
I wanted to pass this idea around the cafe to get some thoughts before 
submitting a trac on this topic.


I'd like to see the mtl removed from the Haskell Platform.

The mtl was a tremendous step forward when it was developed.  However, we 
have learned a few things about monad transformers since the development 
of the mtl, and it is time that we moved forward.


There are at least 3 significant problem with the mtl.

1) `pass' should not be a member functions of the MonadWriter class.  It 
is my understanding that there is no `MonadWriter w m = MonadWriter w 
(ContT s m)' instance because the `pass' function cannot be implemented. 
I'm also highly suspicious of some other methods too (I'm looking at you 
`local').


2) The `StateT s (Cont r a)' instance of callCC is wrong.  The paper on 
modular monad transformers 
http://www.cs.nott.ac.uk/~mjj/pubs/mmt/mmt.pdf describes why this is 
wrong.


3) I am told by many people that the order of the state and value pair in 
`State' is backwards.  Actually, I'm not entirely sure what the issue is 
here, but I trust the people who say this.


I think that use of the mtl should be deprecated so that we move on to 
improved monad transformer libraries.  Having the mtl in the Haskell 
Platform does the opposite by further entrenching its use, possibly to the 
point where we may not be able to get rid of it for years.


If I had to recommend a replace library, I would pick monadLib.  However, 
there are other libraries, such as the mmtl and transformers and it's 
related packages that I haven't looked at, and may also make fine 
replacements for the mtl.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


mapM as a Space Leak (Was: [Haskell-cafe] about Haskell code written to be too smart)

2009-03-26 Thread roconnor

On Wed, 25 Mar 2009, Thomas Hartman wrote:


With the state version, there's a lot of behind-the-scenes magic, and
as we've seen, things can go wrong.

Also, the issue isn't infinite lists, but lists that are longer than
the sum of the partitions provided. The state monad partition version
goes equally as badly awry if the test is restructured as

testP pf = mapM_ putStrLn  [
 show . pf ( take 1000 [3,7..] ) $ [1..10]
 , show . pf [3,7,11,15] $ ( take (10^6) [1..])
 , show . head . last $ pf (take 1000 $ [3,3..]) [1..10^6]
   ]


This is interesting.  It seems to be the familiar issue that sequence does 
not play as nicely with the GC as one might imagine:

http://www.reddit.com/r/haskell/comments/7itbi/mapm_mapm_and_monadic_statements/c06rwnb?context=1

I suspect this may be a general problem that we will keep encountering 
when using higher-order functions, at least with this compiler.  I wonder 
if JHC or some other compiler might work better with these examples?


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO semantics and evaluation - summary

2009-02-13 Thread roconnor
I also recommend reading 
http://www.haskell.org/haskellwiki/IO_Semantics (mostly because I wrote 
it).  Feel free to improve upon it.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Laws and partial values (was: [Haskell-cafe] mapM_ - Monoid.Monad.map)

2009-01-24 Thread roconnor

On Fri, 23 Jan 2009, Luke Palmer wrote:


For example, it is possible to prove that foldr mappend mempty (x:xs) =
foldr1 mappend (x:xs).  Which means that anywhere in the source where we see
the former, we can clean it up to the latter.  However, if monad laws
don't apply to partial values, then we first have to prove that none of the
(x:xs) are _|_, perhaps even that no substrings are _|_.  This is a much
more involved transformation, so much so that you probably just wouldn't do
it if you want to be correct.

Bottoms are part of Haskell's semantics; theorems and laws have to apply to
them to.  You can pretend they don't exist, but then you have to be okay
with never using an infinite data structure.  I.e. if your programs would
run just as well in Haskell as they would in a call-by-value language, then
you don't have to worry about bottoms.


BTW, This last statement isn't true.  The expression (let x = 1:x in x) 
won't work in CBV, but it is a well defined value without any bottoms.
In fact, every subexpression in that value is a well defined value wihtout 
any bottoms.


Now I'm wondering how many bottoms I use in my actual code, because it 
seems like, even though I make use of lazy evaluation, I still don't have 
sub-expressions with bottoms.  If it is the case that I never make use of 
bottoms, then having laws only apply to total values is fine.


Obviously I use bottoms via the error function etc, but I don't count 
these.  These can only be accessed by calling functions with paramters 
violating their preconditions.  If I had dependent types, I'd place the 
preconditions formally into the definition of the function.  I'm looking 
for a place where I have a partial value as a sub-expression of my program 
in some essential way.  I find it plausible that this never happens.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Laws and partial values

2009-01-24 Thread roconnor

On Sat, 24 Jan 2009, Lennart Augustsson wrote:


You can dream up any semantics you like about bottom, like it has to
be () for the unit type.
But it's simply not true.  I suggest you do some cursory study of
denotational semantics and domain theory.
Ordinary programming languages include non-termination, so that has to
be captured somehow in the semantics.
And that's what bottom does.


I'd like to argue (but am not certain) that all the sub-expressions of all 
*correct* programs are total, or rather that the values that the 
sub-expressions represent are total.


One needs to distinguish between the value of the representatives of data, 
and the data being represented.  For example (constructive) real numbers 
are represented by Cauchy sequences, but real numbers are themselves a 
quotient of this type.  We cannot create a data type that directly 
represents a real numbers and are forced to use representatives to compute 
with them.  Similarly we want the reciprocal function only to be defined 
on real numbers that are apart from zero (the reciprocal total on this 
domain), but there is no such function type available in Haskell to do 
this. Therefore we represent it by a partial function.


Therefore we can safely reason about such programs by substitutions using 
laws (such as monoid laws) that are correct with respect to the *what the 
values are representing*. For example, real numbers form a monoid under 
addition only when the equivalence relation for the data that the values 
represent is used.  Would anyone here argue that (Sum CReal) should *not* 
be a Monoid instance?


Sorry if this sounds a bit muddled.  I need to find a clear way of 
conveying what I'm thinking. In short, my position is that partial values 
are only used to define the values of fixpoints and are sometimes used in 
the represenatives of data, but the data being represented is always 
total.  Monoid laws etc. only apply to the data being represented, not to 
the underlying represenations.


If my position is untenable, please explain. :)

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Laws and partial values

2009-01-24 Thread roconnor

On Sat, 24 Jan 2009, Jake McArthur wrote:

What you said makes little sense to me either. ;) But I will try to fit the 
pieces together as best I can.


It appears to me that you may be talking about isomorphisms between the 
concepts we try to map to data types and the data representations themselves, 
and that you are postulating that these concepts are necessarily total, 
therefore the representations should be as well, or something like that.


I'm saying that the concepts are necessarily total.  Acutally, now that I 
think about it, the concepts might not even have a CPO, so perhaps it is 
not meaningful to talk about if the concepts are total or not.  So I'll 
refine my position to saying that the concepts just are.


Their represenatives may not be total.  For example we represent the 
concept of the reciprocal over Rational (whose domain excludes 0) by a 
represenative, recip :: Rational - Rational, which is a partial function. 
In this case we could imagine an alternative implemenation of recip' :: 
NonZeroRational - Rational, which also represents the concept of the 
reciprocal and is a total function.  But in other cases such an 
alternative represenatitive cannot exist (e.g. recip for CReal).


I belive it is the case that the concepts are isomorphic to the 
represenatives under a specific PER.  I cannot imagine it any other way.


Anyhow, the big point is that monoid laws apply to the concepts, not to 
the representatives.


If my understanding of your point is correct, then I disagree with it. What 
you describe sounds like abstraction, and what you describe as a partial 
function sounds like a *leaky* abstraction. If we truly want to restrict the 
domain of a function to nonzero real numbers, then the total way to go 
about it would be to create a new type that represents this domain, say by 
wrapping your real number type with a newtype and only exporting smart 
constructors to build values of that type.


Ah, but it is impossible to create such smart constructors because it is 
undecidable if a particular CReal represents 0 or not.


Deep inside, the function will definitely require a partial expression, 
but this is abstracted away. Then you can define a Monoid instance for 
this domain without fear.


But you *still* have to account for nontermination. You can still arrive at a 
situation where you have


   _|_ `mappend` nonzeroRealNum


Since _|_ is a represenative that has no corresponding concept, the above 
program is simply an error.


. I hope I have understood correctly. I feel that I have not and that this 
email will just contribute to the confusion of other readers. :\


I hope I can work out my underdeveloped viewpoint through conversation. 
Hopefully I'll either see that I'm wrong, or convince people that I'm 
right. :)  I'm sort of refining it as I go along here.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Laws and partial values (was: [Haskell-cafe] mapM_ - Monoid.Monad.map)

2009-01-24 Thread roconnor

On Sun, 25 Jan 2009, Lauri Alanko wrote:


On Fri, Jan 23, 2009 at 08:10:38PM -0500, rocon...@theorem.ca wrote:

I'd like to argue that laws, such as monoid laws, do not apply to partial
values.  But I haven't thought my position through yet.


Before you do, you may want to read Fast and Loose Reasoning is
Morally Correct:

http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.59.8232


This is very good.

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Laws and partial values (was: [Haskell-cafe] mapM_ - Monoid.Monad.map)

2009-01-23 Thread roconnor

On Fri, 23 Jan 2009, Derek Elkins wrote:


mempty `mappend` undefined = undefined (left identity monoid law)
The above definition doesn't meet this, similarly for the right identity
monoid law.  That only leaves one definition, () `mappend` () = () which
does indeed satisfy the monoid laws.

So the answer to the question is Yes.  Another example of making
things as lazy as possible going astray.


I'd like to argue that laws, such as monoid laws, do not apply to partial 
values.  But I haven't thought my position through yet.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Laws and partial values (was: [Haskell-cafe] mapM_ - Monoid.Monad.map)

2009-01-23 Thread roconnor

Thanks for letting me reflect on this.

I assume that my final program (my final value) is always a total value. 
Anything else is an error.  Therefore, if we required relaxed monoid laws 
of the form


x `mappend` mzero = x

then we could safely substitute (x `mappend` mzero) by x without changing 
the final value (I think this true).  But the reverse substituion 
,replacing x with (x `mappend` mzero), might not be sound.  Now, I can see 
why you would prefer that the laws hold for partial values.


On Fri, 23 Jan 2009, Luke Palmer wrote:


On Fri, Jan 23, 2009 at 6:10 PM, rocon...@theorem.ca wrote:
  On Fri, 23 Jan 2009, Derek Elkins wrote:

mempty `mappend` undefined = undefined (left
identity monoid law)
The above definition doesn't meet this, similarly
for the right identity
monoid law.  That only leaves one definition, ()
`mappend` () = () which
does indeed satisfy the monoid laws.

So the answer to the question is Yes.  Another
example of making
things as lazy as possible going astray.


  I'd like to argue that laws, such as monoid laws, do not apply
  to partial values.  But I haven't thought my position through
  yet.


Please try to change your mind.  

You know how annoying it is when you are doing math, and you want to divide,
but first you have to add the provision that the denominator isn't zero.
 Saying that monoid laws do not apply to partial values, while easing the
implementation a bit, add similar provisions to reasoning. 

For example, it is possible to prove that foldr mappend mempty (x:xs) =
foldr1 mappend (x:xs).  Which means that anywhere in the source where we see
the former, we can clean it up to the latter.  However, if monad laws
don't apply to partial values, then we first have to prove that none of the
(x:xs) are _|_, perhaps even that no substrings are _|_.  This is a much
more involved transformation, so much so that you probably just wouldn't do
it if you want to be correct.

Bottoms are part of Haskell's semantics; theorems and laws have to apply to
them to.  You can pretend they don't exist, but then you have to be okay
with never using an infinite data structure.  I.e. if your programs would
run just as well in Haskell as they would in a call-by-value language, then
you don't have to worry about bottoms.

Luke




--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Improved documentation for Bool (Was: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt)

2009-01-18 Thread roconnor

On Sun, 18 Jan 2009, Ross Paterson wrote:


Anyone can check out the darcs repos for the libraries, and post
suggested improvements to the documentation to librar...@haskell.org
(though you have to subscribe).  It doesn't even have to be a patch.

Sure, it could be smoother, but there's hardly a flood of contributions.


I noticed the Bool datatype isn't well documented.  Since Bool is not a 
common English word, I figured it could use some haddock to help clarify 
it for newcomers.


-- |The Bool datatype is named after George Boole (1815-1864).
-- The Bool type is the coproduct of the terminal object with itself.
-- As a coproduct, it comes with two maps i : 1 - 1+1 and j : 1 - 1+1
-- such that for any Y and maps u: 1 - Y and v: 1 - Y, there is a unique 
-- map (u+v): 1+1 - Y such that (u+v) . i = u, and (u+v) . j = v

-- as shown in the diagram below.
--
--  1 -- u -- Y
--  ^ ^^
--  |/ |
--  i  u + v   v
--  | /|
-- 1+1 - j -- 1
--
-- In Haskell we call we define 'False' to be i(*) and 'True' to be j(*) 
-- where *:1.
-- Furthermore, if Y is any type, and we are given a:Y and b:Y, then we 
-- can define u(*) = a and v(*) = b.

-- From the above there is a unique map (u + v) : 1+1 - Y,
-- or in other words, (u+v) : Bool - Y.
-- Haskell has a built in syntax for this map:
-- @if z then a else b@ equals (u+v)(z).
--
-- From the commuting triangle in the diagram we see that
-- (u+v)(i(*)) = u(*).
--  Translated into Haskell notation, this law reads
-- @if True then a else b = a...@.
-- Similarly from the other commuting triangle we see that
-- (u+v)(j(*)) = v(*), which means
-- @if False then a else b = b@

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Names in Haskell (Was: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt)

2009-01-15 Thread roconnor
What I don't understand is why Monoid and Monad are objectionable, while 
Hash, Vector, Boolean, and Integer are (presumably) not objectionable. 
They all appear equally technical to me.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: unsafeInterleaveIO respecting order of actions

2009-01-01 Thread roconnor

On Fri, 2 Jan 2009, Achim Schneider wrote:


There are no lazy monads. Monads imply explicit sequencing... writing


I think this is an extremely bad thing to say and is a source of 
misunderstanding about monads and evaluation.  Most monads _are_ lazy, and 
it is important to understand that when trying to understand the run-time 
properties of your monadic code.


Monads sequence effects, but evaluation is an almost orthogonal issue. 
Here is a recent thread where I talk about laziness:


http://www.reddit.com/r/haskell/comments/7itbi/mapm_mapm_and_monadic_statements/c06s6pm

(for the short short story, simply try out

take 10 $ execWriter (sequence_ (repeat (tell x)))

)

Furthermore, the code in my article on recursive do from The.Monad.Reader 
issue #6 http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf 
requires the monads to be lazy in order to tie the knot.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] ANNOUNCE: colour 0.0.0

2008-10-24 Thread roconnor

On Fri, 24 Oct 2008, Sebastian Sylvan wrote:


Another useful predefined space which I didn't see is the YCoCg space, which is 
used in lots of
compression schemes (like H.264 IIRC).


YCoCg, like HLS and HSV, seems to not really be a colour space because it 
isn't well specified.  A transformation is given from some unknown RGB 
space.


Perhaps I should make a datatype for unknown RGB triple, and create HLS 
HSV, and YCoCg transforms from this type.  I can have toRGB709 and toSRGB 
take and return this unknown RGB triple type.


This would suggest changing sRGB and rgb709 from the type
sRGB :: a - a - a - Colour a

to

sRGB :: RGB a - Colour a

so the code sRGB r g b becomes sRGB (RGB r g b).  That doesn't seem 
very nice.


Also, I could add phantom type annotations to the RGB triple type, 
allowing it to be labeled as linear, or nonlinear, or other information.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe