Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-21 Thread wren ng thornton

On 12/21/12 3:27 AM, Oleksandr Manzyuk wrote:

On Fri, Dec 21, 2012 at 4:40 AM, Alexander Solla  wrote:

I don't see how associativity fails, if we mod out alpha-equivalence.  Can
you give an example?  (If it involves the value "undefined", I'll have
something concrete to add vis a vis "moral" equivalence)


If you compute (f . g) . h, you'll get \x -> (f . g) (h x) = \x -> (\x
-> f (g x)) (h x), whereas f . (g . h) produces \x -> f ((g . h) x) =
\x -> f ((\x -> g (h x)) x).  As raw lambda-terms, these are distinct.
  They are equal if you allow beta-reduction in bodies of abstractions.
  That's what I meant when I said that we probably wanted to consider
equivalence classes modulo some equivalence relation.  That
hypothetical relation should obviously preserve beta-reduction in the
sense (\x -> e) e' = [e'/x]e.


Surely if we have any interest in the semantics of Haskell, we should be 
considering things modulo the usual relations. Of course, this takes us 
directly to the question of what semantics we're actually trying to capture?


Considering terms modulo alpha is obvious. N.B., alpha just refers to 
locally bound variables, not to definitions. We can define multiple 
copies of "the same" type with different names for the data and type 
constructors, and Haskell will hold these things distinct. If they truly 
are "the same" then they'll be isomorphic in the category, which is 
something we deal with all the time.


Considering things modulo delta is also pretty obvious. That is, 
inlining (or outlining) of definitions shouldn't have any semantic 
effect. If it does, then referential transparency fails, and that's one 
of the things we've sworn to uphold.


When we turn to beta (and iota, sigma,...), things start getting 
complicated. On the one hand, we'd like to include beta since it's 
standard in PL semantics. Moreover, since GHC does a certain amount of 
beta at compile time, we sorta can't get away from including it--- if we 
want to believe that (modulo bugs) GHC is semantics preserving. However, 
on the other hand, that means we can't have our semantics say too much 
about the operational differences between Haskell terms. Again, this is 
standard in denotational semantics; but there are reasons to be 
interested in operational semantics as well...


Turning thence to eta, I'm not sure how things stand. It's known that 
eta breaks certain nice properties about type inference/checking, 
especially once you're in the land of full dependent types, but I don't 
recall whether there are any *semantic* issues to be worried about. 
Haskell98 isn't subject to the issues dependent types have, but modern 
GHC is perilously close. E.g., older implementations of GADTs did 
occasionally require outlining in order to provide the necessary type 
signatures, but that's been fixed IIRC. In any case, we do certainly 
need to be careful about the phrasing of eta, since seq can distinguish 
f from (\x -> f x) if f happens to be bottom. So we don't get full eta, 
but how much of it can we salvage? Does it matter for the categorical 
treatment?


--
Live well,
~wren

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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-21 Thread Oleksandr Manzyuk
On Fri, Dec 21, 2012 at 4:40 AM, Alexander Solla  wrote:
>
>
> On Thu, Dec 20, 2012 at 12:53 PM, Oleksandr Manzyuk 
> wrote:
>>
>> I have no problems with the statement "Objects of the category Hask
>> are Haskell types."  Types are well-defined syntactic entities.  But
>> what is a morphism in the category Hask from a to b?  Commonly, people
>> say "functions from a to b" or "functions a -> b", but what does that
>> mean?  What is a function as a mathematical object?  It is a plausible
>> idea to say that a function from a to b is a closed term of type a ->
>> b (and terms are again well-defined syntactic entities).  How do we
>> define composition?  Presumably, by
>>
>> f . g = \x -> f (g x)
>>
>> This however already presupposes that we are dealing not with raw
>> terms, but with their alpha-equivalence classes (otherwise the above
>> is not well-defined as it depends on the choice of the variable x).
>> Even if we mod out alpha-equivalence, so defined composition fails to
>> be associative on the nose, up to equality of (alpha-equivalence
>> classes of) terms.  Apparently, we want to consider equivalence
>> classes of terms modulo some finer equivalence relation.  What is this
>> equivalence relation?  Some kind of definitional equality?
>
>
> I don't see how associativity fails, if we mod out alpha-equivalence.  Can
> you give an example?  (If it involves the value "undefined", I'll have
> something concrete to add vis a vis "moral" equivalence)

If you compute (f . g) . h, you'll get \x -> (f . g) (h x) = \x -> (\x
-> f (g x)) (h x), whereas f . (g . h) produces \x -> f ((g . h) x) =
\x -> f ((\x -> g (h x)) x).  As raw lambda-terms, these are distinct.
 They are equal if you allow beta-reduction in bodies of abstractions.
 That's what I meant when I said that we probably wanted to consider
equivalence classes modulo some equivalence relation.  That
hypothetical relation should obviously preserve beta-reduction in the
sense (\x -> e) e' = [e'/x]e.

When we do equational reasoning about Haskell code, we apply certain
rules.  I think what I'm asking for is an explicit complete set of
such rules.

Note that sometimes you can also hear that the category of Haskell is
a suitable cpo category.  However, this is an answer to a slightly
different question: what is the categorical model of Haskell?  That
is, what kind of categories can Haskell programs be interpreted in.
What I'm after is a kind of universal syntactic Haskell category.  I
expect the situation to be similar to the simply typed lambda-calculus
but more technically involved.  The simply typed lambda-calculus can
be interpreted in any cartesian closed category, but it is also
possible to construct a cartesian closed category out of the simply
typed lambda-calculus.

As someone coming to Haskell and functional programming from category
theory background, I'm probably paying to much attention to details
that don't concern most practicing functional programmers...

Sasha
-- 
Oleksandr Manzyuk
http://oleksandrmanzyuk.wordpress.com

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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-20 Thread Alexander Solla
On Thu, Dec 20, 2012 at 12:53 PM, Oleksandr Manzyuk wrote:

