Set Operations In Haskell's Type System

This is partly a continuation from: http://groups.google.ca/group/haskell-cafe/browse_thread/thread/4ee2ca1f5eb8... and http://hpaste.org/fastcgi/hpaste.fcgi/view?id=25265 Also of relevance: http://groups.google.ca/group/haskell-cafe/browse_thread/thread/9cc8858a2e51... 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 -- ) => IsSuperSet a b c3 where --S isSuperSet a b = undefined::c3 -- isSuperSet a b=(isSuperSet' (u::isaninmal) (u::iseq) (a::a) (b::b))::c3 class IsSuperSet' isOrphan iseq a b c| isOrphan iseq a b -> c where {} -- isSuperSet' :: isOrphan->iseq->a->b->c instance (TypeCast c T)=>IsSuperSet' F T a b c where {} -- isSuperSet' isOrphan iseq a b = T instance (TypeCast c F)=>IsSuperSet' T T a b c where {} --Not sure which logic value is best for this case. instance ( Parrent b d, IsSuperSet a d c )=> IsSuperSet' F F a b c where {} -- isSuperSet' isOrphan iseq a b = (isSuperSet a ((parrent (b::b))::d))::c instance (TypeCast c F)=>IsSuperSet' T F a b c where {} -- isSuperSet' isOrphan iseq a b = F ----------- Logical Types ------------------ data T=T -- deriving (Show) data F=F -- deriving (Show) --25 data M=M -- Fail case instance Show T where show _ = "T" instance Show F where show _ = "F" instance Show M where show _ = "M" class ToBool a where toBool :: a->Bool instance ToBool T where toBool a = True instance ToBool F where toBool a = False -----------------------Loical Type Relations ----------------------------- 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 ----------------------- OKMIJ ------------------------------------------ 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 ----------------------- Testing Code -------------------------------- myCat=Cat bla=isSuperSet Animal Cat bla2=isSuperSet Cat Animal bla3=isSuperSet Animal Noun bla4=isSuperSet Noun Animal bla5=isSuperSet Noun Noun

hello,
2010/5/4 John Creighton
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, 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. Please use more descriptive type-variable names, type-level code should also be easy to read:) regards, Bartek Ćwikłowski

On May 4, 9:46 am, Bartek Ćwikłowski
hello,
2010/5/4 John Creighton
: 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].
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 instance (b2~b) => Child' b2 n a b --instance Child'' () b2 n a b => Child' b2 n a b --instance (Child''' q b2 n a b)=>Child''' q b2 n a b ----------- Logical Types ----------------+++++-- data T=T -- deriving (Show) data F=F -- deriving (Show) --25 --data M=M -- Fail case instance Show T where show _ = "T" instance Show F where show _ = "F" --instance Show M where show _ = "M" class ToBool a where toBool :: a->Bool instance ToBool T where toBool a = True instance ToBool F where toBool a = False ---------------------- Peno Numbers ------------------------- data Z=Z type family Simple a type instance Simple (P (S n)) = n type instance Simple (S (P n)) = n type instance Simple Z = Z data S n = S n data P n = P n type P1 = S Z type P2 = S P1 type P3 = S P2 type P4 = S P3 type N1 = P Z type N2 = P N1 type N3 = P N2 type N4 = P N3 -----------------------Basic Type Declarations ---------------------------50 data Noun = Noun deriving (Show) --15 data Verb = Verb deriving (Show) -- data Adjactive = Adjactive deriving (Show) data Animal=Animal -- deriving (Show) instance Show Animal where show _ = "Animal" data Feline=Feline -- deriving (Show) --50 instance Show Feline where show _ = "Feline" data Cat = Cat -- deriving (Show) instance Show Cat where show _ = "Cat" data Taby_Cat=Taby_Cat deriving (Show) --60 ----------------------- OKMIJ ------------------------------------------ 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

hello,
2010/5/6 John Creighton
"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 ). regards, Bartek Ćwikłowski

On May 6, 4:30 am, Bartek Ćwikłowski
hello,
2010/5/6 John Creighton
: "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.

John Creighton wrote:
On May 6, 4:30 am, Bartek Ćwikłowski
wrote: 2010/5/6 John Creighton
: "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:
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

On May 9, 4:46 am, wren ng thornton
John Creighton wrote:
On May 6, 4:30 am, Bartek Ćwikłowski
wrote: 2010/5/6 John Creighton
: "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:
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-cafe@googlegroups.com. To unsubscribe from this group, send email to haskell-cafe+unsubscribe@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.
participants (3)
-
Bartek Ćwikłowski
-
John Creighton
-
wren ng thornton