Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-04-05 Thread Paul Liu
On Thu, Apr 5, 2012 at 4:30 AM, Ertugrul Söylemez e...@ertes.de wrote:
 Paul Liu nine...@gmail.com wrote:

  This isn't switching.  It's selection.  If fullTime decides to be
  productive, then alterTime acts like fullTime.  Otherwise it acts
  like halfTime.  If both inhibit, then alterTime inhibits.  This
  allows for a much more algebraic description of reactive systems.

 AFRP can do this through ArrowChoice. Maybe you can explain the
 concept of inhibition in more detail?

 I fail to grasp why this is making switches obsolete. The idea of
 switch is to completely abandoning the old state. See the broken
 pendulum example.

 Some of this can be done through ArrowChoice.  The difference is
 comparable to why server parts form a monoid in Happstack.  You don't
 have to decide when a server part reaches a request.  You let the server
 part decide itself.  In other words ArrowChoice forces you to deal with
 events in the application itself:

    -- Library code:
    x = x'
    y = y'

    -- Application code:
    proc inp - do
        r - request - ()
        if p r
          then x - inp
          else y - inp

 Signal inhibition allows the component wires themselves to deal with the
 events and you as the higher level programmer to just stick the wires
 together:

    -- Library code:
    x = proc inp - do requireReq - (); x' - inp
    y = y'

    -- Application code:
    x | y

I'm curious as to how this plays out with the usual arrow
compositions. How does x *** y behave when x inhibits? what about z
 x?

This cannot replace switching though, since the structure of your
arrows cannot change dynamically, while with switches it can.

-- 
Regards,
Paul Liu

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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-04-04 Thread Paul Liu
On Sun, Apr 1, 2012 at 7:03 PM, Ertugrul Söylemez e...@ertes.de wrote:
 No, Netwire does things very differently.  Note the total absence of
 switching combinators.  Where in traditional FRP and regular AFRP you
 have events and switching in Netwire you have signal inhibition and
 selection.  AFRP is really just changes the theory to establish some
 invariants.  Netwire changes the whole paradigm.  Review alterTime as
 expressed in the Netwire framework:

    alterTime = fullTime | halfTime

 This isn't switching.  It's selection.  If fullTime decides to be
 productive, then alterTime acts like fullTime.  Otherwise it acts like
 halfTime.  If both inhibit, then alterTime inhibits.  This allows for a
 much more algebraic description of reactive systems.

AFRP can do this through ArrowChoice. Maybe you can explain the
concept of inhibition in more detail?

I fail to grasp why this is making switches obsolete. The idea of
switch is to completely abandoning the old state. See the broken
pendulum example.

-- 
Regards,
Paul Liu

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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-04-04 Thread Edward Amsden
Ertugrul,

Do you have a conceptual writeup of Netwire anywhere? The only
documentation I've found are the API docs. I ask both out of
curiousity, and because I'm writing up background for a masters thesis
on FRP and I'd like to say something about Netwire.

2012/4/4 Paul Liu nine...@gmail.com:
 On Sun, Apr 1, 2012 at 7:03 PM, Ertugrul Söylemez e...@ertes.de wrote:
 No, Netwire does things very differently.  Note the total absence of
 switching combinators.  Where in traditional FRP and regular AFRP you
 have events and switching in Netwire you have signal inhibition and
 selection.  AFRP is really just changes the theory to establish some
 invariants.  Netwire changes the whole paradigm.  Review alterTime as
 expressed in the Netwire framework:

    alterTime = fullTime | halfTime

 This isn't switching.  It's selection.  If fullTime decides to be
 productive, then alterTime acts like fullTime.  Otherwise it acts like
 halfTime.  If both inhibit, then alterTime inhibits.  This allows for a
 much more algebraic description of reactive systems.

 AFRP can do this through ArrowChoice. Maybe you can explain the
 concept of inhibition in more detail?

 I fail to grasp why this is making switches obsolete. The idea of
 switch is to completely abandoning the old state. See the broken
 pendulum example.

 --
 Regards,
 Paul Liu

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



-- 
Edward Amsden
Student
Computer Science
Rochester Institute of Technology
www.edwardamsden.com

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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-04-02 Thread Peter Minten
On Mon, 2012-04-02 at 04:03 +0200, Ertugrul Söylemez wrote:
 Peter Minten peter.min...@orange.nl wrote:
  As I see FRP it has three components: the basic concepts, the
  underlying theory and the way the libraries actually work.
 
  As far as I understand FRP (which is not very far at all) the basic
  concepts can, simplified, be formulated as:
 
  * There are things which have a different value depending on when you
  look at them. (behaviors)
 
 That's already specific to traditional FRP.  In AFRP the value mutates.
 It's not a function of some notion of time.  It is similar to a list.
 That list contains the current value as well as a description of the
 future of the value:
 
 newtype SF a b = SF (a - (b, SF a b))
 
 The current value and the future depend on a momentary input value of
 type 'a' (which usually comes from another SF).

I think I understand what you're saying now. Basically instead of
behaviors netwire has signal functions which are basically the same idea
as simplified conduits/enumeratees. When you step (run) a signal
function you get two things: an output value and a replacement for the
signal function. Because the signal functions can be replaced a system
of signal functions can change between steps.

Netwire doesn't actually have a notion of time as such. If you need to
know the current time you'll have to supply that yourself. Wires also
don't run continuously, only when stepped explicitly. Where in
traditional FRP you (in some libraries) could ask for the value of a
behavior at any time in netwire you can only get the equivalent value
(the output value of a signal function) by stepping.

The big difference between netwire and traditional AFRP libraries are
ArrowChoice instances which allow if-then-else and case constructions in
proc notation. This simplifies programming greatly as it requires less
thinking in FRP terms.

When you say Event a b = SF a (Maybe b) you're basically saying that
for netwire events are the same thing as behaviors: they're both signal
functions. Events can be expressed as signal functions that sometimes
have a value. If they have a value during a step the event occurs during
that step.

The whole system is very discrete, time isn't a primitive at all. If
time plays a role it's just as an input, it's not built into something.
To get something return 1 but from second 10 onward return 2 you pass
time as an input and once you see that the time is greater than 10 you
can change the signal function to arr (const 2) to fix it to return 2,
whatever the new time is.

Greetings,

Peter Minten


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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-04-01 Thread Heinrich Apfelmus

Peter Minten wrote:


The updated document, which now lives at
http://www.haskell.org/haskellwiki/FRP_explanation_using_reactive-banana
contains a Making the example runnable section which shows how connect
the example with the outside world.


I have added a link from the reactive-banana project homepage. Thanks 
for your great explanation!



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-04-01 Thread Michael Snoyman
On Sat, Mar 31, 2012 at 7:15 PM, Peter Minten peter.min...@orange.nl wrote:
 On Fri, 2012-03-30 at 09:15 +0300, Michael Snoyman wrote:

 First you state that we shouldn't use `union` for the `ePitch` Event,
 and then you used it for `bOctave`. Would it be more efficient to
 implement bOctave as someting like:

     eOctave :: Event t (Int - Int)
     eOctave =
         filterJust toStep $ eKey
       where
         toStep '+' = Just (+ 1)
         toStep '-' = Just (subtract 1)
         toStep _ = Nothing

     bOctave :: Behavior t Octave
     bOctave = accumB 0 eOctave

 Yes. Though it's slightly less bad, the case with ePitch was something
 like 6 appends. It was mostly a case of badly copying the style from the
 examples and not realizing the examples use event streams from different
 outside sources. I've adapted the example to use something similar to
 your eOctave.

 Also, I'm left wondering: how would you create a new event stream in
 the first place? You're telling us to just rely on `eKey`, which is
 fair, but a great follow-up would demonstrate building it. Looking
 through the docs I found `newEvent`, but I'm not quite certain how I
 would combine it all together.

 The updated document, which now lives at
 http://www.haskell.org/haskellwiki/FRP_explanation_using_reactive-banana
 contains a Making the example runnable section which shows how connect
 the example with the outside world.

 The short version, regarding the creation of new events, is that you
 have to do it in two parts. You need newAddHandler in the IO monad to
 get a (a - IO ()) function that fires the event as well as something
 called an AddHandler and fromAddHandler in the NetworkDescription monad
 to get an event from that AddHandler. It's not possible to get values
 out of the NetworkDescription monad (without IORef tricks) and events
 can only be created within a NetworkDescription monad.

 The newEvent function looks like what you'd want, but because you can't
 get the event firing function out of NetworkDescription its use is
 limited.

 Greetings,

 Peter Minten


This looks great, thanks.

