Re: How can I implement this arrow? Thanks

2003-09-17 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>,
 Derek Elkins <[EMAIL PROTECTED]> wrote:

> It's not an arrow the way Yu Di wanted it, but it is an arrow.  Which
> arrow it is was part of my point in the latter paragraphs.

Oh yes, you're right. For some reason I wasn't thinking of the String as 
state.

-- 
Ashley Yakeley, Seattle WA

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


Re: How can I implement this arrow? Thanks

2003-09-17 Thread Derek Elkins
On Tue, 16 Sep 2003 23:28:43 -0700
Ashley Yakeley <[EMAIL PROTECTED]> wrote:

> In article <[EMAIL PROTECTED]>,
>  Derek Elkins <[EMAIL PROTECTED]> wrote:
> 
> > > I don't think this type is an arrow. For a "product arrow", i.e.
> > > an instance of Hughes' "Arrow" class with "first" defined, you can
> > > define this:
> > 
> > Oh, it's definitely an arrow.
> 
> I don't think you can make it an instance of Hughes' Arrow without
> some function for combining Strings.

It's not an arrow the way Yu Di wanted it, but it is an arrow.  Which
arrow it is was part of my point in the latter paragraphs.

Here's the StateFunctor from Hughes' paper:
type StateFunctor s a b c = a (b,s) (c,s)

Using String for s and (->) for a we get:
type StringStateArrow b c = (b,String) -> (c,String)

alternatively, looking at the Kleisli arrow with m being the State monad
we get:
type Kleisli m a b = a -> m b
type StateM s a = s -> (a,s)
type StateA s a b = Kleisli (StateM s) a b
type StateA s a b = a -> s -> (b,s)
type StateA s a b = (a,s) -> (b,s)
type StringState a b = (a,String) -> (b,String)

or, if we do combine Strings we get something like the Writer monad:
type Monoid m => WriterM m a = (a,m)
type Monoid m => WriterA m a b = Kleisli (WriteM m) a b
type Monoid m => WriterA m a b = a -> (b,m)
type StringWriterA a b = a -> (b,String)
where mempty = [] and mappend = (++)

In either of these cases, there is not much reason to use an arrow over
a monad if it's the only arrow you are using and there are reasonable
reasons to use a monad over an arrow.  Neither of these do what Yu Di
apparently wanted.  In the more recent post by Yu Di, an arrow or monad
looks more appropriate, though for different reasons and in a different
way, which just goes to show that when posting one should state what
the ultimate goal is.

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


Re: How can I implement this arrow? Thanks

2003-09-16 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>,
 Derek Elkins <[EMAIL PROTECTED]> wrote:

> > I don't think this type is an arrow. For a "product arrow", i.e. an 
> > instance of Hughes' "Arrow" class with "first" defined, you can define
> > this:
> 
> Oh, it's definitely an arrow.

I don't think you can make it an instance of Hughes' Arrow without some 
function for combining Strings.

-- 
Ashley Yakeley, Seattle WA

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


Re: How can I implement this arrow? Thanks

2003-09-16 Thread Ross Paterson
On Tue, Sep 16, 2003 at 02:32:48PM -0500, Yu Di wrote:
> What I am trying to do is to use Haskell to simulate some process, and 
> meanwhile collecting information about the data-flow throughout the whole 
> process into the output. The (String, a) example is just a simplified 
> version of that. Thanks for pointing out my mistakes, I will try to do it 
> as a decorated-data combinator.

This sounds a bit like the example in

http://www.soi.city.ac.uk/~ross/talks/fop.4.ps.gz

The idea is to define your network as a generic arrow, and instantiate
it differently for different interpretations.  For simulation, one
can use Stream i -> Stream o, though there are other possibilities.
To get a map, you use a state transformer (with the map as the state),
and pass edge labels through the arrows.

I think the reason you're getting in a tangle is that you're trying to
do both with the same interpretation.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: How can I implement this arrow? Thanks

2003-09-16 Thread Derek Elkins
On Tue, 16 Sep 2003 14:32:48 -0500
"Yu Di" <[EMAIL PROTECTED]> wrote:

> What I am trying to do is to use Haskell to simulate some process, and
> meanwhile collecting information about the data-flow throughout the
> whole process into the output. The (String, a) example is just a
> simplified version of that. Thanks for pointing out my mistakes, I
> will try to do it as a decorated-data combinator.
> 
> Thanks again,

If all you want to do is trace the execution of some computation, you
can use the Writer/Output monad.  This will associate the outputting
with the functions that process the simulation.  It looks something
like,
foo a b = do
tell ("Entering foo with "++show a++" "++show b)
doStuff a
someMoreStuff b
tell "Leaving foo"

You can write things other than strings.

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


Re: How can I implement this arrow? Thanks

2003-09-16 Thread Yu Di
What I am trying to do is to use Haskell to simulate some process, and 
meanwhile collecting information about the data-flow throughout the whole 
process into the output. The (String, a) example is just a simplified 
version of that. Thanks for pointing out my mistakes, I will try to do it as 
a decorated-data combinator.

