[Haskell-cafe] Re: GADTs and Scrap your Boilerplate

2010-05-18 Thread John Creighton


On May 18, 11:57 am, Oscar Finnsson oscar.finns...@gmail.com wrote:
  forall d.   gunfold k z c = k (z (DataBox::d-DataBox d))

 Didn't work either. :(

I looked again at the paper (page 27):
Haskell's Overlooked object system.
http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf

I think the forall is suppose to be in the constructor (as opposed to
where I put it) and I don't think you need algebraic datatypes.

data DataBox = forall d. (Show d, Eq d, Data d) = DataBox d

I am not sure if this requires any extensions. Try it with and without
the extension explcit forall

You can also try this with a class called MakeDataBox and make d an
instance of make data box.

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


[Haskell-cafe] Re: What makes Haskell difficult as .NET?

2010-05-15 Thread John Creighton
 IIRC .Net interfaces cannot be added outside assembly (I may be wrong).
 On the other hand Haskell does not have inheritance.

 Generally
         Haskell: newtype/data specify data (and type) while classes provides
 basic abstract operations on it.
         C#/Java/...: Classes specify data AND how to operate on it (including
 non-basic operators) and interfaces abstract operations.

 - It is not that it can occur once:

 class Abc x where
         abc :: x - [x]

 is roughly:

 interface Abcin T {
         public IListT abc();

 }

 - It seems that it is not possible to have default implementations in
 interfaces.

To understand the extend haskell supports object oriented behavior
such as inheritance it is worth reading:
http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf

Perhaps, I should start a new discussion on this.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] What Object Oriented Paradigms Does Haskell Support?

2010-05-15 Thread John Creighton
In response to the discussion

What makes Haskell difficult as .NET?
http://groups.google.ca/group/haskell-cafe/browse_thread/thread/f61ee38f2082dcbe?hl=en#

I thought I'd start a discussion on what object oriented features
Haskell supports.

A good reference is:
Haskell's Overlooked Object System
http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf

The comparison is often made of Haskell's classes to interface.
However, once we define an instance we have something concrete which
is closer to a class under the object oriented paradigm. If our
instances are paramatric:

MyType a = MyType{...child::a}

Then when we can create subclass instances which are sybtypes of our
Paramatric type. This gives us inheritance. Overriding might be
slightly trickier. We can certainly create new instances of the parent
class for a specific subtype. As a minimum we will need to specify
each method we created which is not defined in terms of the others
(our getters and setters) and perhaps we are allowed to over ride the
methods which are derived from the other methods. Anyway, I'll do some
re reading of the paper, experiment with some code and see what other
options there are.

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


[Haskell-cafe] Re: GADTs and Scrap your Boilerplate

2010-05-15 Thread John Creighton


On May 15, 2:19 pm, Oscar Finnsson oscar.finns...@gmail.com wrote:
 Hi,

 I'm writing a XML (de)serializer using Text.XML.Light and Scrap your
 Boilerplate (a thttp://github.com/finnsson/Text.XML.Generic) and so
 far I got working code for normal ADTs but I'm stuck at
 deserializing GADTs.

 I got the GADT

 data DataBox where
   DataBox :: (Show d, Eq d, Data d) = d - DataBox

 and I'm trying to get this to compile

 instance Data DataBox where
   gfoldl k z (DataBox d) = z DataBox `k` d
   gunfold k z c = k (z DataBox)  -- not OK
   toConstr (DataBox d) = toConstr d
   dataTypeOf (DataBox d) = dataTypeOf d

 but I can't figure out how to implement gunfold for DataBox.

 The error message is

 Text/XML/Generic.hs:274:23:
     Ambiguous type variable `b' in the constraints:
       `Eq b'
         arising from a use of `DataBox' at Text/XML/Generic.hs:274:23-29
       `Show b'
         arising from a use of `DataBox' at Text/XML/Generic.hs:274:23-29
       `Data b' arising from a use of `k' at Text/XML/Generic.hs:274:18-30
     Probable fix: add a type signature that fixes these type variable(s)
 It's complaining about not being able to figure out the data type of b.
Not sure if this would work but you could try something like

forall d.   gunfold k z c = k (z (DataBox::d-DataBox d))  -- not OK

but what isn't working for you is the compiler needs to know what type
of Databox to construct.
Also why isn't the paramater c used? Anyway I'll look up what these
functions are suppose to do
and maybe I can offer further help.

As for type casting you might want to look up Typeable:
http://www.haskell.org/ghc/docs/6.12.1/html/libraries/base/Data-Typeable.html

 I'm also trying to implement dataCast1 and dataCast2 but I think I can
 live without them (i.e. an incorrect implementation).

 I guess my questions are:

 1. Is it possible to combine GADTs with Scrap your Boilerplate?
 2. If so: how do you implement gunfold for a GADT?

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

 --
 You received this message because you are subscribed to the Google Groups 
 Haskell-cafe group.
 To post to this group, send email to haskell-c...@googlegroups.com.
 To unsubscribe from this group, send email to 
 haskell-cafe+unsubscr...@googlegroups.com.
 For more options, visit this group 
 athttp://groups.google.com/group/haskell-cafe?hl=en.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Set Operations In Haskell's Type System

2010-05-09 Thread John Creighton


On May 9, 4:46 am, wren ng thornton w...@freegeek.org wrote:
 John Creighton wrote:
  On May 6, 4:30 am, Bartek Ćwikłowski paczesi...@gmail.com wrote:
  2010/5/6 John Creighton johns2...@gmail.com:

  a isa d if their exists a b and c such that the following
  conditions hold:
  a isa subset of b,
  b isa c
  c is a subset of d
  This definition doesn't make sense - it's recursive, but there's no
  base case, unless this is some kind of co-recursion.

  Are you sure that subset isn't what you really want? With subset you
  can already ask questions such as is tabby cat an animal?. If so, my
  code (from hpaste) already has this (iirc isDescendentOf ).

  When I succeed in implementing it I'll show you the result. Anyway,
  some perspective (perhaps), I once asked, what is the difference
  between a subset and an element of a set:

 http://www.n-n-a.com/science/about33342-0-asc-0.html

 And it's truly an interesting question. Too bad it didn't get a better
 discussion going (from what I read of it). Though the link Peter_Smith
 posted looks interesting.

  note 1) Okay I'm aware some will argue my definitions here and if it
  helps I could choose new words, the only question really is, is the
  relationship isa which I described a useful abstraction.

 I think the key issue comes down to what you want to do with it. I'm not
 entirely sure what the intended reading is for isa subset of, but I'll
 assume you mean the same as is a subset of[1]. One apparent side
 effect of the definition above is that it collapses the hierarchy.

 That is, with traditional predicates for testing element and subset
 membership, we really do construct a hierarchy. If A `elem` B and B
 `elem` C, it does not follow that A `elem` C (and similar examples). But
 with your definition it seems like there isn't that sort of
 stratification going on. If the requirements are A `subset` B, B `elem`
 C, and C `subset` D--- well we can set C=D, and now: A `elem` D = A
 `subset` B  B `elem` D.

 Depending on the ontology you're trying to construct, that may be
 perfectly fine, but it's certainly a nonstandard definition for elements
 and subsets. I don't know if this mathematical object has been worked on
 before, but it's not a hierarchy of sets.

 [1] My other, equivalent, guess would be you mean A isa (powerset B)
 but avoided that notation because it looks strange.

 --
 Live well,
 ~wren
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

 --
 You received this message because you are subscribed to the Google Groups 
 Haskell-cafe group.
 To post to this group, send email to haskell-c...@googlegroups.com.
 To unsubscribe from this group, send email to 
 haskell-cafe+unsubscr...@googlegroups.com.
 For more options, visit this group 
 athttp://groups.google.com/group/haskell-cafe?hl=en.

Keep in mind that my recent definition of is a

  a isa d if their exists a b and c such that the following
  conditions hold:
  a isa subset of b,
  b isa c
  c is a subset of d

is distinct from the question I asked a long time ago of the
difference between a set and an element. The question I asked a long
time ago is largely philosophical but can have axiomatic consequences
in set theory. Ignoring the philosophical meanings behind a set, both
the operations of subset and element of, define a partial order. The
subset relationship seems to define things that are more similar then
the element of relationship.

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


[Haskell-cafe] Re: Set Operations In Haskell's Type System

2010-05-07 Thread John Creighton


On May 6, 4:30 am, Bartek Ćwikłowski paczesi...@gmail.com wrote:
 hello,

 2010/5/6 John Creighton johns2...@gmail.com:

  a isa d if their exists a b and c such that the following
  conditions hold:

  a isa subset of b,
  b isa c
  c is a subset of d

 This definition doesn't make sense - it's recursive, but there's no
 base case, unless this is some kind of co-recursion.

 Are you sure that subset isn't what you really want? With subset you
 can already ask questions such as is tabby cat an animal?. If so, my
 code (from hpaste) already has this (iirc isDescendentOf ).

When I succeed in implementing it I'll show you the result. Anyway,
some perspective (perhaps), I once asked, what is the difference
between a subset and an element of a set:

http://www.n-n-a.com/science/about33342-0-asc-0.html

It sounds like a strange question but is a cat a subset of noun? Cat
is relay just a word or a label, we could be referring to the word
Cat, The set of all Cats or a particular cat. If by Nouns we mean
physical things then the set of cats is a subset of the set of things
that are nouns. However, if by noun we mean a type of word, then cat
is not a type or word but noun is a type of word. From the perspective
of programing the latter observation seems more useful. It involves
some context in that we wish to treat word types and instances of
those word types differently rather then trying to fit them into some
homogeneous hierarchy.

For instance if we are building grammar parsing rules then we probably
only care what type or word or phrase something is and any
hierarchical relationship beyond that are not relevant to the context
of parsing. Now if our goal is only to parse then perhaps their is a
better approach but object oriented programing has shown how subclass
polymorphism adds some level of abstraction and helps to make code
more generic. Haskel's type system allows for even more generic
approaches.

To summarize, I have chosen to define isa as a relationship between
hierarchies, while subset/superset are our standard heiercrical view
of the world (e.g. animal kingdom). Now with regards to my definition,
let's go further. Let's create an equivalence between a noun phrase of
length one and a Noun.

http://en.wikipedia.org/wiki/Noun_phrase

while we may wish to view the noun as primitive, with regards to
meaning the phrase narrows the scope of the noun.

For instance big cat, means that cat can no longer refer to all cats
but the cats must be big.

Now if we want to know if big cat is a noun, it is enough to know
that, big cat is a subset of cat, cat is a common noun, and common
noun is a subset of noun. (I'm aware some may object to big cat being
a noun but big cat is a thing and a noun is a thing).


This keeps us from directly having to program a direct relationship
between big cat and noun. One of the goals of AI is to minimize what
we have to tell our system in order to solve a problem. This is
referred to as the A to I ratio. Generic programing has this
characteristic in that our code is widely applicable. The isa rule
above makes code more generic in that we are now able to write
functions four nouns which will apply to say big cat with out even
having to tell our program that big cat is a noun, rather it can
directly infer it from the rules we supplied.

--
note 1) Okay I'm aware some will argue my definitions here and if it
helps I could choose new words, the only question really is, is the
relationship isa which I described a useful abstraction. I think it is
and weather it is or not would of course depend on if it reduces the
amount of code that needs to be written and it produces the correct
results. We could create other relationships which embody what other
people think a useful isa function should do and they could be used
either in parallel with my relationship or with a completely different
approach. I cannot say weather such alternative relationships will be
more or less useful.

note2 ) For the purpose of the above I guess we can define Noun to be
a noun phrase of length one (we can choose a different word if someone
prefers to call this instead of a noun.),

note 3) Anyway, with regards to the above I am using subset with
regards to scope (the number of _ something can refer to) and isa
with regards to type of scope. So noun says the scope refers to a
person place or thing and then, the noun (or noun phrase) limits the
scope of these things that the phrase/noun can refer to. This is
perhaps not the standard English/linguistic usage and I am sure their
are many reasonable objections to the above on semantic grounds. I am
not interested in a debate on semantics but will listen to suggestions
for alternative terms/definitions.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Set Operations In Haskell's Type System

2010-05-05 Thread John Creighton


On May 4, 9:46 am, Bartek Ćwikłowski paczesi...@gmail.com wrote:
 hello,

 2010/5/4 John Creighton johns2...@gmail.com:

  I will continue to try to solve the problem on my own but at the
  moment I'm able to get IsSuperSet to work but not the classes Isa,
  Child and IsSubSet to work. Unlike set theory IsSubSet is not the same
  as switching the order arguments in IsSuperSet because the searching
  is done in the opposite direction. In one case we are searching the
  parents and each child only has one parent. In the other Case we are
  searching the children and each parent could have multiple children).

 Since Subset is the opposite of Superset, you can search in the
 easier (up) direction, so it really is as easy as reversing the
 order of arguments.

 It's not possible to write class/type-level function Child a b | a -
 b, because functions (classes with fun-deps) must be deterministic. If
 you want to enumerate all children (based on Parent class instances),
 it's also impossible in this setup,

That's the approach I finally ended up taking. It seems to work so far
but I haven't tried using my child
function to build a subset or an isa function. My code is rather ugly
but it's the best I came up with. The
following are examples of the enumerations:


instance Parrent' () d Z Cat Feline --
instance Parrent' () d Z Feline Animal --

Z: means the first child
S Z: would be the second child instance
d is a type variable letting the relationship be bidirectional:
() is a dumby argument which is used in the case where their is no
instance.

It is used as follows:

instance (Parrent'' q d z anyChild anyParrent)=Parrent' q d z
anyChild anyParrent

instance (ItsAnOrphan ~ anyParrent)=Parrent'' q P1 n anyChild
anyParrent
instance (HasNoChildern ~ anyChild)=Parrent'' q N1 Z anyChild
anyParrent
instance (HasNoMoreChildern ~ anyChild)=Parrent'' q N1 (S n) anyChild
anyParrent

N1 is short for S Z
P1 is short for P Z (Negative numbers, P stands for previous)

 it's probably possible with Oleg's
 second-order typeclass programming[1].

 [1]http://okmij.org/ftp/Haskell/types.html#poly2


 But what are you actually trying to achieve? I can't thing of anything
 useful that would require walking down the hierarchy tree (and
 backtracking) and it has to be done at the type level.


Well, I need it for my Isa relationship defined so that

a isa d if their exists a b and c such that the following
conditions hold:

a isa subset of b,
b isa c
c is a subset of d

Thus we know d, but we need to search backwards to find c.

Anyway, I don't have the code for isa or subset yet but here is my
code for child (some more testing warranted):
Any hints on making it cleaner or more readable would be appreciated.

-

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

{-# LANGUAGE TypeOperators #-} --10
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeSynonymInstances #-}
u=undefined
bla = child Z Animal
bla2 = child (u::P1) Animal
bla3 = child (u::Z) Cat
bla4 = child (u::P1) Cat
bla5 = parrent Cat
bla6 = parrent Feline
bla7 = parrent Animal
--20
---Instance SubType Relations

data ItsAnOrphan = ItsAnOrphan
instance (Show ItsAnOrphan) where show _ = ItsAnOrphan

data HasNoMoreChildern = HasNoMoreChildern
instance (Show HasNoMoreChildern) where show _ = HasNoMoreChildern

data HasNoChildern = HasNoChildern
instance (Show HasNoChildern) where show _ = HasNoChildern


--30
class Parrent' () P1 Z a b =Parrent a b| a-b where -- Specific Cases
parrent :: a-b --
instance Parrent' () P1 Z a b = Parrent a b where
parrent _ = undefined::b
class Parrent' q d n a b | q d n a- b, q d n b -a
class Parrent'' q d n a b | q d n a - b,q d n b - a
--class Parrent''' q n a b | q n b - a

instance Parrent' () d Z Cat Feline --
instance Parrent' () d Z Feline Animal --
instance (Parrent'' q d z anyChild anyParrent)=Parrent' q d z
anyChild anyParrent

instance (ItsAnOrphan ~ anyParrent)=Parrent'' q P1 n anyChild
anyParrent
instance (HasNoChildern ~ anyChild)=Parrent'' q N1 Z anyChild
anyParrent
instance (HasNoMoreChildern ~ anyChild)=Parrent'' q N1 (S n) anyChild
anyParrent




class Child n a b|n a-b  where  -- a2 is the parrent of b
   child :: n-a-b
   child _ _ = undefined::b
instance (
 Parrent' () N1 n b2 a,
 Child' b2 n a b --b2==b or b2=HasNoChildern or
b2==HasNoMoreChildern
 )=
 Child n a b
class Child' b2 n a b | b2 n a - b --a2==a or a2=HasNoChildern or
a2==HasNoMoreChildern
class Child'' q b2 n a b|q b2 n a b -b
class Child''' q b2 n a b|q b2 n a b -b

instance Child' HasNoChildern Z a HasNoChildern
instance Child' HasNoMoreChildern (S n) a HasNoMoreChildern

[Haskell-cafe] forall (What does it do)

2010-05-05 Thread John Creighton
I've seen forall used in a few places related to Haskell. I know their
is a type extension call explicit forall but by the way it is
documnted in some places, the documentation makes it sound like it
does nothing usefull.

However on Page 27 of Haskell's overlooked object system:


We define an existential envelope for shape data.
data OpaqueShape = forall x. Shape x = HideShape x
“Opaque shapes are (still) shapes.” Hence, a Shape instance:
nstance Shape OpaqueShape
where
   readShape f (HideShape x) = readShape f x
   writeShape f (HideShape x) = HideShape $ writeShape f x
   draw (HideShape x) = draw x
When building the scribble list, we place shapes in the envelope.
let scribble = [ HideShape (rectangle 10 20 5 6)
, HideShape (circle 15 25 8)


It seems that forall can be used as a form of up casting. That is if
we have a parametric type we can treat the parametric types as
homogeneous:

The paper did not seem to regard this feature too highly:

By contrast, the explicit constraint for the existential envelope cannot be 
eliminated.
Admittedly, the loss of type inference is a nuance in this specific example. In
general, however, this weakness of existentials is quite annoying. It is 
intellectually
dissatisfying since type inference is one of the added values of an (extended) 
Hindley/
Milner type system, when compared to mainstream OO languages. Worse than
that, the kind of constraints in the example are not necessary in mainstream OO
languages (without type inference), because these constraints deal with 
subtyping,
which is normally implicit.
We do not use existentials in OOHaskell
http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf

but can't we just use the read shape function above if we want to be
able to infer based on types. I understand that haskers tend to like
things well typed but surely their are times when we would like to be
able to flatten the type of our data somewhat.

On another note, I also wonder how forall relates to type families. I
know their are certain restrictions on where we can use type families
in haskell. I wonder if we can get around these somewhat using forall.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Set Operations In Haskell's Type System

2010-05-04 Thread John Creighton
This is partly a continuation from:

http://groups.google.ca/group/haskell-cafe/browse_thread/thread/4ee2ca1f5eb88e7a?hl=en#
and
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=25265

Also of relevance:
http://groups.google.ca/group/haskell-cafe/browse_thread/thread/9cc8858a2e51a995?hl=en#
http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap
http://homepages.cwi.nl/~ralf/HList/paper.pdf
http://okmij.org/ftp/Haskell/typecast.html
http://www.haskell.org/haskellwiki/User:ConradParker/InstantInsanity
http://okmij.org/ftp/Haskell/types.html (haven't looked at this link
yet)

I will continue to try to solve the problem on my own but at the
moment I'm able to get IsSuperSet to work but not the classes Isa,
Child and IsSubSet to work. Unlike set theory IsSubSet is not the same
as switching the order arguments in IsSuperSet because the searching
is done in the opposite direction. In one case we are searching the
parents and each child only has one parent. In the other Case we are
searching the children and each parent could have multiple children).

Bellow is my current code:

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

{-# LANGUAGE TypeOperators #-} --10
{-# LANGUAGE FlexibleContexts #-}
--{-# LANGUAGE IncoherentInstances #-}
--IsSubSet ---
data ItsNotAParrent
class IsSubSet a b c | a b - c where -- General Definition
isSubSet :: a-b-c
class Child a b|b-a where {}

instance (
  Parrent b a2,
  TypeEq a2 a itsAParrent, --
  Child' itsAParrent a b
  ) = Child a b
class Child' itsAParrent a b where {}
instance (TypeCast b ItsNotAParrent)=Child' F a b --No Childern
instance (TypeCast b c, Parrent c b)=Child' T a b
instance (TypeCast b M)=Child' itsAParrent a b --- Fail Case


instance (
   TypeEq ItsNotAParrent a itsNotAParrent,
   TypeEq a b iseq,
   IsSubSet' itsNotAParrent iseq a b c3 --
 ) =
 IsSubSet a b c3 where --
 isSubSet a b = undefined::c3


class IsSubSet' itsNotAParrent iseq a b c| itsNotAParrent iseq a b -
c where {}

instance (TypeCast c T)=IsSubSet' F T a b c where {}
instance (TypeCast c F)=IsSubSet' T iseq a b c where {} --Not sure
which logic value is best for this case.
instance (TypeCast c M)=IsSubSet' itsNotAParrent iseq a b c where {}
--Fail Case

instance (
  Child a d,
  IsSubSet d b c
 )=
 IsSubSet' F F a b c where {}
--bla11=isSubSet Cat Animal

---Isa
-
class Isa' a b c|a b-c where {} --Direct Relationship
class Isa a b c|a b-c where
   isa::a-b-c
instance (
  Isa' a1 b1 c1,  --Direct Relationship
  IsSuperSet a1 a c2, --Check --20
  IsSuperSet b b1 c3, --
  Isa'' c1 c2 c3 a1 b1 c4 -- Decesion function --
 )=Isa a b c4 where
 isa a b = undefined::c4

class Isa'' c1 c2 c3 a b c4|c1 c2 c3 a b-c4 where {}
--   isa :: c1-c2-c3-a-b-c4

instance Isa'' T T T a1 b1 T where {}
--   isa'' c1 c2 c3 a b = T --30
instance Isa'' F c2 c3 a1 b1 F where {} --
--   isa'' c1 c2 c3 a b = F
instance Isa'' c1 F c3 a1 b1 F where {}
--   isa'' c1 c2 c3 a b = F
instance Isa'' c1 c2 F a1 b1 F where {}
--   isa'' c1 c2 c3 a b = F

 Instance Isa Relations
--
instance Isa' Animal Noun T
instance (TypeCast F result) = Isa' a b result
-Test Relationships
--40
--bla6 = isa Cat Noun --
--bla4 = isa Cat Verb
---Basic Type Declarations
---

data Noun = Noun deriving (Show) --15
data Verb = Verb deriving (Show) --
data Adjactive = Adjactive deriving (Show)

data Animal=Animal deriving (Show)
data Feline=Feline deriving (Show) --50
data Cat = Cat deriving (Show)

data Taby_Cat=Taby_Cat deriving (Show)

---Instance SubType Relations

data ItsAnOrphan = ItsAnOrphan

instance Show ItsAnOrphan where
   show _ = ItsAnOrphan --60

class Parrent a b| a-b where -- Specific Cases
parrent :: a-b --

instance Parrent Cat Feline where --
   parrent a = Feline --40
instance Parrent Feline Animal where --
   parrent a = Animal --
instance (TypeCast result ItsAnOrphan) = Parrent anyChild result
where
   parrent a = undefined::result


--- Generic subType Relations
--

class IsSuperSet a b c | a b - c where -- General Definition
isSuperSet :: a-b-c

--instance (TypeEq b Animal T,TypeEq c F T)=IsSuperSet a b c where
--85
--   isSuperSet a b = F --
u=undefined

instance (
   TypeEq ItsAnOrphan b isOrphan,
   TypeEq a b iseq,
   IsSuperSet' isOrphan iseq a b c3 --
 ) =
  

[Haskell-cafe] Re: Interest in a Mathematics AI strike force ?

2010-05-04 Thread John Creighton
I know that someone has created a Haskell interpreter for lisp.
Perhaps this could server as a starting pointing to creating a
translator between lisp and haskell. This is relevant with regards to
computer algebra because the computer algebra system Maxima is written
is lisp. Their is also a repository of AI programs which are written
in lisp. No doubt starting from scratch with haskell would create new
possibility but it would be nice to also be able to utilize existing
work.

On May 3, 7:59 pm, Alp Mestanogullari a...@mestan.fr wrote:
 Hello -cafe,

 When I started learning Haskell, I saw the AI page [1] which aimed at
 creating a sound, uniform and handy framework for AI programming in Haskell.
 I added my name on it and thought a bit about it. I even wrote a first
 version of HNN [2], a neural network library, quite early in my Haskell
 days.

 I found that idea to be great but did not see any actual effort around this.
 So, I'm now thinking again about that and even enlarging it to mathematics 
 AI. Thus, I would like to have an idea of the number of people interested in
 being involved in such an effort. There are several tools out there on
 hackage but they aren't that much uniform and neither play nicely together.
 I'm pretty convinced this could be improved and as a Mathematics student I'm
 highly interested in that. If enough people are interested, we could for
 example set up a mailing list and a trac to organize the effort and then
 people could just discuss and write Haskell modules when time permits.

 Any comment, idea, reaction, interest ?

 [1]http://www.haskell.org/haskellwiki/AI
 [2]http://www.haskell.org/haskellwiki/HNN

 --
 Alp Mestanogullarihttp://alpmestan.wordpress.com/http://alp.developpez.com/

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

 --
 You received this message because you are subscribed to the Google Groups 
 Haskell-cafe group.
 To post to this group, send email to haskell-c...@googlegroups.com.
 To unsubscribe from this group, send email to 
 haskell-cafe+unsubscr...@googlegroups.com.
 For more options, visit this group 
 athttp://groups.google.com/group/haskell-cafe?hl=en.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell Jaskell Interface?

2010-05-02 Thread John Creighton
I was wondering if a good approach to java interoperability might be a
Haskell Jaskell Interface. Jaskell allows some haskell programs to run
on the java virtual machine and dealt with some of the issues with
regards to interfacing haskell with java on the virtual machine side
of things. Therefore if their was say a GHC bridge between haskell and
jaskell their would be two similar languages talking to each other.
Code ment to be more closely coupled with java could be coded in
jaskell and code that requires say GHC extensions could be written in
haskell and perhaps some io interface between the two languages.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Functional Dependencies Help

2010-05-01 Thread John Creighton


On Apr 30, 6:18 pm, John Creighton johns2...@gmail.com wrote:
 On Apr 29, 7:47 am, John Creighton johns2...@gmail.com wrote:

  I've been trying to apply some stuff I learned about functional
  dependencies, but I run into one of two problems. I either end up with
  inconsistent dependencies (OverlappingInstances  doesn't seem to
  apply) or I end up with infinite recursion. I want to be able to do
  simple things like if a is a subset of b and b is a subset of c then a
  is a subset of c. If a is a is a subset of b and b is a c then a is a
  c.

  Before I added the equality functions I had infinite recursion. Once I
  put them them in then I have trouble with overlapping instances.

 I've been doing some reading and I think the following is an
 improvement but I end up hanging the compiler so I can't tell what the
 errors are. I'll see if their are any trace options that might be
 helpfully for GHC.

So bellow I'll post the latest version of my code but first the errors
which seem very strange to me:



could not deduce (IsSuperSet'
 isanimal iseq isanimal iseq1 (a - b - c3) )
   from the context (IsSuperSet a b c2,
 Typeeq a b iseq1,
 TypeEq Animal b isaninmal,
 IsSuperSet' isanimal iseq1 a b c3)
   arising from a use of 'isSuperSet'' at logicp2.hs:92:25-74
   Possible fix:
  add (IsSuperSet'
  isanimal iseq isanimal iseq1 (a - b - c3)) to context
of the declaration
  or add an instance delaration for
  (IsSuperSet' isanimal iseq isanimal iseq1 (a - b - c3))
   In the expression:
  (isSuperSet' (u :: isanimal) (u :: iseq) (a :: a)
(b ::b)) :: c3
   In the definition of 'isSuperset':
   isSuperset a b
= (isSuperSet' (u :: isanimal) (u :: iseq) (a ::
a) (b :: b))
   in the instance delaration for 'IsSuperSet a b c3'



Now what is strange about these errors, is the type signature haskell
is asking me to supply instance declarations for. For instance

  add (IsSuperSet'
  isanimal iseq isanimal iseq1 (a - b - c3)) to context
of the declaration

Why are the first and the third argument the same. Moreover why do the
third and forth arguments look like types related to my Boolean data
types. I see nothing in my code that could result in Haskell needing
this type signature. Also I'm not entirely sure about the (a - b -
c3). Is this the normal way for Haskell to show the type signature of
functional dependencies.  My code is bellow and was compiled on GHCi.



{-# LANGUAGE EmptyDataDecls,
 MultiParamTypeClasses,
 ScopedTypeVariables,
 FunctionalDependencies,
 OverlappingInstances,
 FlexibleInstances,
 UndecidableInstances#-}

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}


data Noun = Noun deriving (Show) --15
data Verb = Verb deriving (Show) --
data Adjactive = Adjactive deriving (Show)

data Animal=Animal deriving (Show)
data Feline=Feline deriving (Show) --20
data Cat = Cat deriving (Show)

data Taby_Cat=Taby_Cat deriving (Show)
data T=T deriving (Show)
data F=F deriving (Show) --25
--data Z=Z
--data S i = S i
--type One = S Z
--type Zero = Z
class Isa a b c | a b-c where isa::a-b-c --30

instance Isa Animal Noun T where isa a b = T --



class Parrent a b| a-b where -- Specific Cases
parrent :: a-b --

instance Parrent Cat Feline where --
   parrent a = Feline --40
instance Parrent Feline Animal where --
   parrent a= Animal --




class TypeOr a b c|a b-c where
   typeOr :: a-b-c
instance TypeOr T T T where
   typeOr a b = T --50
instance TypeOr T F T where
   typeOr a b = T
instance TypeOr F T T where
   typeOr a b = T
instance TypeOr F F T where
   typeOr a b = T

class TypeEq' () x y b = TypeEq x y b | x y - b
instance TypeEq' () x y b = TypeEq x y b
class TypeEq' q x y b | q x y - b --60
class TypeEq'' q x y b | q x y - b

instance TypeCast b T = TypeEq' () x x b
instance TypeEq'' q x y b = TypeEq' q x y b
instance TypeEq'' () x y F

-- see http://okmij.org/ftp/Haskell/typecast.html
class TypeCast   a b   | a - b, b-a   where typeCast   :: a - b
class TypeCast'  t a b | t a - b, t b - a where typeCast'  :: t-a-
b
class TypeCast'' t a b | t a - b, t b - a where typeCast'' :: t-a-
b --70

instance TypeCast'  () a b = TypeCast a b where typeCast x =
typeCast' () x
instance TypeCast'' t a b = TypeCast' t a b where typeCast' =
typeCast''
instance TypeCast'' () a a where typeCast'' _ x  = x

-- overlapping instances are used only for ShowPred
class EqPred a flag | a-flag where {}

  -- Used only if the other
  -- instances don't apply -- 80

class IsSuperSet a b c | a b - c where -- General Definition
isSuperSet :: a-b-c

[Haskell-cafe] GTKHS mailing list:

2010-05-01 Thread John Creighton
Something needs to be done about the GTKhs mailing list. It is flooded
with spam that no one would want coming to their in box:

http://haskell.org/pipermail/gtkhs/

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


[Haskell-cafe] Re: Functional Dependencies Help

2010-04-30 Thread John Creighton

On Apr 29, 7:47 am, John Creighton johns2...@gmail.com wrote:
 I've been trying to apply some stuff I learned about functional
 dependencies, but I run into one of two problems. I either end up with
 inconsistent dependencies (OverlappingInstances  doesn't seem to
 apply) or I end up with infinite recursion. I want to be able to do
 simple things like if a is a subset of b and b is a subset of c then a
 is a subset of c. If a is a is a subset of b and b is a c then a is a
 c.

 Before I added the equality functions I had infinite recursion. Once I
 put them them in then I have trouble with overlapping instances.

I've been doing some reading and I think the following is an
improvement but I end up hanging the compiler so I can't tell what the
errors are. I'll see if their are any trace options that might be
helpfully for GHC.
{-# LANGUAGE EmptyDataDecls,
 MultiParamTypeClasses,
 ScopedTypeVariables,
 FunctionalDependencies,
 FlexibleInstances #-}

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-} --10
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}


data Noun = Noun deriving (Show) --15
data Verb = Verb deriving (Show) --
data Adjactive = Adjactive deriving (Show)

data Animal=Animal deriving (Show)
data Feline=Feline deriving (Show) --20
data Cat = Cat deriving (Show)

data Taby_Cat=Taby_Cat deriving (Show)
data T=T deriving (Show)
data F=F deriving (Show) --25
--data Z=Z
--data S i = S i
--type One = S Z
--type Zero = Z
class Isa a b c | a b-c where isa::a-b-c --30

instance Isa Animal Noun T where isa a b = T --



class Parrent a b| a-b where -- Specific Cases
parrent :: a-b --

instance Parrent Cat Feline where --
   parrent a = Feline --40
instance Parrent Feline Animal where --
   parrent a= Animal --




class TypeOr a b c|a b-c where
   typeOr :: a-b-c
instance TypeOr T T T where
   typeOr a b = T --50
instance TypeOr T F T where
   typeOr a b = T
instance TypeOr F T T where
   typeOr a b = T
instance TypeOr F F T where
   typeOr a b = T

class TypeEq' () x y b = TypeEq x y b | x y - b
instance TypeEq' () x y b = TypeEq x y b
class TypeEq' q x y b | q x y - b --60
class TypeEq'' q x y b | q x y - b

instance TypeCast b T = TypeEq' () x x b
instance TypeEq'' q x y b = TypeEq' q x y b
instance TypeEq'' () x y F

-- see http://okmij.org/ftp/Haskell/typecast.html
class TypeCast   a b   | a - b, b-a   where typeCast   :: a - b
class TypeCast'  t a b | t a - b, t b - a where typeCast'  :: t-a-
b
class TypeCast'' t a b | t a - b, t b - a where typeCast'' :: t-a-
b --70

instance TypeCast'  () a b = TypeCast a b where typeCast x =
typeCast' () x
instance TypeCast'' t a b = TypeCast' t a b where typeCast' =
typeCast''
instance TypeCast'' () a a where typeCast'' _ x  = x

-- overlapping instances are used only for ShowPred
class EqPred a flag | a-flag where {}

  -- Used only if the other
  -- instances don't apply -- 80

class IsSuperSet a b c | a b-c where -- General Definition
isSuperSet :: a-b-c

--instance (TypeEq b Animal T,TypeEq c F T)=IsSuperSet a b c where
--85
--   isSuperSet a b = F --
u=undefined
instance (
   TypeEq a b iseq, --90
   TypeEq Animal b isaninmal,
   IsSuperSet' isaninmal iseq a b c3 --
 ) =
 IsSuperSet a b c3 where --
 isSuperSet a b=(isSuperSet' (u::isaninmal) (u::iseq) (a::a)
(b::b))::c3

class IsSuperSet' isanimal iseq a b c| isanimal iseq a b-c where
isSuperSet' :: a-b-c

instance IsSuperSet' isanimal T a b T where
   isSuperSet' a b = T

instance (Parrent b d, IsSuperSet a b c)=IsSuperSet' F F a b c where
   isSuperSet' a b = (isSuperSet a ((parrent (b::b)::d)))::c

instance IsSuperSet' T F a b F where
   isSuperSet' a b = F


class ToBool a where
   toBool :: a-Bool

instance ToBool T where
   toBool a = True

instance ToBool F where
   toBool a = False

myCat=Cat
bla=isSuperSet Animal Cat
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Functional Dependencies Help

2010-04-29 Thread John Creighton
I've been trying to apply some stuff I learned about functional
dependencies, but I run into one of two problems. I either end up with
inconsistent dependencies (OverlappingInstances  doesn't seem to
apply) or I end up with infinite recursion. I want to be able to do
simple things like if a is a subset of b and b is a subset of c then a
is a subset of c. If a is a is a subset of b and b is a c then a is a
c.

Before I added the equality functions I had infinite recursion. Once I
put them them in then I have trouble with overlapping isntances.

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}


data Noun = Noun deriving (Show) --10
data Verb = Verb deriving (Show) --
data Adjactive = Adjactive deriving (Show)

data Animal=Animal deriving (Show)
data Feline=Feline deriving (Show)
data Cat = Cat deriving (Show)

data Taby_Cat=Taby_Cat deriving (Show)
data T=T deriving (Show)
data F=F deriving (Show) --20


class Isa a b c | a b-c where isa::a-b-c

instance Isa Animal Noun T where isa a b = T --25

class IsSuperSet a b c | a b-c where
isSuperSet :: a-b-c

instance IsSuperSet Feline Cat T where --30
   isSuperSet a b=T
instance IsSuperSet Animal Feline T where
   isSuperSet a b=T
instance IsSuperSet a Animal F where
   isSuperSet a b=F --35

class TypeNotEq d b c | d b-c where
   typeNotEq :: a-b-c

instance (IsSuperSet d b c, --40
  IsSuperSet a d c,
  TypeNotEq a d T,
  TypeNotEq b d T,
  TypeEq c T T
 )=
IsSuperSet a b c where
  isSuperSet a b=undefined::c

instance TypeNotEq a a c where
typeNotEq a b = undefined::c --50
instance TypeNotEq a b c where
typeNotEq a b = undefined::c
class TypeEq a b c | a b-c where
typeEq :: a-b-c
instance TypeEq a a c where
typeEq a b = undefined::c
instance TypeEq a b c where
typeEq a b = undefined::c

class ToBool a where
   toBool :: a-Bool

instance ToBool T where
   toBool a = True

instance ToBool F where
   toBool a = False

myCat=Cat
bla=isSuperSet Animal Cat
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Sorting Types

2010-04-27 Thread John Creighton
 I was wondering if it is possible to sort types in hakell and if so what
 language extension I should use. Not sure if
 this is possible but here is my attempt:

 (I'm aware I don't need so many pragmas

 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE TypeSynonymInstances #-}
 data Z=Z deriving (Show)
 data S i=S i deriving (Show)
 data family N a
 type family Add n m
 type instance Add Z m = m
 type instance Add m Z = m
 type instance Add (S n) (S m) = S (S (Add n m))
 --14
 type family LT a b
 data Cat=Cat
 data Dog=Dog
 data Fish=Fish
 type family Sort a --19
 data And a b=And a b

 type instance LT Dog Z = Cat
 type instance LT Fish Z = Dog
 type instance LT a (S i) = LT (LT a Z) i
 type instance Sort (And a (LT a i))=And (LT a i) a

 I get the following error:

   Illegal type synonym family application in instance: And a (LT a i)
   In the type synonym instance declaration for 'Sort'
 Failed, modules loaded: none,



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


[Haskell-cafe] Is XHT a good tool for parsing web pages?

2010-04-27 Thread John Creighton
 Subject: Is XHT a good tool for parsing web pages?
 I looked a little bit at XHT and it seems very elegant for writing
 concise definitions of parsers by forms but I read that it fails if
 the XML isn't strict and I know a lot of web pages don't use strict
 XHTML. Therefore I wonder if it is an appropriate tool for web pages.


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