Michael

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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-04-01 Thread Peter Minten
On Fri, 2012-03-30 at 02:30 +0200, Ertugrul Söylemez wrote:
 Peter Minten peter.min...@orange.nl wrote:
 
  I've been trying to get my head around Functional Reactive Programming
  by writing a basic explanation of it, following the logic that
  explaining something is the best way to understand it.
 
  Am I on the right track with this explanation?
 
 You are explaining a particular instance of FRP.  Functional reactive
 programming is not a single concept, but a whole family of them.
 Traditional FRP as implemented by reactive-banana (and older libraries
 like Elerea, Fran and Reactive) is based on behaviors and events.  It
 uses the notion of a time-dependent value in a direct fashion.
 Conceptionally traditional FRP is this:
 
 Behavior a = Time - a
 Event a= [(Time, a)]
 
 -- The current time at even seconds and half the current time at odd
 -- seconds:
 
 alterTime = fullTime
 fullTime = switch (after 1) currentTime halfTime
 halfTime = switch (after 1) (fmap (/ 2) currentTime) fullTime
 
 There is a second instance of FRP though called AFRP.  The A stands for
 arrowized, but in modern times I prefer to think of it as
 applicative.  The underlying control structure is now a category and
 the concept of a time-varying value is changed to a time-varying
 function (called signal function (SF)), which is just an automaton and
 there is an arrow for it.  This simplifies implementation, makes code
 more flexible and performance more predictable.  The libraries Animas
 and Yampa implement this concept (Animas is a fork of Yampa).
 Conceptionally:
 
 SF a b= a - (b, SF a b)
 Event a b = SF a (Maybe b)
 
 alterTime = fullTime
 fullTime = switch (after 1) currentTime halfTime
 halfTime = switch (after 1) ((/ 2) ^ currentTime) fullTime

Sorry, I don't understand this. Would it be correct to say that AFRP
shares the basic ideas of FRP in that it has behaviors and
events/signals and that the main difference comes from the way AFRP is
implemented?

As I see FRP it has three components: the basic concepts, the underlying
theory and the way the libraries actually work.

As far as I understand FRP (which is not very far at all) the basic
concepts can, simplified, be formulated as:

* There are things which have a different value depending on when you
look at them. (behaviors)
* It is possible to express that something has occured at a certain
point in time. (events/signals)
* Behaviors can change in response to events/signals.
* A behavior's value may be different on different points in time even
if no event has come in.

Normal FRP theory expresses behaviors as Time - a and events as
[(Time,a)]. AFRP uses some kind of signal function to express
behaviors, or behaviors are signal functions and those functions
interact with events. Anyway AFRP uses a completely different
theoretical way of thinking about events and behaviors.

The reactive-banana library uses some internal representation which
exposes an API using applicative functors. The theory behind it, as
shown in the haddock comments, is Normal FRP.

The reactive library uses monads and not just applicative functors. It
uses the Normal FRP style.

Yampa/Animas use arrows and have a different underpinning in math.
However the basic concepts of FRP are shared with all the other
libraries.

Netwire also uses AFRP but extends the theory with something called
signal inhibition. Like everything else it shares the basic concepts of
FRP.

FRP concepts - FRP- reactive
   - reactive-banana
 - AFRP   - Yampa
   - Animas
 - wired AFRP - Netwire

Is this a correct way to summarize the differences?

Greetings,

Peter Minten


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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-04-01 Thread Ertugrul Söylemez
Peter Minten peter.min...@orange.nl wrote:

 Sorry, I don't understand this. Would it be correct to say that AFRP
 shares the basic ideas of FRP in that it has behaviors and
 events/signals and that the main difference comes from the way AFRP is
 implemented?

Well, FRP is usually interpreted as dealing with time-varying values.
The main selling point of FRP is the ability to combine those values
like ordinary ones and let them react to events.

AFRP offers the same functionality, but the underlying idea is
different.  To the user the difference becomes apparent when combining
those special values (whatever you call them, I always thought
behavior is a bad name).  Also the values can implement certain
semantics which would be impossible in the traditional concept, like a
frame counter.


 As I see FRP it has three components: the basic concepts, the
 underlying theory and the way the libraries actually work.

 As far as I understand FRP (which is not very far at all) the basic
 concepts can, simplified, be formulated as:

 * There are things which have a different value depending on when you
 look at them. (behaviors)

That's already specific to traditional FRP.  In AFRP the value mutates.
It's not a function of some notion of time.  It is similar to a list.
That list contains the current value as well as a description of the
future of the value:

newtype SF a b = SF (a - (b, SF a b))

The current value and the future depend on a momentary input value of
type 'a' (which usually comes from another SF).


 Normal FRP theory expresses behaviors as Time - a and events as
 [(Time,a)]. AFRP uses some kind of signal function to express
 behaviors, or behaviors are signal functions and those functions
 interact with events. Anyway AFRP uses a completely different
 theoretical way of thinking about events and behaviors.

A behavior from traditional FRP is a special case of a signal function.
It's a 'stateless' signal function, i.e. one that never mutates.  In
both cases you would use switching combinators to react to events.


 Netwire also uses AFRP but extends the theory with something called
 signal inhibition. Like everything else it shares the basic concepts
 of FRP.

No, Netwire does things very differently.  Note the total absence of
switching combinators.  Where in traditional FRP and regular AFRP you
have events and switching in Netwire you have signal inhibition and
selection.  AFRP is really just changes the theory to establish some
invariants.  Netwire changes the whole paradigm.  Review alterTime as
expressed in the Netwire framework:

alterTime = fullTime | halfTime

This isn't switching.  It's selection.  If fullTime decides to be
productive, then alterTime acts like fullTime.  Otherwise it acts like
halfTime.  If both inhibit, then alterTime inhibits.  This allows for a
much more algebraic description of reactive systems.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-03-31 Thread Peter Minten
On Fri, 2012-03-30 at 09:15 +0300, Michael Snoyman wrote:

 First you state that we shouldn't use `union` for the `ePitch` Event,
 and then you used it for `bOctave`. Would it be more efficient to
 implement bOctave as someting like:
 
 eOctave :: Event t (Int - Int)
 eOctave =
 filterJust toStep $ eKey
   where
 toStep '+' = Just (+ 1)
 toStep '-' = Just (subtract 1)
 toStep _ = Nothing
 
 bOctave :: Behavior t Octave
 bOctave = accumB 0 eOctave

Yes. Though it's slightly less bad, the case with ePitch was something
like 6 appends. It was mostly a case of badly copying the style from the
examples and not realizing the examples use event streams from different
outside sources. I've adapted the example to use something similar to
your eOctave.

 Also, I'm left wondering: how would you create a new event stream in
 the first place? You're telling us to just rely on `eKey`, which is
 fair, but a great follow-up would demonstrate building it. Looking
 through the docs I found `newEvent`, but I'm not quite certain how I
 would combine it all together.

The updated document, which now lives at
http://www.haskell.org/haskellwiki/FRP_explanation_using_reactive-banana
contains a Making the example runnable section which shows how connect
the example with the outside world.

The short version, regarding the creation of new events, is that you
have to do it in two parts. You need newAddHandler in the IO monad to
get a (a - IO ()) function that fires the event as well as something
called an AddHandler and fromAddHandler in the NetworkDescription monad
to get an event from that AddHandler. It's not possible to get values
out of the NetworkDescription monad (without IORef tricks) and events
can only be created within a NetworkDescription monad.

The newEvent function looks like what you'd want, but because you can't
get the event firing function out of NetworkDescription its use is
limited.

Greetings,

Peter Minten


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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-03-30 Thread Michael Snoyman
On Thu, Mar 29, 2012 at 7:15 PM, Peter Minten peter.min...@orange.nl wrote:
 Hi,

 I've been trying to get my head around Functional Reactive Programming
 by writing a basic explanation of it, following the logic that
 explaining something is the best way to understand it.

 Am I on the right track with this explanation?

Hi Peter,

I'm no expert on FRP (in fact, I'm just trying to understand it), so I
can't speak to the technical accuracy of your post. However, I think
you're absolutely on the right track as far as explaining what FRP is.
I think you've done a great job of explaining things from the ground
up. Thank you! I just had a few questions.

First you state that we shouldn't use `union` for the `ePitch` Event,
and then you used it for `bOctave`. Would it be more efficient to
implement bOctave as someting like:

eOctave :: Event t (Int - Int)
eOctave =
filterJust toStep $ eKey
  where
toStep '+' = Just (+ 1)
toStep '-' = Just (subtract 1)
toStep _ = Nothing

bOctave :: Behavior t Octave
bOctave = accumB 0 eOctave

Also, I'm left wondering: how would you create a new event stream in
the first place? You're telling us to just rely on `eKey`, which is
fair, but a great follow-up would demonstrate building it. Looking
through the docs I found `newEvent`, but I'm not quite certain how I
would combine it all together.

Thanks again for writing this up.

Michael

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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-03-30 Thread Heinrich Apfelmus

Peter Minten wrote:


I've been trying to get my head around Functional Reactive Programming
by writing a basic explanation of it, following the logic that
explaining something is the best way to understand it.

Am I on the right track with this explanation?


I think so. Your explanation looks fine to me, except for one really 
subtle but really important issue:



Stepped sounds a lot like stepper and we can create that function by
making a few small adjustments.

type Time = Int
stepper :: a - [(Time, a)] - (Time - a)
stepper d es = \t - case takeWhile (\(t', _) - t' = t) es of
[] - d
xs - snd (last xs)


The correct definition of  stepper  usesinstead of  =

... case takeWhile (\(t', _) - t'  t) es of ...

In other words, at the moment  t == t' , the behavior still returns the 
old value, not the new value from the event. This important because 
it allows for recursive definitions, like


let b = accumB 1 e
e = (+) $ b @ eKey

If you were to use  =  here, then the new value of the behavior would 
depend on itself and the result would be undefined.


(Actually, even if you use the correct definition for  stepper,  trying 
to implement Event and Behavior in terms of  [(Time,a)]  and  Time - a 
 in Haskell would give undefined on this recursive example. That's 
because the data types still aren't lazy enough, you have to use another 
model. That's one reason why implementing FRP has traditionally been hard.)




P.S. Sorry about the long mail, the explanation ended up a little longer
than I originally expected. :)


I know it was time to get a blog when my mailing list posts got too long. ;)


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-03-30 Thread Heinrich Apfelmus

Michael Snoyman wrote:

First you state that we shouldn't use `union` for the `ePitch` Event,
and then you used it for `bOctave`. Would it be more efficient to
implement bOctave as someting like:

eOctave :: Event t (Int - Int)
eOctave =
filterJust toStep $ eKey
  where
toStep '+' = Just (+ 1)
toStep '-' = Just (subtract 1)
toStep _ = Nothing

bOctave :: Behavior t Octave
bOctave = accumB 0 eOctave


It's largely a matter of efficiency in notation rather than efficiency 
in run-time.



Also, I'm left wondering: how would you create a new event stream in
the first place? You're telling us to just rely on `eKey`, which is
fair, but a great follow-up would demonstrate building it. Looking
through the docs I found `newEvent`, but I'm not quite certain how I
would combine it all together.


It's best to look at the example for that and peruse the documentation 
in  Reactive.Banana.Frameworks  in case something is unclear.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: [Haskell-cafe] Is this a correct explanation of FRP?

2012-03-29 Thread Ertugrul Söylemez
Peter Minten peter.min...@orange.nl wrote:

 I've been trying to get my head around Functional Reactive Programming
 by writing a basic explanation of it, following the logic that
 explaining something is the best way to understand it.

 Am I on the right track with this explanation?

You are explaining a particular instance of FRP.  Functional reactive
programming is not a single concept, but a whole family of them.
Traditional FRP as implemented by reactive-banana (and older libraries
like Elerea, Fran and Reactive) is based on behaviors and events.  It
uses the notion of a time-dependent value in a direct fashion.
Conceptionally traditional FRP is this:

Behavior a = Time - a
Event a= [(Time, a)]

-- The current time at even seconds and half the current time at odd
-- seconds:

alterTime = fullTime
fullTime = switch (after 1) currentTime halfTime
halfTime = switch (after 1) (fmap (/ 2) currentTime) fullTime

There is a second instance of FRP though called AFRP.  The A stands for
arrowized, but in modern times I prefer to think of it as
applicative.  The underlying control structure is now a category and
the concept of a time-varying value is changed to a time-varying
function (called signal function (SF)), which is just an automaton and
there is an arrow for it.  This simplifies implementation, makes code
more flexible and performance more predictable.  The libraries Animas
and Yampa implement this concept (Animas is a fork of Yampa).
Conceptionally:

SF a b= a - (b, SF a b)
Event a b = SF a (Maybe b)

alterTime = fullTime
fullTime = switch (after 1) currentTime halfTime
halfTime = switch (after 1) ((/ 2) ^ currentTime) fullTime

Now both the predefined event function 'after' and the predefined signal
'currentTime' are signal functions.  It also allows to implement some
analysis tools easily:

-- Emit an event whenever the given signal function's output
-- changes:

changesOf :: (Eq b) = SF a b - SF a (Maybe b)

Finally there is an extension of AFRP of which I'm the proud
inventor. =) By generalizing the automaton arrow to allow what I call
signal inhibition you get to the wire arrow.  This adds another layer of
flexibility, unifies the notions of time-varying functions and events
and completely removes the need for switching.  Events can now be
handled implicitly.  The library Netwire implements this concept.
Conceptionally:

Wire a b  = a - (Maybe b, Wire a b)
Event = Wire

changesOf :: (Eq b) = Wire a b - Wire a b

alterTime = fullTime | halfTime
fullTime = when (even . floor) . time
halfTime = fmap (/ 2) time


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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