[Haskell-beginners] Implementing a Local Propagation Network

Patrick LeBoutillier patrick.leboutillier at gmail.com
Wed May 19 21:20:36 EDT 2010


Stephen,

On Wed, May 19, 2010 at 6:55 PM, Stephen Blackheath [to
Haskell-Beginners] <mutilating.cauliflowers.stephen at 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 wires@[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 wires@[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.stephen at 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 at haskell.org
>>> http://www.haskell.org/mailman/listinfo/beginners
>>>
>>
>>
>>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



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


More information about the Beginners mailing list