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:  Implementing a Local Propagation Network
      (Patrick LeBoutillier)
   2. Re:  Implementing a Local Propagation Network
      (Stephen Blackheath [to Haskell-Beginners])
   3. Re:  lazy IO in readFile (Andrew Sackville-West)
   4. Re:  Implementing a Local Propagation Network
      (Patrick LeBoutillier)
   5. Re:  Help with slow algorithm (Diego Echeverri)


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

Message: 1
Date: Wed, 19 May 2010 15:12:40 -0400
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: Re: [Haskell-beginners] Implementing a Local Propagation
        Network
To: "Stephen Blackheath [to Haskell-Beginners]"
        <mutilating.cauliflowers.step...@blacksapphire.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktinvqh8zxotm6xizzgor76m8ocucps7mtbmku...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Stephen,

Thanks for the advice, finally I ended up using a State Monad and
names (String) as symbolic references.

Here is what I came up with: http://pastebin.com/gqkP2sWy

Here is some test code:

import LPN
import Control.Monad.State

testfc = snd $ runState fc networkMake

fc :: LPN ()
fc = do
  i:j:k:l:m:[] <- sequence $ map addWire ["i", "j", "k", "l", "m"]
  f <- addIO "Fahrenheit" i
  c <- addIO "Celsius" m
  addConstant "32" 32 j
  addConstant "5/9" (5/9) l
  addAdder "+" j k i
  addMultiplier "*" k l m
  input f 212

At first it felt kind of messy, but as I kept refactoring and pushing
stuff into the monad it became a lot cleaner and felt less heavy.
I learned a lot about the State Monad doing this.


Thanks,

Patrick



On Mon, May 17, 2010 at 10:41 PM, Stephen Blackheath [to
Haskell-Beginners] <mutilating.cauliflowers.step...@blacksapphire.com>
wrote:
> Patrick,
>
> If you want to implement it in a functional style, you have to use an
> association map of some sort.  Haskell only has values, but not any
> concept of a reference (unless you count things like IORef, but I am not
> counting those).  Generally speaking this is needed whenever you are
> dealing with a data structure that has cycles.  (Generally speaking
> because it's possible to make data structures lazily refer to themselves.)
>
> People usually use IntMap, but there's a new package EnumMap on Hackage
> which is really powerful.  It's like IntMap only typesafe.  You will
> need a counter in your data structure as a source of unique ids.  You
> can also use value-supply (from Hackage), which is a great bit of code.
>
> On the face of it, this seems cumbersome, but the way to do it is to
> create a data structure and access it through accessor functions like
> "add node", "delete node", "follow wire", etc.  This way you can
> abstract those details away.  People have done various directed/undirect
> graph packages and so on on Hackage - I can't recommend anything.
>
> Stick with it - this approach does work.  I've done things like
> conversion of 3D models into triangle strips using this method, with
> very satisfying results.
>
>
> Steve
>
> On 18/05/10 12:59, Patrick LeBoutillier wrote:
>> Hi all,
>>
>> After learning some Haskell recently, I decided to revisit a book
>> about functional programming techniques for Perl: Higher Order Perl. I
>> didn't fully understand the book at the time but now my Haskell
>> experience has proved to be very insightful.
>>
>> Towards the end of the book the author implements a local propagation 
>> network.
>>
>> Here is the Perl source code:
>> http://hop.perl.plover.com/Examples/Chap9/Local-Propagation/
>> The PDF of the specific chapter is here:
>> http://hop.perl.plover.com/book/pdf/09DeclarativeProgramming.pdf
>>
>> I would like to experiment with something similar in Haskell, but the
>> way this network is designed is all about state and references:
>>
>> - Wires have a values that can change over time;
>> - Wires have references to nodes;
>> - Nodes have references to wires;
>>
>> I'm a bit stuck as to how to approach the "object has a list
>> references to other objects" situation from Haskell. I tried this:
>>
>> type Name = String
>> data Node = Node Name [Wire]
>> data Wire = Wire Name Node Double [Node]
>>
>> But that doesn't seem like it would work since when I change a Wire I
>> must find all "copies" of it (in the Node objects) and update them
>> also. Perhaps I should just refer to Wires/Nodes by name and use an
>> association list to lookup them up, but that seems cumbersome.
>>
>> Anybody have any suggestions?
>>
>>
>> Thanks a lot,
>>
>> Patrick
>>
>>
>>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


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

Message: 2
Date: Thu, 20 May 2010 10:55:04 +1200
From: "Stephen Blackheath [to Haskell-Beginners]"
        <mutilating.cauliflowers.step...@blacksapphire.com>
Subject: Re: [Haskell-beginners] Implementing a Local Propagation
        Network
To: beginners@haskell.org
Message-ID: <4bf46c48.5010...@blacksapphire.com>
Content-Type: text/plain; charset=UTF-8

Patrick,

I think that looks like about the best way you could do it.  If I were
doing it, I would probably write it without the state monad, with all
the LPN ()'s becoming Network -> Network, and the code wouldn't be all
that different, except that 'multiplier' and 'adder' would become
slightly less readable.

If you did that, then in those cases (where your algorithm is described
by a sequence of modifications) you can say 'flip execState network $ do
...'.  Then all the 'revokeWire sum name's have to become 'modify $
revokeWire sum name'.

There's no particular reason why that's better - it's just style.  If
your main program is going to describe a whole lot of complex
transformations that happen in sequence, then your way would likely be
better than my suggested way.


Steve

On 20/05/10 07:12, Patrick LeBoutillier wrote:
> Stephen,
> 
> Thanks for the advice, finally I ended up using a State Monad and
> names (String) as symbolic references.
> 
> Here is what I came up with: http://pastebin.com/gqkP2sWy
> 
> Here is some test code:
> 
> import LPN
> import Control.Monad.State
> 
> testfc = snd $ runState fc networkMake
> 
> fc :: LPN ()
> fc = do
>   i:j:k:l:m:[] <- sequence $ map addWire ["i", "j", "k", "l", "m"]
>   f <- addIO "Fahrenheit" i
>   c <- addIO "Celsius" m
>   addConstant "32" 32 j
>   addConstant "5/9" (5/9) l
>   addAdder "+" j k i
>   addMultiplier "*" k l m
>   input f 212
> 
> At first it felt kind of messy, but as I kept refactoring and pushing
> stuff into the monad it became a lot cleaner and felt less heavy.
> I learned a lot about the State Monad doing this.
> 
> 
> Thanks,
> 
> Patrick
> 
> 
> 
> On Mon, May 17, 2010 at 10:41 PM, Stephen Blackheath [to
> Haskell-Beginners] <mutilating.cauliflowers.step...@blacksapphire.com>
> wrote:
>> Patrick,
>>
>> If you want to implement it in a functional style, you have to use an
>> association map of some sort.  Haskell only has values, but not any
>> concept of a reference (unless you count things like IORef, but I am not
>> counting those).  Generally speaking this is needed whenever you are
>> dealing with a data structure that has cycles.  (Generally speaking
>> because it's possible to make data structures lazily refer to themselves.)
>>
>> People usually use IntMap, but there's a new package EnumMap on Hackage
>> which is really powerful.  It's like IntMap only typesafe.  You will
>> need a counter in your data structure as a source of unique ids.  You
>> can also use value-supply (from Hackage), which is a great bit of code.
>>
>> On the face of it, this seems cumbersome, but the way to do it is to
>> create a data structure and access it through accessor functions like
>> "add node", "delete node", "follow wire", etc.  This way you can
>> abstract those details away.  People have done various directed/undirect
>> graph packages and so on on Hackage - I can't recommend anything.
>>
>> Stick with it - this approach does work.  I've done things like
>> conversion of 3D models into triangle strips using this method, with
>> very satisfying results.
>>
>>
>> Steve
>>
>> On 18/05/10 12:59, Patrick LeBoutillier wrote:
>>> Hi all,
>>>
>>> After learning some Haskell recently, I decided to revisit a book
>>> about functional programming techniques for Perl: Higher Order Perl. I
>>> didn't fully understand the book at the time but now my Haskell
>>> experience has proved to be very insightful.
>>>
>>> Towards the end of the book the author implements a local propagation 
>>> network.
>>>
>>> Here is the Perl source code:
>>> http://hop.perl.plover.com/Examples/Chap9/Local-Propagation/
>>> The PDF of the specific chapter is here:
>>> http://hop.perl.plover.com/book/pdf/09DeclarativeProgramming.pdf
>>>
>>> I would like to experiment with something similar in Haskell, but the
>>> way this network is designed is all about state and references:
>>>
>>> - Wires have a values that can change over time;
>>> - Wires have references to nodes;
>>> - Nodes have references to wires;
>>>
>>> I'm a bit stuck as to how to approach the "object has a list
>>> references to other objects" situation from Haskell. I tried this:
>>>
>>> type Name = String
>>> data Node = Node Name [Wire]
>>> data Wire = Wire Name Node Double [Node]
>>>
>>> But that doesn't seem like it would work since when I change a Wire I
>>> must find all "copies" of it (in the Node objects) and update them
>>> also. Perhaps I should just refer to Wires/Nodes by name and use an
>>> association list to lookup them up, but that seems cumbersome.
>>>
>>> Anybody have any suggestions?
>>>
>>>
>>> Thanks a lot,
>>>
>>> Patrick
>>>
>>>
>>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
> 
> 
> 


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

Message: 3
Date: Wed, 19 May 2010 18:17:31 -0700
From: Andrew Sackville-West <and...@swclan.homelinux.org>
Subject: Re: [Haskell-beginners] lazy IO in readFile
To: beginners@haskell.org
Message-ID: <20100520011731.gj2...@basement.swclan.homelinux.org>
Content-Type: text/plain; charset="us-ascii"

On Sun, May 16, 2010 at 11:03:03PM +1200, Stephen Blackheath [to 
Haskell-Beginners] wrote:
> Andrew,
> 
> On 15/05/10 11:57, Andrew Sackville-West wrote:
> > I'm having trouble determining how to put this into the existing
> > context of a string of filter's and maps where the contents of the
> > file are used in a predicate to a filter. (if you really want you can
> > look at my ridiculous code at
> > http://git.swclan.homelinux.org/rss2email.git)
> 
> I took a look.  You've got a list of items and you want to check each
> one against your 'seen it' file.  I'm not sure what your requirements
> are but currently the whole file gets read into memory.  So, sticking
> with that, here's _a_ way to do it (with a Set, which gives a faster
> lookup):

yeah, reading it all in is fine. NOt sure in the long term what the
problems are with that. I suppose if it was a really big history file,
it would be important to do something else, but it works for now.

> 
> import Control.Exception
> import Data.Set (Set)
> import qualified Data.Set as S
> import System.IO.Error
> import Prelude hiding (catch)
> 
> 
> -- | Return "seen it" predicate
> readHistory :: FilePath -> IO (String -> Bool)
> readHistory fn = do
>     hist <- withFile fn ReadMode $ \h -> fetchLines h S.empty
>     return (`S.member` hist)
>   where
>     fetchLines h hist = do
>         l <- hGetLine h
>         fetchLines h $! S.insert l hist
>       `catch` \exc ->
>         if isEOFError exc
>             then return hist
>             else throwIO exc
> 
> This is completely strict.  The $! is there to make sure we're keeping a
> set in memory, not a chain of inserts (though the inserts wouldn't
> actually take up any more memory than the set does).  I haven't tried
> compiling this.

thanks for this. it helps a lot. hmmm... I wonder why it is I never
have a problem returning functions in Scheme, but it never occurs to
me as I learn Haskell? 

thanks for your help.

A
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: Digital signature
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20100519/f1b4d9ff/attachment-0001.bin

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

Message: 4
Date: Wed, 19 May 2010 21:20:36 -0400
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: Re: [Haskell-beginners] Implementing a Local Propagation
        Network
To: "Stephen Blackheath [to Haskell-Beginners]"
        <mutilating.cauliflowers.step...@blacksapphire.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktild31omwfuo0-ds1irv7p5iowv7mez8j-asl...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Stephen,

On Wed, May 19, 2010 at 6:55 PM, Stephen Blackheath [to
Haskell-Beginners] <mutilating.cauliflowers.step...@blacksapphire.com>
wrote:
> Patrick,
>
> I think that looks like about the best way you could do it.  If I were
> doing it, I would probably write it without the state monad, with all
> the LPN ()'s becoming Network -> Network, and the code wouldn't be all
> that different, except that 'multiplier' and 'adder' would become
> slightly less readable.
>
> If you did that, then in those cases (where your algorithm is described
> by a sequence of modifications) you can say 'flip execState network $ do
> ...'.  Then all the 'revokeWire sum name's have to become 'modify $
> revokeWire sum name'.

For learning purposes, I tried what you suggested and you were
absolutely right. With the arguments properly ordered, i.e. (... ->
Network -> Network), the code remains pretty similar without the State
monad. Proper ordering of arguments in combination with partial
application and (.) is really fantastic!

I also hadn't realized that you could create "monadic" code
"on-the-fly" like this:

adder :: NodeName -> WireName -> WireName -> WireName -> Network -> Network
adder name ad1 ad2 sum net = flip execState net $ do
  if isJust v1 && isJust v2
    then modify $ setWire sum name (fromJust v1 + fromJust v2)
    else modify $ revokeWire sum name
  if isJust v1 && isJust vs
    then modify $ setWire ad2 name (fromJust vs - fromJust v1)
    else modify $ revokeWire ad2 name
  if isJust v2 && isJust vs
    then modify $ setWire ad1 name (fromJust vs - fromJust v2)
    else modify $ revokeWire ad1 name
  where v1 = lookupWireValue ad1 name net
        v2 = lookupWireValue ad2 name net
        vs = lookupWireValue sum name net

That's very neat.

For the testing code I came up with 2 variants, I'm still not sure
which one I like best:

fc =
  input f 212
  . addMultiplier "*" k l m
  . addAdder "+" j k i
  . addConstant "32" 32 j
  . addConstant "5/9" (5/9) l
  . addIO f i
  . addIO c m
  . foldr addWire networkMake $ wires
  where wi...@[i, j, k, l, m] = ["i", "j", "k", "l", "m"]
        [f, c] = ["Fahrenheit", "Celsius"]

fcm = flip execState networkMake $ do
  mapM_ (\w -> modify $ addWire w) wires
  modify $ addIO f i
  modify $ addIO c m
  modify $ addConstant "32" 32 j
  modify $ addConstant "5/9" (5/9) l
  modify $ addAdder "+" j k i
  modify $ addMultiplier "*" k l m
  modify $ input f 212
  where wi...@[i, j, k, l, m] = ["i", "j", "k", "l", "m"]
        [f, c] = ["Fahrenheit", "Celsius"]


Thanks a lot for your insight,

Patrick

>
> There's no particular reason why that's better - it's just style.  If
> your main program is going to describe a whole lot of complex
> transformations that happen in sequence, then your way would likely be
> better than my suggested way.
>
>
> Steve
>
> On 20/05/10 07:12, Patrick LeBoutillier wrote:
>> Stephen,
>>
>> Thanks for the advice, finally I ended up using a State Monad and
>> names (String) as symbolic references.
>>
>> Here is what I came up with: http://pastebin.com/gqkP2sWy
>>
>> Here is some test code:
>>
>> import LPN
>> import Control.Monad.State
>>
>> testfc = snd $ runState fc networkMake
>>
>> fc :: LPN ()
>> fc = do
>>   i:j:k:l:m:[] <- sequence $ map addWire ["i", "j", "k", "l", "m"]
>>   f <- addIO "Fahrenheit" i
>>   c <- addIO "Celsius" m
>>   addConstant "32" 32 j
>>   addConstant "5/9" (5/9) l
>>   addAdder "+" j k i
>>   addMultiplier "*" k l m
>>   input f 212
>>
>> At first it felt kind of messy, but as I kept refactoring and pushing
>> stuff into the monad it became a lot cleaner and felt less heavy.
>> I learned a lot about the State Monad doing this.
>>
>>
>> Thanks,
>>
>> Patrick
>>
>>
>>
>> On Mon, May 17, 2010 at 10:41 PM, Stephen Blackheath [to
>> Haskell-Beginners] <mutilating.cauliflowers.step...@blacksapphire.com>
>> wrote:
>>> Patrick,
>>>
>>> If you want to implement it in a functional style, you have to use an
>>> association map of some sort.  Haskell only has values, but not any
>>> concept of a reference (unless you count things like IORef, but I am not
>>> counting those).  Generally speaking this is needed whenever you are
>>> dealing with a data structure that has cycles.  (Generally speaking
>>> because it's possible to make data structures lazily refer to themselves.)
>>>
>>> People usually use IntMap, but there's a new package EnumMap on Hackage
>>> which is really powerful.  It's like IntMap only typesafe.  You will
>>> need a counter in your data structure as a source of unique ids.  You
>>> can also use value-supply (from Hackage), which is a great bit of code.
>>>
>>> On the face of it, this seems cumbersome, but the way to do it is to
>>> create a data structure and access it through accessor functions like
>>> "add node", "delete node", "follow wire", etc.  This way you can
>>> abstract those details away.  People have done various directed/undirect
>>> graph packages and so on on Hackage - I can't recommend anything.
>>>
>>> Stick with it - this approach does work.  I've done things like
>>> conversion of 3D models into triangle strips using this method, with
>>> very satisfying results.
>>>
>>>
>>> Steve
>>>
>>> On 18/05/10 12:59, Patrick LeBoutillier wrote:
>>>> Hi all,
>>>>
>>>> After learning some Haskell recently, I decided to revisit a book
>>>> about functional programming techniques for Perl: Higher Order Perl. I
>>>> didn't fully understand the book at the time but now my Haskell
>>>> experience has proved to be very insightful.
>>>>
>>>> Towards the end of the book the author implements a local propagation 
>>>> network.
>>>>
>>>> Here is the Perl source code:
>>>> http://hop.perl.plover.com/Examples/Chap9/Local-Propagation/
>>>> The PDF of the specific chapter is here:
>>>> http://hop.perl.plover.com/book/pdf/09DeclarativeProgramming.pdf
>>>>
>>>> I would like to experiment with something similar in Haskell, but the
>>>> way this network is designed is all about state and references:
>>>>
>>>> - Wires have a values that can change over time;
>>>> - Wires have references to nodes;
>>>> - Nodes have references to wires;
>>>>
>>>> I'm a bit stuck as to how to approach the "object has a list
>>>> references to other objects" situation from Haskell. I tried this:
>>>>
>>>> type Name = String
>>>> data Node = Node Name [Wire]
>>>> data Wire = Wire Name Node Double [Node]
>>>>
>>>> But that doesn't seem like it would work since when I change a Wire I
>>>> must find all "copies" of it (in the Node objects) and update them
>>>> also. Perhaps I should just refer to Wires/Nodes by name and use an
>>>> association list to lookup them up, but that seems cumbersome.
>>>>
>>>> Anybody have any suggestions?
>>>>
>>>>
>>>> Thanks a lot,
>>>>
>>>> Patrick
>>>>
>>>>
>>>>
>>> _______________________________________________
>>> Beginners mailing list
>>> Beginners@haskell.org
>>> http://www.haskell.org/mailman/listinfo/beginners
>>>
>>
>>
>>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


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

Message: 5
Date: Sat, 15 May 2010 11:27:49 -0500
From: Diego Echeverri <diegoe...@gmail.com>
Subject: Re: [Haskell-beginners] Help with slow algorithm
To: Daniel Fischer <daniel.is.fisc...@web.de>
Message-ID:
        <aanlktikq2prwntgfwenglbobrocb80bagthpl40bh...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Thanks!

I checked Brandon's link and it was indeed wasting too much time doing
GC (80%-70%). I did profiling by type and most of it were lists. I'm
only using lists in the addOne function when I get the elements of the
array. Maybe it would help to create the ByteArray directly without
using that intermediate list (No idea how to do it). Or it would be
even better if I could just use something like "mutable bytestrings"
That would avoid some of the packing and unpacking.

Even when I managed to make it pass. I feel like cheating. Instead of
changing it algorithmically I changed some of the GC options to avoid
GC time. In order to do this I followed this:
http://www.haskell.org/haskellwiki/SPOJ

In case anybody is interested, here's the code:

http://gist.github.com/402282



On Sat, May 15, 2010 at 2:57 AM, Daniel Fischer
<daniel.is.fisc...@web.de> wrote:
> Congrats.
> But you should try to squeeze a little more out of it.
>
> Cheers,
> Daniel
>



-- 
Att: Diego Echeverri Saldarriaga


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

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


End of Beginners Digest, Vol 23, Issue 31
*****************************************

Reply via email to