> I have no problems with the statement "Objects of the category Hask
> are Haskell types."  Types are well-defined syntactic entities.  But
> what is a morphism in the category Hask from a to b?  Commonly, people
> say "functions from a to b" or "functions a -> b", but what does that
> mean?  What is a function as a mathematical object?  It is a plausible
> idea to say that a function from a to b is a closed term of type a ->
> b (and terms are again well-defined syntactic entities).  How do we
> define composition?  Presumably, by
>
> f . g = \x -> f (g x)
>
> This however already presupposes that we are dealing not with raw
> terms, but with their alpha-equivalence classes (otherwise the above
> is not well-defined as it depends on the choice of the variable x).
> Even if we mod out alpha-equivalence, so defined composition fails to
> be associative on the nose, up to equality of (alpha-equivalence
> classes of) terms.  Apparently, we want to consider equivalence
> classes of terms modulo some finer equivalence relation.  What is this
> equivalence relation?  Some kind of definitional equality?
>

I don't see how associativity fails, if we mod out alpha-equivalence.  Can
you give an example?  (If it involves the value "undefined", I'll have
something concrete to add vis a vis "moral" equivalence)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-20 Thread Jay Sulzberger



On Thu, 20 Dec 2012, Oleksandr Manzyuk  wrote:


the category of Haskell types and Haskell functions[1]

[1] Note that this may not actually work out to be a category, but the basic
idea is sound.


I would be curious to see this example carefully worked out.  I often
hear that Haskell types and Haskell functions constitute a category,
but I have seen no rigorous definition.

I have no problems with the statement "Objects of the category Hask
are Haskell types."  Types are well-defined syntactic entities.  But
what is a morphism in the category Hask from a to b?  Commonly, people
say "functions from a to b" or "functions a -> b", but what does that
mean?  What is a function as a mathematical object?  It is a plausible
idea to say that a function from a to b is a closed term of type a ->
b (and terms are again well-defined syntactic entities).  How do we
define composition?  Presumably, by

f . g = \x -> f (g x)

This however already presupposes that we are dealing not with raw
terms, but with their alpha-equivalence classes (otherwise the above
is not well-defined as it depends on the choice of the variable x).
Even if we mod out alpha-equivalence, so defined composition fails to
be associative on the nose, up to equality of (alpha-equivalence
classes of) terms.  Apparently, we want to consider equivalence
classes of terms modulo some finer equivalence relation.  What is this
equivalence relation?  Some kind of definitional equality?

Apparently, this (rather non-trivial) exercise has already been
carried out for the simply typed lambda-calculus.  I'd be curious to
see how that generalizes to Haskell (or some equivalent formal
system).

Sasha


Yes.  It would be well worth carefully carrying out your program
for some approximation of a large part of Haskell as she lives in
GHC.  As mentioned earlier, we should not ignore the distinctions
between

  a. the text of a Haskell program
  b. the binary of the now compiled program
  c. the running of the program
  d. the input output behavior of the program

Attempting to force the hoped for clarification to operate only
on one part of the whole at least four part structure is likely
to not give us what we, ah, I, really want to see.

There is some work directly dealing with part of the program:

  http://www.haskell.org/haskellwiki/Hask

oo--JS.



--
Oleksandr Manzyuk
http://oleksandrmanzyuk.wordpress.com


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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-20 Thread Oleksandr Manzyuk
> the category of Haskell types and Haskell functions[1]
>
> [1] Note that this may not actually work out to be a category, but the basic
> idea is sound.

I would be curious to see this example carefully worked out.  I often
hear that Haskell types and Haskell functions constitute a category,
but I have seen no rigorous definition.

I have no problems with the statement "Objects of the category Hask
are Haskell types."  Types are well-defined syntactic entities.  But
what is a morphism in the category Hask from a to b?  Commonly, people
say "functions from a to b" or "functions a -> b", but what does that
mean?  What is a function as a mathematical object?  It is a plausible
idea to say that a function from a to b is a closed term of type a ->
b (and terms are again well-defined syntactic entities).  How do we
define composition?  Presumably, by

f . g = \x -> f (g x)

This however already presupposes that we are dealing not with raw
terms, but with their alpha-equivalence classes (otherwise the above
is not well-defined as it depends on the choice of the variable x).
Even if we mod out alpha-equivalence, so defined composition fails to
be associative on the nose, up to equality of (alpha-equivalence
classes of) terms.  Apparently, we want to consider equivalence
classes of terms modulo some finer equivalence relation.  What is this
equivalence relation?  Some kind of definitional equality?

Apparently, this (rather non-trivial) exercise has already been
carried out for the simply typed lambda-calculus.  I'd be curious to
see how that generalizes to Haskell (or some equivalent formal
system).

Sasha
-- 
Oleksandr Manzyuk
http://oleksandrmanzyuk.wordpress.com

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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-20 Thread wren ng thornton

On 12/18/12 5:03 PM, Christopher Howard wrote:

Since I received the two responses to my question, I've been trying to
think deeply about this subject, and go back and understand the core
ideas. I think the problem is that I really don't have a clear
understanding of the basics of category theory, and even less clear idea
of the connection to Haskell programming. I have been reading every link
I can find, but I'm still finding the ideas of "objects" and especially
"morphisms" to be quite vague.


As others have mentioned, that "vagueness" is, in fact, intentional. 
There are two ways I can think of to help clear up the abstraction. The 
first is just to give a bunch of examples:


the category of sets (objects) and set-theoretic functions (morphisms)
the category of Haskell types and Haskell functions[1]
... (small) categories, and functors
... rings, and ring homomorphisms
... groups, and group homomorphisms
... vectors, and linear transformations
... natural numbers, and matrices
... elements of a poset, and the facts that one element precedes another
... nodes of a directed graph, and paths on that graph


The second approach is to compare it to something you're already 
familiar with. I'm sure you've encountered monoids before: they're just 
an associative operation on some carrier set, plus an element of that 
set which is the identity for the operation. Perhaps the most auspicious 
one to think about is multiplication, or concatenation of lists.


