[Haskell-cafe] Chaining modifications using (>>>)

Mateusz Kowalczyk fuuzetsu at fuuzetsu.co.uk
Sat Sep 20 16:23:50 UTC 2014


On 09/20/2014 02:14 AM, martin wrote:
> Hello all,
> 
> I've been playing with Data.Graph.Inductive, which provides functions to modify a graph. I take these functions and
> build something more complex from them. To do so, I have to apply several such modifications one after the other.
> 
> I can write this using ($) or (.), but I didn't like to write things backwards (last function to apply comes first), so
> I use (>>>) from the Arrows module to chain functions Graph -> Graph (aka GraphTransforms) and my complex function looks
> like f >>> g >>> h. To actually build a Graph I have to apply my function to some Graph (often "empty").
> 
> This works okay as long as the inidividual functions f,g,h do not need access to the graph. However, there is one
> function where I use "pre" (predecessors) and "suc" (succerssors), which need the Graph as a parameter.
> 
> groupNodes :: DynGraph gr => (Label,[Node])  -> GraphTransform gr pl
> groupNodes (lbl,ids) gr =
>   let
>     id = head $ newNodes 1 gr
>     oldEdgesTo     = [(toOld, old)   | old <- ids, toOld   <- pre gr old] -- <== here "pre"
>     oldEdgesFrom   = [(old, fromOld) | old <- ids, fromOld <- suc gr old]
>     oldEdges       = oldEdgesTo ++ oldEdgesFrom
>     oldEdgesWithin = [ (i,j) | (i,j) <- oldEdges, i `elem` ids, j `elem` ids]
>     newEdges       = map (uncurry e0) $ uniq $
>                                 map (setDest id)  (oldEdgesTo   \\ oldEdgesWithin) ++
>                                 map (setOrig id)  (oldEdgesFrom \\ oldEdgesWithin)
>   in --------------- look here: -----------------------
>       (
>       insNode (id, (NN lbl))
>       >>> delNodes ids
>       >>> delEdges oldEdges
>       >>> insEdges newEdges
>       ) gr
> 
> This works, but I don't like the "in" part and I'd rather omit the braces and the gr argument. Without the gr argument
> to the whole function this would work, however with the gr I have to kinda eta expand (?) it.
> 
> Is there a way I can write this more point free and still have access to gr for pre and suc?
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 

Did you look at the arrow syntax extension?

-- 
Mateusz K.


More information about the Haskell-Cafe mailing list