Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Issue installing  reactive-banana-5.0.0.1 (Heinrich Apfelmus)


----------------------------------------------------------------------

Message: 1
Date: Mon, 07 May 2012 14:12:50 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: Re: [Haskell-beginners] Issue installing
        reactive-banana-5.0.0.1
To: beginners@haskell.org
Message-ID: <jo8e82$pfo$1...@dough.gmane.org>
Content-Type: text/plain; charset=UTF-8; format=flowed

Miguel Negrao wrote:
> A 06/05/2012, ?s 14:31, Heinrich Apfelmus escreveu:
>> Ah, ok, then I don't understand your specification.
>>
>> Could you give a specification in terms of a simple list transformation
>>
>>  example :: [Double] -> [Double]
>>
>> ? All list functions are allowed, we can then transform it into a
> > style that uses only the combinators available in reactive-banana.
> 
> Ok, this should demonstrate an example of what I mean:
> 
> module Main where
> 
> main :: IO()
> main = print $ test [0.9,0.1,0.2,0.8]
> --should output [0.9,0.1,0.8,0.8]
> 
> test :: [Double]->[Double]
> test (x:xs) = x : test1 xs x
> test [] = []
> 
> test1:: [Double]->Double->[Double]
> test1 (x:xs) lastValue = let
>       y = if lastValue>=0.8 then x else 1.0-x
>       in if (y<=0.2) || (y>=0.8) then y : test1 xs y else test1 xs lastValue
> test1 [] _ = []   

You can reformulate this function in terms of the  mapAccum  combinators 
from Data.List. Once you have done this, you can easily adapt it to the 
  mapAccum  combinator from reactive-banana.

   test :: Event t Double -> Event t Double
   test e = filterJust $ fst $ mapAccum Nothing $ next <$> e
       where
       next x Nothing          = (Just x, Just x)
       next x (Just lastValue) =
           let y = if lastValue>=0.8 then x else 1.0-x
           in if (y<=0.2) || (y>=0.8)
               then (Just y , Just y)
               else (Nothing, Just lastValue)


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com




------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 47, Issue 9
****************************************

Reply via email to