A category is nothing more than a generalization from monoids to 
"monoid-oids". That is, with monoids we give our operator the following 
type:


(*) :: A -> A -> A

but sometimes things aren't so nice. Just think about matrix 
multiplication, or function composition. These are partial operations 
because they only work on some subset of A. The two As must air up in a 
nice way. Thus, what we really have is not one carrier, but a family of 
carriers which are indexed by their "input" end (domain) and their 
"output" end (codomain). Thus, we have the type:


(*) :: A i j -> A j k -> A i k

or

(*) :: A j k -> A i j -> A i k

where i, j, and k, are our indices. Which one of the above two types you 
get doesn't matter, it's just the difference between (<<<) and (>>>) in 
Haskell. Of course, now that we've indexed everything, we can't have 
just one identity element for the operation; instead, we need a whole 
family of identity elements:


1 :: A i i

In a significant sense, the objects are really only there to serve as 
indices for the domain and codomain of a morphism. They need not have 
any other significance. A good example of this is when we compare two of 
the example categories above: linear transformations, vs matrices. For 
the category of vector spaces and linear transformations, the objects 
actually mean something: they're vector spaces. However, in the category 
of natural numbers and matrices, the natural numbers only serve to tell 
us the dimensions of the matrices so that we know whether we can 
multiply them together or not. Thus, these are different categories, 
even though they're the same in just about every regard.



[1] Note that this may not actually work out to be a category, but the 
basic idea is sound.




But here I am
confused: If "functions" are a category, this would seem to imply (by
the phrasing) that functions are the objects of the category. However,
since we compose functions, and only morphisms are composed, it would
follow that functions are actually morphisms. So, in the "function"
category, are functions objects or morphisms? If they are morphisms,
then what are the objects of the category?


Objects in Haskell are types, and functions aren't types. But cherish 
that confusion for a bit, because it hints at a deeper thing going on 
here. In the simplest scenario, functions are the morphisms between 
objects (i.e., types). But what happens when we consider higher-order 
functions?


In Haskell we write things like:

(A -> B) -> C
D -> (E -> F)

Whereas, in category theory we would distinguish the first-order arrows 
from the higher-order arrows:


B^A -> C
D -> F^E

That is, we have an object B^A (read that as an exponent), and we have a 
class of morphisms A->B (sometimes this class is instead written 
Hom(A,B)). These are different things, though we willfully conflate them 
in functional programming. The B^A can be thought of as the class of all 
functions from A to B when we consider these functions as data; whereas 
the A->B can be thought of as the class of all functions from A to B 
when we consider these functions as procedures to be executed. Part of 
the reason we conflate these in functional programming is because we 
know that the one reflects the other. Whereas the reason category theory 
distinguishes them is because this sort of reflection isn't possible in 
all categories. Some categories have exponential objects, others don't.[2]


Thus, when you ask whether a function b

Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-20 Thread wren ng thornton

On 12/17/12 9:45 PM, Christopher Howard wrote:

So you could have...

(coupler <.> thing) <.> gadget

Because the coupler and the thing would combine to create a component
with one spare connector. This would then combine with the gadget to
make the final component. However, if you did...

coupler <.> (thing <.> gadget)

Then thing and gadget combine to make a component with no spare
connectors. And so the new component and the coupler then fail to
combine. Associativity law broken.


I don't know about this particular case, but often when "it should be 
associative but isn't" problems come up, it helps to rephrase things. 
For example, consider plain old Haskell, but where we make application 
explicit. On the one hand, we can have:


f $ (g $ x)

and that's fine. But it's not equivalent to:

(f $ g) $ x

But the problem here isn't that we don't have associativity; the problem 
is that function application isn't the associative operator. The 
associative operator is function composition. Thus, we can rephrase the 
above as:


f . (g . const x)

Which is indeed equivalent to:

(f . g) . const x

Note that in order to dispense with ($) entirely, we had to replace "x" 
by "const x" in order to make it a function just like everything else. 
This is akin to the trick we use in category theory to get away from 
talking about "values" or "elements". If your category has a terminal 
object, which I'll call (), then we can represent the "elements" of A by 
morphisms ()->A. By terminality there's no "interesting" structure in 
(), thus, the only information in ()->A is however we're selecting our 
"element" of A.


This is, of course, the same exact thing that happens in vector spaces 
and the like. If I write (*.) for scaling a vector, then we have:


x *. (y *. a) == (x * y) *. a

which should look suspiciously similar to:

f $ (g $ x) == (f . g) $ x


But from your description, it sounds like the above may not be the 
source of your problem. The second sort of non-associativity problem 
that's common is when dealing with a function of multiple arguments (or 
similar). That is, there are two separate kinds of "whitespace for 
application" in Haskell. This is easy to see if we switch to the 
Applicative paradigm:


   f <$> x <*> y

Now, for Applicatives this happens because the f above is pure. But we 
also run into it with plain functions--- namely, we can have our 
functions curried or not. We can freely switch between these different 
representations, but we can't get away from the fact that they both 
exist. Thus, there's a sort of inherent difference between the 
juxtaposition of a function and it's (first) argument, vs the 
juxtaposition of multiple arguments. Regardless of whether we view the 
latter as tupling or as subsequent-application, both of those 
perspectives are distinct from the initial-application.


The solution here, I think, is just to recognize what's going on. If you 
need two operators, then you need two operators, and that's fine. With 
the examples above it comes from dealing with a cartesian closed 
category, but there are certainly other structures your operators may be 
examples of.


--
Live well,
~wren

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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-19 Thread Ertugrul Söylemez
Mark Flamer  wrote:

> I have also become intrigued and confused by this "category theory"
> and how it relates to Haskell. It has been stated many times that you
> don't need to understand category theory to utilize the Haskell
> language but all the concepts, patterns and every paper describing
> them seems to be written by someone who understands it. It really
> appears that to "innovate" in this community it helps to at least have
> a basic understanding of the theory. I have started working through
> this book "Conceptual Mathematics, A first introduction to categories"
> and so far it seems very understandable and interesting for mere
> mortals like myself.

My experience is that you can very well innovate in this community
without understanding anything of category theory (CT).  The fun starts
when you realize that your concept, when sound, can most often be
expressed in the categorical framework, and if not, then your concept is
either unsound or can be improved by CT.

In other words, you can learn it along the way, and you do that best by
writing software and using well designed libraries.

For understanding CT itself my suggestion is that you don't try too
hard.  The human mind is used to visualizing things, and except for an
abstract directed graph this fails terribly for CT.  That means, when
you feel stuck, chances are that's just a false feeling.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-19 Thread Mark Flamer
I have also become intrigued and confused by this "category theory" and how
it relates to Haskell. It has been stated many times that you don't need to
understand category theory to utilize the Haskell language but all the
concepts, patterns and every paper describing them seems to be written by
someone who understands it. It really appears that to "innovate" in this
community it helps to at least have a basic understanding of the theory. I
have started working through this book "Conceptual Mathematics, A first
introduction to categories" and so far it seems very understandable and
interesting for mere mortals like myself.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/category-design-approach-for-inconvenient-concepts-tp5722579p5722664.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-19 Thread Alexander Solla
On Tue, Dec 18, 2012 at 11:53 PM, Christopher Howard <
christopher.how...@frigidcode.com> wrote:

> I really like the idea that all
> parts of my program could be cleanly and systematically composed from
> smaller pieces, in some beautiful design patter. Many of the problems in
> my practical programming, however, are not like the examples I have seen
> (nice pipes or unidirectional calculations) but rather complex fitting
> together of components. E.g., space ships are made up of guns + engines
> + shields + ammo. Different kinds of space ships may use the same kind
> of guns (reusable components) but some wont. Some will have many guns,
> some will have none.
>

So, suppose we have the types:

data Gun = Gun { requiresAmmo :: Ammo }
data Engine = ...
data Ammo = ...
data Shield = ...

Now, we can build up a space ship in two basic ways:

type SpaceShip = ([Gun], [Engine], [Shield], [Ammo])
mkSpaceShip :: [Gun] -> [Engine] -> [Shield] -> [Ammo] -> SpaceShip

or we can define a data type:

data SpaceShip = SpaceShip [Gun] [Engine] [Shied] [Ammo]

or other variations.  Note that, as morphisms, mkSpaceShip and 'SpaceShip'
are "isomorphic", insofar as the objects they build are different
representations of the same data -- both are "product" types.  In any case,
note that some spaceships can have lots of engines, and others can have
none.

Now, suppose we want a spaceship to actually do something.  In particular,
we might worry about pirate space ships:

   type PirateShip = SpaceShip

and worry about whether your speedy ship can deal with them effectively.
 How would we model this?  Here is an example:

   simulateBattle :: SpaceShip -> PirateShip -> Bool
   simulateBattle s@(SpaceShip gs es ss as) p@(SpaceShip gs' es' ss' as') =
if es `subset` es' then mustFight s p
 else True -- Your ship ran away

   mustFight :: SpaceShip -> PirateShip -> Bool
   mustFight = undefined -- encode semantics about guns, shields, weight,
etc here

We claim that simulateBattle is a "morphism scheme" -- we can /say/ that it
is a morphism from a variety of categories to a variety of categories.  For
example, by rearranging, we can view it as a morphism from
 (SpaceShape -> PirateShip) to Bool (as I said elsewhere, this kind of
morphism isn't particularly useful to a programmer, since we can't analyze
a function to produce a Bool -- being able to do so would mean we have
solved the Halting problem)

or from
 SpaceShip to (PirateShip -> Bool)
or from (SpaceShip, PirateShip) to Bool
or from (SpaceShip) to (PirateShip, Bool)

Note that these choices have different representations as data structures,
and that these structures might have very different properties in terms of
space/time usage.

Compositionality isn't "an" architecture.  It's a property that lets us
transform compositional architectures into other compositional
architectures, while still maintaining the semantics we want.  There are no
"surprises" about the "meaning" of any of the simulateBattle types, even
though their values might behave differently in space and time, because of
the different data structures in play.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Christopher Howard
On 12/18/2012 08:02 PM, Gershom Bazerman wrote:
> On 12/17/12 9:45 PM, Christopher Howard wrote:
> 
> I don't think you're describing a "Category" in the sense of the Haskell
> Category typeclass. But that's ok! Just because some things are
> categories and are nice doesn't mean that we can't have other nice
> things that aren't necessarily categories. My first thought was
> something with multiple inputs and one output is often an Operad
> (http://en.wikipedia.org/wiki/Operad_theory) but associativity is still
> an issue. Also bear in mind that operads and categories are both
> *directional* whereas your notion of coupling doesn't seem to be (which
> has something to do with associativity failing, I'd imagine).

I think the example I gave was pretty messed up anyway, because I was
trying to compose objects rather than morphisms. But that directional
aspect you mentioned does seem significant... so I guess my main
question is how that things that are more complex (like a
multi-directional system built from pluggable components) could be
represented in the Categorical manner. I'm looking for the Grand
Unifying Theory to follow, if you will; I really like the idea that all
parts of my program could be cleanly and systematically composed from
smaller pieces, in some beautiful design patter. Many of the problems in
my practical programming, however, are not like the examples I have seen
(nice pipes or unidirectional calculations) but rather complex fitting
together of components. E.g., space ships are made up of guns + engines
+ shields + ammo. Different kinds of space ships may use the same kind
of guns (reusable components) but some wont. Some will have many guns,
some will have none. And such like issues.

Soylemez seems to have answered this issue directly in his reply.
Unfortunately, I didn't understand most of what he wrote. :|

> 
> I also don't understand, e.g., what happens if I couple a thing with two
> connectors and one connector -- which connector from the first gets
> used, or are they interchangeable?
> 

The example I gave was hastily put together and not well thought out. I
was Just trying to come up with something that would convey the general
idea. But perhaps each component would have a list of connectors, and
the first ones in the list would be used first. When a new component was
created from other components, the new list would be taken from the
leftover connectors (if any). In real world use I would probably have
multiple types of connectors, but I haven't thought that far ahead.

> Going back even further, you've suggested a "Fail" to represent when the
> connectors don't match. Why not start with encoding connectors in types
> to begin with, so that it is a type error to not have matching
> connectors? Follow the logic of your idea, shape your types to match
> your representable states, and then see what algebraic structures
> naturally emerge.
> 
> Cheers,
> Gershom
> 

Sounds good. Of course, I still haven't figured out what design pattern
to fit said types into. :(


-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Gershom Bazerman

On 12/17/12 9:45 PM, Christopher Howard wrote:

However, what I'm wondering about is ideas that can be "composed" but
that don't seem to fit the idea of "category", because they don't obey
the associativity law. To give a specific example (pseudo code like,
without any idea here of implementation or proper syntax):

Say you created a type called "Component" (C for short), the idea being
to compose Components out of other Components. Every C has zero or more
connectors on it. Two Cs can be connected to form a new C using some
kind of composition operator (say, <.>), provided there are enough
connectors (one on each). Presumably you would need a "Fail" constructor
of some kind to represent the situation when there is not enough connectors.

Say you had a C (coupler) with two connectors, a C (thing) with one
connector, and a C (gadget) with one connector.

So you could have...

(coupler <.> thing) <.> gadget

Because the coupler and the thing would combine to create a component
with one spare connector. This would then combine with the gadget to
make the final component. However, if you did...

coupler <.> (thing <.> gadget)

Then thing and gadget combine to make a component with no spare
connectors. And so the new component and the coupler then fail to
combine. Associativity law broken.

So, can I adjust my idea to fit the "category" concept? Or is it just
not applicable here? Or am I just misunderstanding the whole concept?


I don't think you're describing a "Category" in the sense of the Haskell 
Category typeclass. But that's ok! Just because some things are 
categories and are nice doesn't mean that we can't have other nice 
things that aren't necessarily categories. My first thought was 
something with multiple inputs and one output is often an Operad 
(http://en.wikipedia.org/wiki/Operad_theory) but associativity is still 
an issue. Also bear in mind that operads and categories are both 
*directional* whereas your notion of coupling doesn't seem to be (which 
has something to do with associativity failing, I'd imagine).


I also don't understand, e.g., what happens if I couple a thing with two 
connectors and one connector -- which connector from the first gets 
used, or are they interchangeable?


Going back even further, you've suggested a "Fail" to represent when the 
connectors don't match. Why not start with encoding connectors in types 
to begin with, so that it is a type error to not have matching 
connectors? Follow the logic of your idea, shape your types to match 
your representable states, and then see what algebraic structures 
naturally emerge.


Cheers,
Gershom

P.S. I think you're right to be confused by that article. It's 
confusingly written, and I think is a poor entry point into either 
category theory as such or even the proper use of the Category typeclass 
in Haskell.


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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Alexander Solla
On Tue, Dec 18, 2012 at 4:49 PM, Ertugrul Söylemez  wrote:

> These laws make morphisms isolated and composition lightweight as well
> as undisturbing.  Now try to transfer these notions to a concrete
> category, for example the category of web servers:  The objects are sets
> and a morphism f : A -> B is a function from A × Request to B.
>

Expanding on this point, we can "refactor" how we "present" this category,
using laws from basic category theory, so that

   f :: (A, Request) -> B
   f :: A -> Request -> B
   f :: A -> (Request -> B)
   f :: (A -> Request) -> B (this one isn't very useful to a programmer)
   f :: a -> Request B (by lifting a concrete Request object into a functor
of the form (Request a))

etc, are all "equivalent", insofar as they merely present different
interfaces to the same data.  Note that these are distinct as
"presentations", but equivalent as categories ("isomorphic", up to
decidability -- the one I said wasn't useful really isn't, because "as a
matter of fact", we can't decidably analyze/deconstruct a function (g :: A
-> Request) to produce a B).

This should make architectural decisions easy (or hard) -- once you have
decided to use a category at all, you merely have to choose the
presentation for the category that satisfies other requirements.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Richard O'Keefe

On 19/12/2012, at 11:03 AM, Christopher Howard wrote:
> Since I received the two responses to my question, I've been trying to
> think deeply about this subject, and go back and understand the core
> ideas. I think the problem is that I really don't have a clear
> understanding of the basics of category theory, and even less clear idea
> of the connection to Haskell programming. I have been reading every link
> I can find, but I'm still finding the ideas of "objects" and especially
> "morphisms" to be quite vague.

Roughly speaking, Category Theory is the study of mathematical analogies
that work.  You notice that the symmetries of a cube have properties that
remind you of the properties of integer addition, and end up constructing
Group Theory to describe a huge range of things that can be modelled as
"things" acted on by "operations" to give other things, where the operations
follow particular laws.  And you get this astonishing range of theorems that
have lots of not-obviously-related applications.  Then you notice that
Group Theory and Lattice Theory and a bunch of other things seem to have
more analogies than you expected, and you abstract out what they have in
common (structured collections of things with transformations from one
structure to another that preserve various properties of the structured
collections).

What's the connection to Haskell programming?

Reusability.

Both Category Theory and Haskell push rather harder on abstraction than
most people are comfortable with, in order to get mathematical results in
the one case and functional code in the other that can be applied to lots
of problems.

The price of reusability is vagueness.

Let me offer an analogy.   At primary school I was introduced to the
greatest common divisor and Euclid's algorithm.  Here's this algorithm
that applies to integers and this is what it tells you.  And in a
program you might write gcd(x,y).  These days, I look at gcd and see
"oh yes, the meet in the 'divides' lattice" and write x/\y, where
the same symbol ("meet", /\) can be used for gcd, set intersection,
bitwise and, unification, ...) and I know more _laws_ that /\ obeys
than I did back then, but the integers have receded from view.

> The original link I gave
>  purposely skipped
> over any discussion of objects, morphisms, domains, and codomains. The
> author stated, in his first example, that "Haskell functions" are a
> category, and proceeded to describe function composition.

This mailing list often talks about the "Hask" category.
For example, in Orchard's blog (http://dorchard.wordpress.com) we find

The Hask category

The starting point of the idea is that programs in Haskell
can be understood as providing definitions within some
category, which we will call Hask.  Categories comprise
a collection of objects and a collection of morphisms
which are mappings between objects.  Categories come
equipped with identity morphisms for every object and
an associative composition operation for morphisms
(see Wikipedia for a more complete, formal definition).
For Hask, the objects are Haskell types, morphisms are
functions in Haskell, identity morphisms are provided
by the identity function, and composition is the usual
function composition operation.

In Hask, Haskell functions are the *morphisms* of a category, not its
objects.  That's not to say that you couldn't have a category whose
objects were (in some sense) Haskell functions, just that it would be
a different category.  Rather confusingly, the "objects" of Hask are
*not* data values, they are data *types*.  This is just like the way
that in the category of sets, the objects are *sets*, not their
elements.

But of course category theory is too general for a neat summary like
"objects are sets or types and morphisms are functions between them".
No, objects are _whatever_ you choose to model as not-further-analysed
objects, and morphisms are _whatever_ connections between your objects
you choose to model as morphisms, so long as they obey the laws.

I am struggling with category theory myself.  I'll be learning about
some kind of mathematical structure, getting to grips with the elements
and the operations on the elements, and suddenly the book will move up
a level and instead of looking at patterns between elements, will look
at patterns of morphisms.  And to add insult to injury, the book will
claim that moving from one large space to an exponentially larger
(if not worse) space remote from the things I'm trying to understand
actually makes things _simpler_ to think about.  One of my colleagues
here divides people into "set theory people" and "category theory
people".  He and I both classify ourselves as "set theory people".
Maybe in another 50 years I'll be comfortable with category theory,
but by then I'll be dead.

Right now, the issues for you ar

Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Ertugrul Söylemez
Christopher Howard  wrote:

> Since I received the two responses to my question, I've been trying to
> think deeply about this subject, and go back and understand the core
> ideas. I think the problem is that I really don't have a clear
> understanding of the basics of category theory, and even less clear
> idea of the connection to Haskell programming. I have been reading
> every link I can find, but I'm still finding the ideas of "objects"
> and especially "morphisms" to be quite vague.

It's vague on purpose, or in better words it's abstract.  A category C
is a collection of objects called ob(C) and a collection of morphisms
hom(C) together with morphism composition that satisfies a few laws.
That's it.  It's up to you to interpret the objects and morphisms.
Different categories give rise to completely different interpretations.

What makes category theory interesting for programming is the set of
laws, because unlike the unspecified nature of objects and morphisms,
the laws are very specific.  They establish a rigorous notion of
soundness and locality.  Let's review these laws:

  * For all f : A -> B, g : B -> A:
id A . g = g
f . id A = f

This law is often understated.  It means that identity morphisms are
free of effects that could disturb composition.  It also means that the
composition does not change the nature of the component morphisms and is
free of effects that could disturb the neutrality of identity morphisms.

  * f . (g . h) = (f . g) . h

Not much to be said about this one, except that it makes composition
'lightweight' in a sense.  This basically means that you don't care how
compositions are grouped.

These laws make morphisms isolated and composition lightweight as well
as undisturbing.  Now try to transfer these notions to a concrete
category, for example the category of web servers:  The objects are sets
and a morphism f : A -> B is a function from A × Request to B.


> The original link I gave
>  purposely
> skipped over any discussion of objects, morphisms, domains, and
> codomains. The author stated, in his first example, that "Haskell
> functions" are a category, and proceeded to describe function
> composition. But here I am confused: If "functions" are a category,
> this would seem to imply (by the phrasing) that functions are the
> objects of the category. However, since we compose functions, and only
> morphisms are composed, it would follow that functions are actually
> morphisms. So, in the "function" category, are functions objects or
> morphisms? If they are morphisms, then what are the objects of the
> category?

You are absolutely right there.  The category is common called Hask, the
category of types and functions in Haskell.  It is strongly related to
the category of sets and functions, because Haskell types are actually
just sets, where every set has one additional member: bottom.  We say
that the set is 'lifted'.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Jay Sulzberger



On Tue, 18 Dec 2012, Christopher Howard wrote:


On 12/17/2012 06:30 PM, Richard O'Keefe wrote:


On 18/12/2012, at 3:45 PM, Christopher Howard wrote:

It's basically the very old idea that an Abstract Data Type
should be a nice algebra: things that look as though they
ought to fit together should just work, and rearrangements
of things ought not to change the semantics in surprising
ways (i.e., Don't Be SQL).



Categories contain two things:
"objects"
and "arrows" that connect objects.  Some important things about arrows:
 - for any object x there must be an identity id : x -> x
 - any two compatible arrows must compose in one and only one way:
   f : x -> y & g : y -> z  =>  g . f : x -> z
 - composition must be associative (f . g) . h = f . (g . h)
   when the arrows fit together.

Of course for any category there is a dual category,
so what I'm about to say doesn't really make sense,
but there's sense in it somewhere:  the things you are
trying to hook together with your <.> operator seem to me more
like objects than arrows, and it does not seem as if
they hook together in one and only one way, so it's not so
much _associativity_ being broken, as the idea of <.> being
a composition in the first place.




Since I received the two responses to my question, I've been trying to
think deeply about this subject, and go back and understand the core
ideas. I think the problem is that I really don't have a clear
understanding of the basics of category theory, and even less clear idea
of the connection to Haskell programming. I have been reading every link
I can find, but I'm still finding the ideas of "objects" and especially
"morphisms" to be quite vague.


Much discussion that I have seen of "categories and Haskell" is
imprecise.  It is often possible to convey some fact, or point of
view, using imprecise language, but in many cases, the
communication will fail, unless the reader has a solid
understanding of the basics.  Getting this understanding requires
studying harsh and, often, off putting, textbooks.

I will say two things:

1. Usually, to understand category theory a firm grasp of the
concept "structure" is required.

2. To connect categories with Haskell requires some apparatus,
which apparatus should be laid out precisely, at least once in
the exposition.

ad 1: By "a structure" I mean what Bourbaki calls "a structure".
  See:

  http://en.wikipedia.org/wiki/Mathematical_structure
  [page was last modified on 7 August 2012 at 17:15]

  http://en.wikipedia.org/wiki/Structure_%28mathematical_logic%29
  [page was last modified on 15 December 2012 at 19:36]

  http://en.wikipedia.org/wiki/Algebraic_structure
  [page was last modified on 11 December 2012 at 02:51]

ad 2: The tutorial should carefully distinguish these different
things:

  a. the text of a Haskell program
  b. the binary of the now compiled program
  c. the running of the program
  d. the input output behavior of the program

Each of these gives rise to at least one category, and there are
various functors among these categories.

Set theory, say ZFC style, and New Crazy Type Theory, offer two
different Backround Mechanisms to explicate the notion of
"structure".  There are similarities between these two Grand
Theories, but there are also political differences.

ad seeming vagueness of the notions object and morphism: This
vagueness, which is felt by all students at first, is often
explicated/excused by saying that the notions are "more abstract"
than say, the notions of "integer" and "addition of integers" and
"multiplication of integers".  This way of speaking is not
entirely wrong, but I think it mainly wrong and misleading.
Bourbaki somewhere says something like:

  Recent mathematics characteristically differs from older
  mathematics in that our axiom systems usually have more than
  one model, whereas in the old mathematics, theories usually had
  only one model.

Here is how this explicates the sentence:

   The theory of rings is more abstract than the theory of
   addition and multiplication of the integers.

We all know the integers.  The integers form a set, with such
elements as 0, 1, 17, -345, and so on.  We have learned two
operations on this single set: addition and multiplication.  This
understanding is a "concrete" understanding of a single concrete
object, which does indeed have parts, such as -345, and the
operation +, for example, but all the statements we might make
can, in some sense, be settled by looking at this single
structure and its various parts.  Or so we feel.  (Note in the
sentence in which there are two occurences of the word
"concrete", the two occurences must have different sense.)

But the theory of rings is quite a different theory.  There are
many different structures which are studied in the theory of
rings.  For example the ring of integers is one such structures.
There is also the ring of complex numbers.  There is also the
ring of 2 x 2 matrices over the integers.  Ano

Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Gábor Lehel
On Tue, Dec 18, 2012 at 11:03 PM, Christopher Howard
>
> The original link I gave
>  purposely skipped
> over any discussion of objects, morphisms, domains, and codomains. The
> author stated, in his first example, that "Haskell functions" are a
> category, and proceeded to describe function composition. But here I am
> confused: If "functions" are a category, this would seem to imply (by
> the phrasing) that functions are the objects of the category. However,
> since we compose functions, and only morphisms are composed, it would
> follow that functions are actually morphisms. So, in the "function"
> category, are functions objects or morphisms? If they are morphisms,
> then what are the objects of the category?

Types.


(P.S. Thanks Ertugrul, for giving me a way to latch onto the meaning
of profunctors - now I'll have to go back to that package again and
see if it makes more sense...)

-- 
Your ship was destroyed in a monadic eruption.

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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-18 Thread Christopher Howard
On 12/17/2012 06:30 PM, Richard O'Keefe wrote:
> 
> On 18/12/2012, at 3:45 PM, Christopher Howard wrote:
> 
> It's basically the very old idea that an Abstract Data Type
> should be a nice algebra: things that look as though they
> ought to fit together should just work, and rearrangements
> of things ought not to change the semantics in surprising
> ways (i.e., Don't Be SQL).
> 
> 
> 
> Categories contain two things:
> "objects"
> and "arrows" that connect objects.  Some important things about arrows:
>  - for any object x there must be an identity id : x -> x
>  - any two compatible arrows must compose in one and only one way:
>f : x -> y & g : y -> z  =>  g . f : x -> z
>  - composition must be associative (f . g) . h = f . (g . h)
>when the arrows fit together.
> 
> Of course for any category there is a dual category,
> so what I'm about to say doesn't really make sense,
> but there's sense in it somewhere:  the things you are
> trying to hook together with your <.> operator seem to me more
> like objects than arrows, and it does not seem as if
> they hook together in one and only one way, so it's not so
> much _associativity_ being broken, as the idea of <.> being
> a composition in the first place.
> 
> 

Since I received the two responses to my question, I've been trying to
think deeply about this subject, and go back and understand the core
ideas. I think the problem is that I really don't have a clear
understanding of the basics of category theory, and even less clear idea
of the connection to Haskell programming. I have been reading every link
I can find, but I'm still finding the ideas of "objects" and especially
"morphisms" to be quite vague.

The original link I gave
 purposely skipped
over any discussion of objects, morphisms, domains, and codomains. The
author stated, in his first example, that "Haskell functions" are a
category, and proceeded to describe function composition. But here I am
confused: If "functions" are a category, this would seem to imply (by
the phrasing) that functions are the objects of the category. However,
since we compose functions, and only morphisms are composed, it would
follow that functions are actually morphisms. So, in the "function"
category, are functions objects or morphisms? If they are morphisms,
then what are the objects of the category?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-17 Thread Ertugrul Söylemez
Christopher Howard  wrote:

> Say you created a type called "Component" (C for short), the idea
> being to compose Components out of other Components. Every C has zero
> or more connectors on it. Two Cs can be connected to form a new C
> using some kind of composition operator (say, <.>), provided there are
> enough connectors (one on each). Presumably you would need a "Fail"
> constructor of some kind to represent the situation when there is not
> enough connectors.
>
> Say you had a C (coupler) with two connectors, a C (thing) with one
> connector, and a C (gadget) with one connector.
>
> So you could have...
>
> (coupler <.> thing) <.> gadget
>
> Because the coupler and the thing would combine to create a component
> with one spare connector. This would then combine with the gadget to
> make the final component. However, if you did...
>
> coupler <.> (thing <.> gadget)
>
> Then thing and gadget combine to make a component with no spare
> connectors. And so the new component and the coupler then fail to
> combine. Associativity law broken.
>
> So, can I adjust my idea to fit the "category" concept? Or is it just
> not applicable here? Or am I just misunderstanding the whole concept?

You are not misunderstanding the concept.  You just need to learn how to
apply it in this situation.  Pluggable components with multiple slots
are still modelled by regular categories.  Let's say that Comp is such a
component category (I'm using Haskell syntax):

Comp :: * -> * -> *

To model a component that takes two inputs you just write a component
that takes one (!) tuple of inputs:

myComp :: Comp (X, Y) Z

For partial application of your component you need a bit more than the
basic category pattern.  Most categories form a family of applicative
functors:

instance Applicative (Comp a)

Then partial application is really just this:

partialMyComp :: X -> Comp Y Z
partialMyComp x = myComp . fmap (\y -> (x, y)) id

Every category that forms such a family of applicative functors is a
profunctor (see the 'profunctors' package by Edward Kmett):

instance Profunctor Comp

That makes expressing partialMyComp slightly more pleasing:

partialMyComp x = lmap (\y -> (x, y)) myComp

Finally to save even more keystrokes enable the TupleSections extension:

partialMyComp x = lmap (x,) myComp

You can get similar description through the Arrow interface:

instance Arrow Comp

partialMyComp x = myComp . arr (x,)

However, often the applicative interface is much more pleasing.

Now to the theory:  What does an applicative functor give you?  It
basically extends a categorical concept by the ability to combine
multiple morphisms to a single one.  Given two morphisms,

c1 :: Comp A B
c2 :: Comp A C

and a function

f :: B -> C -> D

an applicative functor gives you a well-defined way to combine c1 and c2
into another morphism of type

c3 :: Comp A D

An applicative functor provides about the same theoretical soundness as
a category in that such a combination of multiple Comp morphisms is
itself always a Comp morphism, and that the combination operator itself
cannot introduce unwanted effects because of the Applicative laws:

pure f <*> x = fmap f x
f <*> pure x = fmap ($ x) f

pure f <*> pure x = pure (f x)

In other words, all effects are introduced by primitive components.  I
call them "atoms".


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] category design approach for inconvenient concepts

2012-12-17 Thread Richard O'Keefe

On 18/12/2012, at 3:45 PM, Christopher Howard wrote:
> Recently I read this article I happened across, about the categorical
> design pattern:
> 
> http://www.haskellforall.com/2012/08/the-category-design-pattern.html

It's basically the very old idea that an Abstract Data Type
should be a nice algebra: things that look as though they
ought to fit together should just work, and rearrangements
of things ought not to change the semantics in surprising
ways (i.e., Don't Be SQL).

> However, what I'm wondering about is ideas that can be "composed" but
> that don't seem to fit the idea of "category", because they don't obey
> the associativity law.

> Say you created a type called "Component" (C for short), the idea being
> to compose Components out of other Components. Every C has zero or more
> connectors on it. Two Cs can be connected to form a new C using some
> kind of composition operator (say, <.>), provided there are enough
> connectors (one on each).

Categories contain two things:
"objects"
and "arrows" that connect objects.  Some important things about arrows:
 - for any object x there must be an identity id : x -> x
 - any two compatible arrows must compose in one and only one way:
   f : x -> y & g : y -> z  =>  g . f : x -> z
 - composition must be associative (f . g) . h = f . (g . h)
   when the arrows fit together.

Of course for any category there is a dual category,
so what I'm about to say doesn't really make sense,
but there's sense in it somewhere:  the things you are
trying to hook together with your <.> operator seem to me more
like objects than arrows, and it does not seem as if
they hook together in one and only one way, so it's not so
much _associativity_ being broken, as the idea of <.> being
a composition in the first place.



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


[Haskell-cafe] category design approach for inconvenient concepts

2012-12-17 Thread Christopher Howard
Recently I read this article I happened across, about the categorical
design pattern:

http://www.haskellforall.com/2012/08/the-category-design-pattern.html

Barely understood it, of course, but it was a rather intriguing concept.
So now I'm looking at all my programming problems trying to make types
that can be composed and that seem to fit the idea of a "category".

However, what I'm wondering about is ideas that can be "composed" but
that don't seem to fit the idea of "category", because they don't obey
the associativity law. To give a specific example (pseudo code like,
without any idea here of implementation or proper syntax):

Say you created a type called "Component" (C for short), the idea being
to compose Components out of other Components. Every C has zero or more
connectors on it. Two Cs can be connected to form a new C using some
kind of composition operator (say, <.>), provided there are enough
connectors (one on each). Presumably you would need a "Fail" constructor
of some kind to represent the situation when there is not enough connectors.

Say you had a C (coupler) with two connectors, a C (thing) with one
connector, and a C (gadget) with one connector.

So you could have...

(coupler <.> thing) <.> gadget

Because the coupler and the thing would combine to create a component
with one spare connector. This would then combine with the gadget to
make the final component. However, if you did...

coupler <.> (thing <.> gadget)

Then thing and gadget combine to make a component with no spare
connectors. And so the new component and the coupler then fail to
combine. Associativity law broken.

So, can I adjust my idea to fit the "category" concept? Or is it just
not applicable here? Or am I just misunderstanding the whole concept?

-- 
frigidcode.com



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe