Re: [Haskell-cafe] NewbieQ: colon prefix for operators, e.g., Ratio ?

2004-10-10 Thread Matt Harden
On Sunday 10 October 2004 10:35 pm, Brian Beckman wrote:
> Apologies if this is the wrong mailing list in which to pester folks with
> Newbie Questions, but I couldn't find my answer after half an hour of
> scouring the Haskell Report, the Haskell Wiki, the School of Expression
> book and a couple of tutorials.  The frustrating thing is that I know I saw
> the answer in ONE of those sources and it didn't stick at the time:
>
> what does it mean when an operator is prefixed by a colon?  For instance,
> in the Ratio module, the meaning of x % y is clear, but x :% y appears in
> multiple places and I'm confused.

It's in the Report. 



Operator symbols are formed from one or more symbol characters, as defined
above, and are lexically distinguished into two namespaces (Section 1.4):

* An operator symbol starting with a colon is a constructor.
* An operator symbol starting with any other character is an ordinary
identifier.

So (:%) is the constructor for the Ratio type, whereas (%) is a function that 
returns a Ratio.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: determining if a int is a power

2003-11-09 Thread Matt Harden
On Saturday 08 November 2003 04:31 am, Wolfgang Jeltsch wrote:
> Am Samstag, 8. November 2003, 00:22 schrieb Hamilton Richards:
> > Also note that
> >
> > if x then True else False
> >
> > is just a verbose way of writing
> >
> > x
>
> Actually, it's just a verbose way of writing x `seq` x, but this detail is,
> of course, not interesting for beginners.

??

Sorry, but x `seq` x is just a verbose way of saying x.

Matt

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: "listProduct" -- is this a standard function?

2003-10-15 Thread Matt Harden
On Wednesday 15 October 2003 11:07 am, Graham Klyne wrote:
> I've constructed a "listProduct" function that I think I've seen somewhere
> else... is it a standard function?  If so, where is it defined?

Yes.  It's called "sequence".  It's defined in the prelude.
It works with arbitrary monads, not just lists.

I think that's pretty cool.  8-)

Matt Harden

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Puzzle

2003-08-26 Thread Matt Harden
On Friday 22 August 2003 04:29 pm, Ralf Hinze wrote:
> | Seeing as its thst time of year again and everyone is posting their
> | homework, has anyone got any good puzzles to do?
> | I wouldn't mind having a go at something a bit tricky.
>
> Here is another one: figure out what `unknown' is.
>
> > unknown   =  mysterious unknown
> >
> > mysterious ks =  0 : weird ks
> > weird (k : ks)=  (k + 1) : mysterious ks


Cool!  That leads me to this contraption:

> tricky= 0 : enigma tricky tricky
> enigma (k : ks)   = (k :) . labyrinth (enigma ks)
> labyrinth f (k : _ : ks)  = (k + 1) : f ks

Figure out what `tricky' is, and what its relationship is to `unknown'.

Enjoy!

Matt Harden

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Writing a counter function

2002-07-02 Thread Matt Harden

John Hughes wrote:

> On Sun, 30 Jun 2002, Jon Cast wrote:
> 
>>Mark Carroll <[EMAIL PROTECTED]> wrote:
>>
>>>On Sat, 29 Jun 2002, Samuel E. Moelius III wrote:
>>>(snip)
>>>
>>>>Here's another not-exactly-what-you-wanted solution.  :)
>>>
>>>(snip)
>>
>>>Do any of the experimental extensions to Haskell allow a
>>>what-he-wanted solution? I couldn't arrange one in H98 without
>>>something having an infinitely-recursive type signature.
>>
>>That's because the problem requires an infinitely-recursive type.
>>
>>(snip)
>>
> 
> It isn't particularly hard to implement this. Haskell typecheckers use
> unification to match types up; the only difference is that a graph
> unification algorithm would be needed instead. Such algorithms exist ---
> the only real difference is you have to remember what you're unifying to
> avoid falling into a loop when unifying graphs with cycles.
> 
> The idea of adding this to Haskell has been proposed several times, but
> never implemented. And the reason for THAT is that it would make type
> errors significantly harder to understand.
> 
> (snip)
 >

Yes, but the dreaded Monomorphism Restriction was added for the same 
reason, wasn't it?  Haskell allows us to get around the M.R. by using 
explicit type signatures where required.  It seems to me that we could 
allow recursive types in the same way -- simply require a type signature 
for toplevel objects with recursive types.  Is there a reason why this 
wouldn't work?

Regards,

Matt Harden

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Question about typing

2001-04-09 Thread Matt Harden

I won't try to explain functional dependencies, because I don't
understand them all that well, there is documentation, and others on
this list could explain them much better than I can.

Here is an example of how to implement a polymorphic zip (used together
with the ZipFunctor I defined earlier):

> class Zippable a f b | a -> f b, f b -> a where
>zip :: a -> f b
> 
> instance (ZipFunctor f) => Zippable (f a,f b) f (a,b) where
>zip (xs,ys) =
>fmap (,) xs `zap` ys
> 
> instance (ZipFunctor f) => Zippable (f a,f b,f c) f (a,b,c) where
>zip (xs,ys,zs) =
>fmap (,,) xs `zap` ys `zap` zs
> 
> instance (ZipFunctor f) =>
>  Zippable (f a,f b,f c,f d) f (a,b,c,d) where
>zip (xs1,xs2,xs3,xs4) =
>fmap (,,,) xs1 `zap` xs2 `zap` xs3 `zap` xs4
>
> -- Hopefully you can see how to define instances for more tuples
>

Nothing stops us from adding `unzip` to the class as well, but I left
that out to keep it short.  Without functional dependencies, the type
system would have difficulty with type inference, and we would have to
put type declarations all over the place when using these classes.  By
the way, I should point out that these zip functions aren't used exactly
the same way as the current zip functions.  They convert a tuple of
lists into a list of tuples.  So, here's a demonstration of the
difference:

> -- here is the old zip3 function
> zip3 [1..5] "abcd" [0.0,3.14]  == [(1,'a',0.0),(2,'b',3.14)]
>
> -- and here is the new zip
> zip ([1..5],"abcd",[0.0,3,14]) == [(1,'a',0.0),(2,'b',3.14)]


Yoann Padioleau wrote:
> 
> Matt Harden <[EMAIL PROTECTED]> writes:
> >
> >zip  :: ZipFunctor f => f a -> f b -> f (a,b)
> >zip  = zipWith  (,)
> >zip3 :: ZipFunctor f => f a -> f b -> f c -> f (a,b,c)
> >zip3 = zipWith3 (,,)
> >
> > One can easily create ZipFunctor instances for trees and other data
> > structures.  I can provide examples if you like.  With multiple
> > parameter type classes (MPTCs, they are not in Haskell 98) as well as
> > functional dependencies (also not in h98), one can also create a
> > "Zippable" class to generalize the zip function over multiple tuple
> > types and eliminate zip3, zip4, etc.
> 
> can you explain how you do that ?? (i dont know what is
>  functional dependencies, but i think i understand multiple parameter type classes
>  and i dont see how do make something that avoid to define a zip3 zip4 
> 
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Question about typing

2001-04-07 Thread Matt Harden

In a lazy language like Haskell, a list is essentially the same as a
lazy stream, though I'm not well versed in the parallel stuff...

Anyway, it can be quite desirable to be able to "zip" together data
structures other than lists; trees or arrays for example.  The standard
prelude and library does not include any class to do this.  I played
with this awhile back, and came up with the following:

   module Zip where
   import Prelude hiding (zip, zipWith, zipWith3, zip3)

   class (Functor f) => ZipFunctor f where
  -- "zap" stands for "zip apply"
  -- it applies a set of functions to a set
  -- of arguments, producing a set of results
  zap :: f (a->b) -> f a -> f b

   instance ZipFunctor [] where
  (f:fs) `zap` (x:xs) = f x : fs `zap` xs
  _ `zap` _ = []

   instance ZipFunctor Maybe where
  (Just f) `zap` (Just x) = Just (f x)
  _ `zap` _ = Nothing

   zipWith  :: (ZipFunctor f) => (a->b->c) -> f a -> f b -> f c
   zipWith  f xs ys = f `fmap` xs `zap` ys

   zipWith3 :: (ZipFunctor f) => (a->b->c->d)->f a->f b->f c->f d
   zipWith3 f xs ys zs = f `fmap` xs `zap` ys `zap` zs

   zip  :: ZipFunctor f => f a -> f b -> f (a,b)
   zip  = zipWith  (,)
   zip3 :: ZipFunctor f => f a -> f b -> f c -> f (a,b,c)
   zip3 = zipWith3 (,,)

One can easily create ZipFunctor instances for trees and other data
structures.  I can provide examples if you like.  With multiple
parameter type classes (MPTCs, they are not in Haskell 98) as well as
functional dependencies (also not in h98), one can also create a
"Zippable" class to generalize the zip function over multiple tuple
types and eliminate zip3, zip4, etc.

I don't know of any way to make option 1 below equivalent to the other
two; I think it is impossible with Haskell's current type systems. 
However, you can create an "Id" type, which is a wrapper that holds
exactly one instance of another type.  Id happens to trivially be a
Functor and a Monad, is also trivially a ZipFunctor, and can be defined
as a newtype to eliminate overhead in the compiled program.  Then you
would have option 1 as follows:
   1. Adding two integers together: Id Int -> Id Int -> Id Int
The function for all three options would then be (zipWith (+)).

Hope this helps,
Matt


[EMAIL PROTECTED] wrote:
> 
> Is there a class that both lists and lazy streams could implement, so
> that zip et al could be more general?  The distinction between 2 and 3
> below seems a bit arbitrary.  Something like fmap/Functor?  (If there
> is, I guess it could apply to 1 too?; if not, why not - is it
> impractical (efficiency?) or just wrong?)
> 
> Curious,
> Andrew
> 
> On Thu, Apr 05, 2001 at 06:19:30PM +0100, Toby Watson wrote:
> > Intuitively the following scenarios seem to be related, can anyone point my
> > in the direction of formal work on this, or give me the formal terms I need
> > to search around?
> >
> > 1. Adding two integers together: Int -> Int -> Int
> >
> > 2. Adding two lists of Integers together: [Int] -> [Int] -> [Int]
> >
> > 3. Adding two lazy streams of integers together, possibly in seperate
> > (parallel) processes for example.
> >
> >
> > cheers,
> > Toby
> >
> >
> > ___
> > Haskell-Cafe mailing list
> > [EMAIL PROTECTED]
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> 
> --
> http://www.andrewcooke.free-online.co.uk/index.html
> 
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Scalable and Continuous

2001-02-17 Thread Matt Harden

Dylan Thurston wrote:
> 
> On Fri, Feb 16, 2001 at 10:21:57PM -0600, Matt Harden wrote:
> > Marcin 'Qrczak' Kowalczyk wrote:
> > > Wed, 14 Feb 2001 23:27:55 -0600, Matt Harden <[EMAIL PROTECTED]> pisze:
> > > > such defaults would only be legal if the superclass did not define
> > > > a default for the same function.
> > >
> > > Not necessarily. For example (^) in Num (of the revised Prelude)
> > > has a default definition, but Fractional gives the opportunity to
> > > have better (^) defined in terms of other methods. When a type is an
> > > instance of Fractional, it should always have the Fractional's (^)
> > > in practice. When not, Num's (^) is always appropriate.
> > What happens if classes A and B are superclasses of C, all three
> > define a default for function foo, and we have a type that's an instance
> > of A and B, but not C, which doesn't override foo?  Which default do we
> > use?  It's not only a problem for the compiler to figure out, it also
> > quickly becomes confusing to the programmer.
> 
> (Presumably you mean that A and B are subclasses of C, which contains
> foo.)  I would make this an error, easily found by the compiler.
> But I need to think more to come up with well-defined and uniform
> semantics.

No, I meant superclasses.  I was referring to the possible feature we
(Marcin and I) were discussing, which was the ability to create new
superclasses of existing classes.  If you are allowed to create
superclasses which are not referenced in the definition of the subclass,
then presumably you could create two classes A and B that contained foo
from C.  You would have to then be able to create a new subclass of both
of those classes, since C is already a subclass of both.  Then the
question becomes, if they both have a default for foo, who wins?

My contention was that the compiler should not allow a default for foo
in the superclass and the subclass because that would introduce
ambiguities.  I would now like to change my stance on that, and say that
defaults in the superclasses could be allowed, and in a class AB
subclassing both A and B, there would be no default for foo unless it
was defined in AB itself.  Also C would not inherit any default from A
or B, since it does not mention A or B in its definition.

If this feature of creating new superclasses were adopted, I would also
want a way to refer explicitly to default functions in a particular
class definition, so that one could say that foo in AB = foo from A.

BTW, I'm not saying this stuff is necessarily a good idea, just
exploring the possibility.

Matt Harden

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Scalable and Continuous

2001-02-16 Thread Matt Harden

Marcin 'Qrczak' Kowalczyk wrote:
> 
> Wed, 14 Feb 2001 23:27:55 -0600, Matt Harden <[EMAIL PROTECTED]> pisze:
> 
> > I also wonder: should one be allowed to create new superclasses of an
> > existing class without updating the original class's definition?
> 
> It would not buy anything. You could not make use of the superclass
> in default definitions anyway (because they are already written).

But that's not the point.  The point is you could create objects that
were only instances of the new superclass and not of the subclass.  It
allows us to have hidden superclasses of Num that wouldn't even have to
be referenced in the standard Prelude, for instance.  It allows users to
define (+) for a type without defining (*), by creating an  appropriate
superclass of Num.  We could keep the current Prelude while allowing
numerous "Geek Preludes" that could coexist with the std one (at least
with regard to this particular issue).

> And what would happen to types which are instances of the subclass
> but not of the new superclass?

They would automatically be instances of the new superclass.  Why not? 
They already have all the appropriate functions defined.  Again, I
wouldn't allow default definitions for the same function in multiple
classes, and this is one of the reasons.  It would introduce ambiguity
when a type that is an instance of a subclass, and didn't override the
default, was considered as an instance of the superclass.

> > Also, should the subclass be able to create new default definitions
> > for functions in the superclasses?
> 
> I hope the system can be designed such that it can.

Me too :).

> > such defaults would only be legal if the superclass did not define
> > a default for the same function.
> 
> Not necessarily. For example (^) in Num (of the revised Prelude)
> has a default definition, but Fractional gives the opportunity to
> have better (^) defined in terms of other methods. When a type is an
> instance of Fractional, it should always have the Fractional's (^)
> in practice. When not, Num's (^) is always appropriate.
> 
> I had many cases like this when trying to design a container class
> system. It's typical that a more specialized class has something
> generic as a superclass, and that a more generic function can easily
> be expressed in terms of specialized functions (but not vice versa).
> It follows that many kinds of types have the same written definition
> for a method, which cannot be put in the default definition in the
> class because it needs a more specialized context.
> 
> It would be very convenient to be able to do that, but it cannot be
> very clear design. It relies on the absence of an instance, a negative
> constraint. Hopefully it will be OK, since it's determined once for a
> type - it's not a systematic way of parametrizing code over negative
> constrained types, which would break the principle that additional
> instances are harmless to old code.

What happens if classes A and B are superclasses of C, all three
define a default for function foo, and we have a type that's an instance
of A and B, but not C, which doesn't override foo?  Which default do we
use?  It's not only a problem for the compiler to figure out, it also
quickly becomes confusing to the programmer.  I'd rather just make the
simple rule of a single default per function.  If multiple "standard"
definitions for a function make sense, then be explicit about which one
you want for each type; i.e.:

   instance Fractional MyFraction where
  (^) = fractionalPow

> This design does have some problems. For example what if there are two
> subclasses which define the default method in an incompatible ways.
> We should design the system such that adding a non-conflicting instance
> does not break previously written code. It must be resolved once per
> module, probably complaining about the ambiguity (ugh!), but once
> the instance is generated, it's cast in stone for this type.

Yeah, ugh.  I hate having opportunities for ambiguity.  Simple rules and
obvious results are far better, IMHO.

> > What do you mean by mutual definitions?
(snipped explanation of mutual definitions)

OK, that's what I thought :).  I didn't really think this was of
particular importance with allowing the definition of superclass's
instances in subclasses, but now I think I see why you said that.  It
would be easy to forget to define one of the functions if the defaults
are way up the hierarchy in one of the superclasses.

Btw, I'm one of those who agrees that omitting a definition of a class
function in an instance should be an error.  If you really intend to
omit the implementation of a function without a default, define it as
(error "Intentionally omitted")!

Matt Harden

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Scalable and Continuous

2001-02-14 Thread Matt Harden

Marcin 'Qrczak' Kowalczyk wrote:
> 
> I'm afraid of making too many small classes. But it would perhaps be not
> so bad if one could define superclass' methods in subclasses, so that one
> can forget about exact structure of classes and treat a bunch of classes
> as a single class if he wishes. It would have to be combined with
> compiler-inferred warnings about mutual definitions giving bottoms.

I totally agree with this.  We should be able to split up Num into many
superclasses, while still retaining the traditional Num, and not
inconveniencing anybody currently using Num.  We could even put the
superclasses into Library modules, so as not to "pollute" the standard
Prelude's namespace.  The Prelude could import those modules, then
define Num and Num's instances, and only export the Num stuff.

We shouldn't have to be afraid of making too many classes, if that more
precisely reflects reality.  It is only the current language definition
that makes us afraid of this.  We should be able to work with a class,
subclass it, and define instances of it, without needing to know about
all of its superclasses.  This is certainly true in OOP, although I
realize of course that OOP classes are not Haskell classes.

I also wonder: should one be allowed to create new superclasses of an
existing class without updating the original class's definition?  Also,
should the subclass be able to create new default definitions for
functions in the superclasses?  I think it should; such defaults would
only be legal if the superclass did not define a default for the same
function.

What do you mean by mutual definitions?

Matt Harden

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe