Re: Data types basics

2003-11-04 Thread Patty Fong
Another prompt reply! thanks Hal :) I think I understand this correctly now

For my previous problem which was:
 ::= ( ".")*
 :: =  | 
 ::=  ":-" ("," )*
 ::=  [“(“  (“,” )* “)”]
 ::=  |  | 
 ::= 
Does this appear to be correct:
type Prolog = [Assertion]
data Assertion = StrucAssert Structure | RuleAssert Rule
data Rule = Rule Structure Structure [Structure]
data Structure = Structure Name Term [Term]
data Term = NumTerm Number | VarTerm Variable | StrucTerm Structure
type Variable = Name
type Name = String
type Number = Int
From: Hal Daume III To: Patty Fong CC: Haskell Cafe , Hal Daume Subject: 
Re: Data types basics Date: Tue, 4 Nov 2003 22:10:03 -0800 (PST)

Hi again,

On Wed, 5 Nov 2003, Patty Fong wrote:

> Hi to anyone reading this. i'm still strugling a bit with data type > 
declarations. > > The was i understand it is that if i delcare a new data 
type: > > data myType = myType a | b | c

This isn't entirely correct. The names of types have to begin with capital 
letters, as do constructors (more later). So you would need this to be:

data MyType = MyType A | B | C

where A is an existing type.

This type now has three constructors:

MyType :: A -> MyType B :: MyType C :: MyType

It's perhaps a bit easier to understand when the names are different.

When we say:

data Foo = Bar Int | Baz String

this means that a "Foo" is of one of two forms (the "|" can be read as 
disjunction). A value of type Foo is either of the form "Bar x" for some x 
which is an Int or "Baz y" for some y which is a String.

"Bar" and "Baz" are called "constructors" because they take arguments and 
"construct" a Foo. So, in this case,

Bar :: Int -> Foo Baz :: String -> Foo

are the two constructors.

Of course, you have have any number of constructors and each can have any 
number of arguments.

data Foo = Bar | Baz Int | Bazaa String Bool

Now there are three constructors:

Bar :: Foo Baz :: Int -> Foo Bazaa :: String -> Bool -> Foo

they can be recursive:

data Foo = Bar | Baz Int Foo

Bar :: Foo Baz :: Int -> Foo -> Foo

and can have "type variables", for instance:

data Foo a = Bar | Baz a

here, something of type "Foo a" is either of the form Bar or of the form 
Baz x for some x which is of type a. This has constructors:

Bar :: Foo a Baz :: a -> Foo a

I hope this sheds some light on the issue...

--
Hal Daume III | [EMAIL PROTECTED] "Arrest this man, he talks in maths." | 
www.isi.edu/~hdaume

_
Hot chart ringtones and polyphonics. Go to  
http://ninemsn.com.au/mobilemania/default.asp

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


Re: Data types basics

2003-11-04 Thread Hal Daume III
Hi again,

On Wed, 5 Nov 2003, Patty Fong wrote:

> Hi to anyone reading this. i'm still strugling a bit with data type
> declarations.
> 
> The was i understand it is that if i delcare a new data type:
> 
> data myType = myType a | b | c

This isn't entirely correct.  The names of types have to begin with 
capital letters, as do constructors (more later).  So you would need this 
to be:

data MyType = MyType A | B | C

where A is an existing type.

This type now has three constructors:

  MyType :: A -> MyType
  B :: MyType
  C :: MyType

It's perhaps a bit easier to understand when the names are different.

When we say:

data Foo = Bar Int | Baz String

this means that a "Foo" is of one of two forms (the "|" can be read as 
disjunction).  A value of type Foo is either of the form "Bar x" for some 
x which is an Int or "Baz y" for some y which is a String.

"Bar" and "Baz" are called "constructors" because they take arguments and 
"construct" a Foo.  So, in this case,

  Bar :: Int -> Foo
  Baz :: String -> Foo

are the two constructors.

Of course, you have have any number of constructors and each can have any 
number of arguments.

data Foo = Bar | Baz Int | Bazaa String Bool

Now there are three constructors:

  Bar :: Foo
  Baz :: Int -> Foo
  Bazaa :: String -> Bool -> Foo

they can be recursive:

data Foo = Bar | Baz Int Foo

  Bar :: Foo
  Baz :: Int -> Foo -> Foo

and can have "type variables", for instance:

data Foo a = Bar | Baz a

here, something of type "Foo a" is either of the form Bar or of the form 
Baz x for some x which is of type a.  This has constructors:

  Bar :: Foo a
  Baz :: a -> Foo a

I hope this sheds some light on the issue...


-- 
 Hal Daume III   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."   | www.isi.edu/~hdaume

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


Data types basics

2003-11-04 Thread Patty Fong

Hi to anyone reading this. i'm still strugling a bit with data type declarations.
The was i understand it is that if i delcare a new data type:
data myType = myType a | b | c
The constructor is of type a -> myType. can it also be of type b -> myType, or c -> myType ?
What I am reall strugling to understand is if i declare a new data type as such
data myType = a | b | c
That a, b & c are all contructors for the new data type, but, what exactly does this mean ? what, in this case is the type of the constructor(s). And what do a, b & c have to be in this instance ? functions or ??. This all has me very confused.
not sure if i'm making sense :) ...
ANY help is much appreciated :)
Cheers,
PatrickHot chart ringtones and polyphonics.  Click here 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-04 Thread oleg

Hello!

Let me describe (my understanding of) the problem first. Let us assume
a Java-like OO language, but with multiple inheritance. Let us
consider the following hierarchy: 

Object -- the root of the hierarchy

ClassA: inherits from Object
  defines method Foo::Int -> Bool
  defines method Bar::Bool -> Int

ClassB: inherits from Object and ClassA
  overloads the inherited method Foo with Foo:: Int->Int
  overrides method Bar:: Bool -> Int

ClassC: inherits from ClassA
  -- defines no extra methods

ClassD: inherits from ClassB
  overrides method Foo::Int->Bool 
it inherited from ClassA via ClassB

ClassE: inherits from classes A, B, C, and D


We would like to define a function foo that applies to an object of
any class that implements or inherits method Foo. Likewise, we want a
function bar be applicable to an object of any class that defines or
inherits method Bar. We want the typechecker to guarantee the above
properties. Furthermore, we want the typechecker to choose the most
appropriate class that implements the desired method. That is, we want
the typechecker to resolve overloading and overriding in
multiple-inheritance hierarchies. The resolution depends not only on
the name of the method but also on the type of its arguments _and_ the
result.

That is, we aim higher than most languages that command the most of
the job postings.

The code below is a trivial modification to the code Brandon Michael Moore
posted the other month.