Thanks again,

Di, Yu
9.16
From: Derek Elkins <[EMAIL PROTECTED]>
To: Yu Di <[EMAIL PROTECTED]>
CC: [EMAIL PROTECTED], Ashley Yakeley <[EMAIL PROTECTED]>
Subject: Re: How can I implement this arrow? Thanks
Date: Tue, 16 Sep 2003 12:24:17 -0400
On Tue, 16 Sep 2003 01:52:03 -0700
Ashley Yakeley <[EMAIL PROTECTED]> wrote:
> In article <[EMAIL PROTECTED]>,
>  "Yu Di" <[EMAIL PROTECTED]> wrote:
Replying to both:

> > Hi, I want to create an arrow which is essentially
> >
> > data MyArrow a b = MyArrow ((String, a) -> (String,b))
>
> I don't think this type is an arrow. For a "product arrow", i.e. an
> instance of Hughes' "Arrow" class with "first" defined, you can define
> this:
Oh, it's definitely an arrow.

> > i.e. there is an "information" asscioated with each piece of data
> > (represented by the string),
So make a data type that sticks together something and it's information.

> > and I want to pass it around.

What's wrong with the support Haskell already has for passing around
things?  Why do you think you need an arrow?
From how you read the meaning of the MyArrow type, you are apparently
misunderstanding what arrows are.  Arrows generalize functions.
As such things of arrow type are intuitively transformers and the arrow
framework standardizes how to stick transformations together to make a
larger transformation. The things in an arrow's representation are
what's required for the implementations of the transformations.
Therefore, things in an arrows representation are, in a sense, "owned"
by the arrow computation. This is evidenced by a) arrows have a fully
polymorphic type, they place no restrictions on their input; within the
computation, the String in MyArrow is not even visible let alone
required to be provided, and b) the above arrow is the State arrow
specialized to Strings. The String is the state and is owned by the
computation. You are having trouble defining 'first' as you'd like
because what you want is to duplicate the state of the
computation. -The- (there is only one at any time) String being passed
around isn't associated with the objects.
From the sounds of it you simply want a combinator library that operates
on some decorated data.  A monad or arrow may be useful to support
that, e.g. the environment monad, but a monad/arrow isn't that.  You
haven't really given much detail to what you're ultimately trying to
achieve so I can't really provide much advice.
_
Use custom emotions -- try MSN Messenger 6.0! 
http://www.msnmessenger-download.com/tracking/reach_emoticon

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


Re: How can I implement this arrow? Thanks

2003-09-16 Thread Derek Elkins
On Tue, 16 Sep 2003 01:52:03 -0700
Ashley Yakeley <[EMAIL PROTECTED]> wrote:

> In article <[EMAIL PROTECTED]>,
>  "Yu Di" <[EMAIL PROTECTED]> wrote:

Replying to both:

> > Hi, I want to create an arrow which is essentially
> > 
> > data MyArrow a b = MyArrow ((String, a) -> (String,b))
> 
> I don't think this type is an arrow. For a "product arrow", i.e. an 
> instance of Hughes' "Arrow" class with "first" defined, you can define
> this:

Oh, it's definitely an arrow.

> > i.e. there is an "information" asscioated with each piece of data 
> > (represented by the string), 

So make a data type that sticks together something and it's information.

> > and I want to pass it around. 

What's wrong with the support Haskell already has for passing around
things?  Why do you think you need an arrow?

>From how you read the meaning of the MyArrow type, you are apparently
misunderstanding what arrows are.  Arrows generalize functions. 
As such things of arrow type are intuitively transformers and the arrow
framework standardizes how to stick transformations together to make a
larger transformation. The things in an arrow's representation are
what's required for the implementations of the transformations.
Therefore, things in an arrows representation are, in a sense, "owned"
by the arrow computation. This is evidenced by a) arrows have a fully
polymorphic type, they place no restrictions on their input; within the
computation, the String in MyArrow is not even visible let alone
required to be provided, and b) the above arrow is the State arrow
specialized to Strings. The String is the state and is owned by the
computation. You are having trouble defining 'first' as you'd like
because what you want is to duplicate the state of the
computation. -The- (there is only one at any time) String being passed
around isn't associated with the objects.

>From the sounds of it you simply want a combinator library that operates
on some decorated data.  A monad or arrow may be useful to support
that, e.g. the environment monad, but a monad/arrow isn't that.  You
haven't really given much detail to what you're ultimately trying to
achieve so I can't really provide much advice.

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


Re: How can I implement this arrow? Thanks

2003-09-16 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>,
 "Yu Di" <[EMAIL PROTECTED]> wrote:

> Hi, I want to create an arrow which is essentially
> 
> data MyArrow a b = MyArrow ((String, a) -> (String,b))

I don't think this type is an arrow. For a "product arrow", i.e. an 
instance of Hughes' "Arrow" class with "first" defined, you can define 
this:

  arrProduct :: arrow p q -> arrow p r -> arrow p (q,r);
  arrProduct apq apr =
arr (\p -> (p,p)) >>>
first apr >>>
arr (\(r,p) -> (p,r)) >>>
first apq;

This has a certain intuitive symmetry in its arguments, though for 
instance for a Kleisli arrow (a -> m b for some monad m), arrProduct 
will essentially execute one before the other. But if you try to define 
this directly for MyArrow, you'll find you need to pick one of the two 
Strings (losing information) or else combine them somehow. Perhaps this:

  arrProduct (MyArrow f1) (MyArrow f2) = MyArrow (\sa -> let
{
(s1,b1) <- f1 sa;
(s2,b2) <- f2 sa;
} in (s1 ++ s2,(b1,b2)));

In general, a type of the form (f a -> f b) is an arrow if f is a 
Functor that has one of these:

  fApply :: f (a -> b) -> f a -> f b;
  fProduct :: f a -> f b -> f (a,b);

I call this class of Functors "FunctorApply", but maybe someone has a 
better name. I'm not sure what the attached laws are, but I imagine 
they're fairly straightforward.

-- 
Ashley Yakeley, Seattle WA

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


Re: How can I implement this arrow? Thanks

2003-09-15 Thread Marc A. Ziegert
Am Dienstag 16 September 2003 04:57 schrieb Yu Di:
> Hi, I want to create an arrow which is essentially
> 
> data MyArrow a b = MyArrow ((String, a) -> (String,b))
> 
> i.e. there is an "information" asscioated with each piece of data 
> (represented by the string), and I want
> to pass it around. But I have a problem about how to define "pure" and 
> "first". At first, I declared
> 
> pure f = MyArrow (\(s, x) -> (s, f x))
> first (MyArrow f) = MyArrow (\(s, (x, y)) -> let (s', z) = f (s, x) in (s', 
> (z, y)))
> 
> this seems to work, but then I begin to have problems with the 
> "data-plumbing" pure arrows, e.g. in
> 
> pure (\x -> (x, x)) >>> first someArrow  pure (\(_, x) -> x)
> 
> Ideally, this arrow will preserve whatever information I put there for the 
> input, but because "first
> someArrow" will change the whole information associated with the pair of 
> result, I can't find any
> way to let "pure (\(_, x)->x)" (which is an extremely generic function) 
> retrieve the part of information for the second piece in the pair tuple.


what does the compiler say? or is it a runtime error?
how did you implement "(>>>) :: a b c -> a c d -> a b d"?

(MyArrow f1) >>> (MyArrow f2) = MyArrow (f2 . f1)

does this compile?:

(pure (\x -> (x, x)) :: MyArrow a (a,a)) >>> (first (someArrow :: MyArrow a b) :: 
MyArrow (a,a) (b,a)) >>> (pure (\(_, x) -> x) :: MyArrow (b,a) a)

pure and first seem to be correct.
but ... just as an (slow) alternative:

-- first :: a x fx -> a (x, y) (fx, y)
first (MyArrow f) = MyArrow $ (\((fs,fx),y)->(fs,(fx,y))) . (\(sx,y)->(f sx,y)) . 
(\(s,(x,y))->((s,x),y))




- marc


> 
> Of course I can create specialized arrows for the tasks \x -> (x, x) and 
> \(_, x) -> x which passes the information around, but this will become 
> tedious as I will have to define specialized arrows for a lot of similar 
> tasks one by one, and I won't be able to use the arrow pre-processor at all.
> 
> So how can I implement this? Thanks very much!
> 
> Di, Yu
> 9.15
> 
> _

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


How can I implement this arrow? Thanks

2003-09-15 Thread Yu Di
Hi, I want to create an arrow which is essentially

data MyArrow a b = MyArrow ((String, a) -> (String,b))

i.e. there is an "information" asscioated with each piece of data 
(represented by the string), and I want
to pass it around. But I have a problem about how to define "pure" and 
"first". At first, I declared

pure f = MyArrow (\(s, x) -> (s, f x))
first (MyArrow f) = MyArrow (\(s, (x, y)) -> let (s', z) = f (s, x) in (s', 
(z, y)))

this seems to work, but then I begin to have problems with the 
"data-plumbing" pure arrows, e.g. in

pure (\x -> (x, x)) >>> first someArrow  pure (\(_, x) -> x)

Ideally, this arrow will preserve whatever information I put there for the 
input, but because "first
someArrow" will change the whole information associated with the pair of 
result, I can't find any
way to let "pure (\(_, x)->x)" (which is an extremely generic function) 
retrieve the part of information for the second piece in the pair tuple.

Of course I can create specialized arrows for the tasks \x -> (x, x) and 
\(_, x) -> x which passes the information around, but this will become 
tedious as I will have to define specialized arrows for a lot of similar 
tasks one by one, and I won't be able to use the arrow pre-processor at all.

So how can I implement this? Thanks very much!

Di, Yu
9.15
_
Get 10MB of e-mail storage! Sign up for Hotmail Extra Storage.  
http://join.msn.com/?PAGE=features/es

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