> {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances 
> -fallow-overlapping-instances #-}
> import Debug.Trace

marker types for the classes

> data Object = Object
> data ClassA = ClassA
> data ClassB = ClassB
> data ClassC = ClassC
> data ClassD = ClassD
> data ClassE = ClassE
>
> instance Show Object where { show _ = "Object" }
> instance Show ClassA where { show _ = "ClassA" }
> instance Show ClassB where { show _ = "ClassB" }
> instance Show ClassC where { show _ = "ClassC" }
> instance Show ClassD where { show _ = "ClassD" }
> instance Show ClassE where { show _ = "ClassE" }

marker types for the methods

> data Foo arg result = Foo
> data Bar arg result = Bar

Let us encode the class hierarchy by a straightforward translation of
the above class diagram. For each class, we specify the list of its
_immediate_ parents.

> class Interface super sub | sub -> super
> instance Interface () Object
> instance Interface (Object,()) ClassA
> instance Interface (Object,(ClassA,())) ClassB
> instance Interface (ClassA,()) ClassC
> instance Interface (ClassB,()) ClassD
> instance Interface (ClassD, (ClassA,(ClassB,(ClassC,() ClassE

Let us now describe the methods defined by each class. A method
is specified by its full signature: Foo Int Bool is to be read as
Foo:: Int -> Bool.

> class Methods cls methods | cls -> methods
> instance Methods Object ()
>
> instance Methods ClassA (Foo Int Bool, (Bar Bool Int, ()))
> instance Methods ClassB (Foo Int Int,  (Bar Bool Int,()))
> instance Methods ClassC ()  -- adds no new methods
> instance Methods ClassD (Foo Int Bool,())
> instance Methods ClassE ()  -- adds no new methods


The following is the basic machinery. It builds (figuratively
speaking) the full transitive closure of Interface and Method
relations and resolves the resolution. The tests are at the very end.

First we define two "mutually recursive" classes that do the
resolution of the overloading and overriding.
By "mutually recursive" we mean that the typechecker must mutually
recurse. A poor thing...

Methods mtrace_om and mtrace_ahm will eventually tell the result
of the resolution: the name of the concrete class that defines or
overrides a particular signature.

> class AHM objs method where
>   mtrace_ahm:: objs -> method -> String
> 
> class OM methods objs obj method where
>   mtrace_om:: methods -> objs -> obj -> method -> String
>
> instance (Methods c methods, Interface super c, 
>   OM methods (super,cs) c method) 
>  => AHM (c,cs) method where
> mtrace_ahm _ = 
>mtrace_om (undefined::methods) (undefined::(super,cs))
>  (undefined::c)
>   
> instance (AHM cls t) => AHM ((),cls) t where
> mtrace_ahm _ = mtrace_ahm (undefined::cls)
>
> instance (Show c) => OM (method,x) objs c method where
> mtrace_om _ _ c _ = show c
>
> instance (OM rest objs c method) => OM (x,rest) objs c method where
> mtrace_om _ = mtrace_om (undefined::rest)
>   
> instance (AHM objs method) => OM () objs c method where
> mtrace_om _ _ _ = mtrace_ahm (undefined::objs)
>
> instance (AHM (a,(b,cls)) t) => AHM ((a,b),cls) t where
> mtrace_ahm _ = mtrace_ahm (undefined::(a,(b,cls)))

Now we can express the constraint that a class inherits a method

> class HasMethod method obj args result where
>   call  :: method args result -> obj -> args -> result
>   mtrace:: method args result -> obj -> String
>  
> in

RE: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-04 Thread Brandon Michael Moore
On Tue, 4 Nov 2003, Simon Peyton-Jones wrote:

>
> | We really should change GHC rather than keep trying to work around
> stuff
> | like this. GHC will be my light reading for winter break.
>
> Maybe so.  For the benefit of those of us who have not followed the
> details of your work, could you summarise, as precisely as possible,
> just what language extension you propose, and how it would be useful?  A
> kind of free-standing summary, not assuming the reader has already read
> the earlier messages.
>
> Simon

There are two extensions here:

More overlapping:
Allow any overlapping rules, and apply the most specific rule that
matches our target. Only complain if there is a pair of matching
rules neither of which is more specific than the other.

This follow the spirit of the treatment of duplicate imports, and
lets you do more interesting computations with type classes.
For example, the sort of type class hack Oleg and I have been writing much
easier. You use nested tuples to hold a list of values your search
is working over, have a rule that expands the head to a list of
subgoals, a rule that flattens lists with a head of that form,
and an axiom that stops the search if the head has a different
form, without needing the stop form to unify with a pair.

This extension would accept the code I just posted, and seems pretty
conservative.

Backtracking search:
If several rules matched your target, and the one you picked didn't
work, go back and try another.

This isn't as well through out: you probably want to backtrack through all
the matching rules even if some are unordered by being more specific. It
would probably be godd enough to respect specificity, and make other
choices arbitrarilily (line number, filename, etc. maybe Prolog has a
solution?). This probably isn't too hard if you can just add
nondeterminism to the monad the code already lives in.

This would give you OR. The example Integral a => MyClass a,
Fractional a => MyClass a would work just fine and give you a class that
is the union of integral and fractional. This class hierarchy search
could be done by a SubClass class that had an instance linking a class
to each of it's different parents, then the search just needs to backtrack
on which parent to look at:

class SubClass super sub

instance SubClass A C
instance SubClass B C

class HasFoo cls
  foo :: cls -> Int
instance (SubClass super sub,HasFoo super) => HasFoo sub
instance HasFoo B

now look for an instance of HasFoo D
  uses first rule for HasFoo,.
  Needs an instance SubClass x D. Tries A, but can't derive HasFoo A.
  GHC backtracks to trying B as the parent, where it can
  use the second instance for HasFoo and finish the derivation.

Overloading resolution:
This one is really half-baked, but sometimes it would be nice if there was
some way to look at

class MyNumber a where
  one::a
instance MyNumber Int where
  one = 1

then see (one+1) and deduce that the 1 must have type Int, rather than
complaining about being unable to deduce MyNumber a from Num a. This is
really nice for some cases, like a lifting class I wrote for an Unlambda
interpreter, with instances for LiftsToComb Comb and (LiftsToComb a =>
LiftsToComb (a -> Comb)). With some closed world reasoning lift id and
lift const might give you I and K rather than a type error. Also, for
this work with modelling inheritance you almost always have to give type
signatures on numbers so you find the method that takes an Int, rather
than not finding anything that takes any a with Num a. This obviously
breaks down if you have instances for Int and Integer, and I don't yet
know if it is worth the trouble for the benefits in the cases where it
would help. Implementation is also a bit tricky. I think it requires
unifying from both sides when deciding if a rule matches a goal.

Improvements and better suggestions welcome. I'm only particularly
attached to the first idea.

Brandon

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


AW: AW: Heap profiling in GHC broken?

2003-11-04 Thread Markus . Schnell
> The canonical tutorial paper is in the Advanced Functional Programming
> Summer Schools series:
> 
> C. Runciman and N. Ro"jemo. Heap profiling for space efficiency.
> In J. Launchbury, E. Meijer, and T. Sheard, editors, 2nd 
> Intl. School
> on Advanced Functional Programming, pages 159-183, Olympia, WA,
> August 1996. Springer LNCS Vol. 1129.

Great! I knew only the more compiler-oriented Runciman/Röjemo papers.
(Which were already helpful, but not very 'tutorial'.)


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


Re: AW: Heap profiling in GHC broken?

2003-11-04 Thread Malcolm Wallace
> > A tutorial on this by one of the experts would be very welcome.
> 
> The people at York University have written some great papers on this topic. 

The canonical tutorial paper is in the Advanced Functional Programming
Summer Schools series:

C. Runciman and N. Ro"jemo. Heap profiling for space efficiency.
In J. Launchbury, E. Meijer, and T. Sheard, editors, 2nd Intl. School
on Advanced Functional Programming, pages 159-183, Olympia, WA,
August 1996. Springer LNCS Vol. 1129.

Other relevant papers can be found amongst those listed for the York
programming languages group at:
http://www.cs.york.ac.uk/plasma/publications/

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


Re: AW: Heap profiling in GHC broken?

2003-11-04 Thread Alastair Reid

> A tutorial on this by one of the experts would be very welcome.

The people at York University have written some great papers on this topic.  I 
especially remember one presented at the Glasgow Functional Programming 
workshop by Colin Runciman about 8-10 years ago.  In the draft proceedings or 
the presentation, the title was something to do with the tail and the leg of 
the dog but I don't recall the title of the final paper.

--
Alastair Reid

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


AW: Heap profiling in GHC broken?

2003-11-04 Thread Markus . Schnell
I have no idea how to set up cvs under windows to get things 
from a non-local repository, but anyway, profiling worked on 
the macintosh.

I spent the whole weekend plus monday to find the space leak,
but eventually I did. 
Heap Profiling was very helpful there.

Unfortunately, space leaks are barely mentioned in the Haskell
books/tutorials, but they are a real burden if you want to run 
programs for larger problems.

A tutorial on this by one of the experts would be very welcome.
:-)

Thanks,
Markus

> -Ursprüngliche Nachricht-
> Von: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] Im Auftrag von David Roundy
> Gesendet: Donnerstag, 30. Oktober 2003 13:48
> An: [EMAIL PROTECTED]
> Betreff: Re: Heap profiling in GHC broken?
> 
> 
> On Wed, Oct 29, 2003 at 05:43:23PM +0100, 
> [EMAIL PROTECTED] wrote:
> > When I tried to profile my program in search for space leaks,
> > it core dumped on me (actually on Win2000/Cygwin). I'm 
> using ghc 6.0.1. 
> > Does anybody know what could be the problem?
> > 
> > (To be more precise: any +RTS -h_ options make problems, 
> +RTS -p works
> > fine.  I get a message meaning the equivalent of "statement in
> > '0x0058db43' points to memory in '0xfffc'. Could not read.")
> 
> I believe this bug is fixed in CVS, so you could get it there 
> or wait for
> 6.2.  (I didn't fix it, I just reported it.)
> -- 
> David Roundy
> http://www.abridgegame.org/darcs
> ___
> 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: Data representation, maybe reflection, laziness

2003-11-04 Thread Frank Atanassow
On dinsdag, nov 4, 2003, at 00:39 Europe/Amsterdam, Frank Atanassow 
wrote:

For example,  our translator takes the Schema type doc (representing a 
bibliographic entry) ... to a certain ugly datatype X.
Oops. For "X" I should have written E_doc, that is, the translation of 
Schema type "doc" is named "E_doc" ("E" is for Element); it's used in 
the example at the end.

< main= interact work
< toE_doc = unparse{|E_doc|} . expand{|E_doc|} . reduce{|Doc|}
< toDoc   = expand{|Doc|} . reduce{|E_doc|} . parse{|E_doc|}
< work= toE_doc . (\d -> d { authors = filter (/= "Dubya") (authors 
d) }) . toDoc

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


Re: Data representation, maybe reflection, laziness

2003-11-04 Thread Frank Atanassow
On vrijdag, okt 31, 2003, at 21:06 Europe/Amsterdam, Mark Carroll wrote:
Ralf Hinze and Simon Peyton-Jones wrote an interesting paper on generic
programming and derivable type classes. It looked like maybe 
programmers
would be able to write their own "deriving xml" stuff and whatever, 
which
looked great because, if there's not already one out there, I'd love to
derive some read/show analogue automatically for data in some encoding
that's very efficient to write and parse (i.e. not XML (-:).
Johan Jeuring and I submitted a paper [1] to PLAN-X concerning this 
topic. In an earlier paper [2] we described a Haskell-XML data binding, 
that is, a type-safe translation scheme from (a sizeable subset of) XML 
Schema to Haskell. In [1] we describe a Generic Haskell program which 
automatically infers certain coercions between the translation of an 
XML Schema type, which is very large and ugly, and user-defined Haskell 
datatype capable of representing values of the Schema type. The idea is 
to infer the function that transforms values of the ugly type picked by 
the translator to values of a traditional, Haskellish datatype picked 
by the user.

For example,  our translator takes the Schema type doc (representing a 
bibliographic entry):


   
  



  
  




  


  




to a certain ugly datatype X. [2] defines generic functions:

  parse{|t|} :: String -> Maybe t
  unparse{|t|} :: t -> Maybe String
(Well, we only describe parse, but unparse is very easy...)

Now say the user defines the following datatype in some module:

> data Doc = Doc
>   { key  :: String,
> authors  :: [String],
> title:: String,
> pubDate  :: Maybe PubDate }
>
> data PubDate= PubDate
>   { year :: Integer,
> month:: Integer }
This is, IMO, the `ideal' translation of the Schema type. Now, although 
X /= Doc, there is in fact a `canonical' injection X -> Doc, determined 
by the types alone, which happens to do what one wants.

In [1] we define generic functions:

  reduce{|t|} :: t -> Univ
  expand{|t|} :: Univ -> t
where Univ is a universal type which you don't need to know anything 
about. The program

> expand{|T|} . reduce{|S|} :: S -> T

denotes the canonical function, which is inferred generically by 
inspecting the types S and T, relieving the user of the burden of 
writing it out themselves.

So now, say you want to write a GH program which reads in a document 
conforming
to the Schema type `doc' from standard input, deletes all authors named 
"Dubya", and writes the result to standard output. Here it is:

< main= interact work
< toE_doc = unparse{|E_doc|} . expand{|E_doc|} .
<   reduce{|Doc|}
< toDoc   = expand{|Doc|} . reduce{|E_doc|} .
<   parse{|E_doc|}
< work= toE_doc .
<   (\d -> d { authors =
<  filter (/= "Dubya") (authors d) }) .
<   toDoc
And that's it. All the messy stuff is inferred by GH and the translator.

OK, now the reason that I prepended this message with "FWIW": although 
we have an implementation of the translator and coercion inferencer, 
they're only prototypes and far from usable in practice. In fact, the 
translator doesn't read XML at all but rather operates on XML abstract 
syntax (a tree datatype).

Frankly, I don't think I will take the time to turn the prototype into 
anything releasable, but I wouldn't mind turning over the sources (such 
as they are :) to someone who has a serious interest. Take a look at 
the papers and see if it appeals to you.

Regards,
Frank
[1] @TechReport{ACJ03c,
  author =   {Atanassow, Frank and Clarke, Dave and Jeuring, Johan},
  title ={Scripting {XML} with {G}eneric {H}askell},
  institution =  {Utrecht University},
  year = {2003},
  url = {ftp://ftp.cs.uu.nl/pub/RUU/CS/techreps/CS-2003/2003-023.pdf},
  number =   "UU-CS-2003"
}
[2] @misc{AJ03,
  author  = {Frank Atanassow and Johan Jeuring},
  title   = {Type isomorphisms simplify {XML} programming},
  year= 2003,
  note= {Submitted to PLAN-X 2004},
  url = {http://www.cs.uu.nl/~franka/pub},
  urlpdf  = {http://www.cs.uu.nl/~franka/planx04.pdf},
  pubcat  = {journal},
}
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-04 Thread Simon Peyton-Jones

| We really should change GHC rather than keep trying to work around
stuff
| like this. GHC will be my light reading for winter break.

Maybe so.  For the benefit of those of us who have not followed the
details of your work, could you summarise, as precisely as possible,
just what language extension you propose, and how it would be useful?  A
kind of free-standing summary, not assuming the reader has already read
the earlier messages.

Simon

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