
Hi there, I have a really annoying scrap of code: unmaybe Nothing = mempty unmaybe (Just dia) = dia It happened because I'm using Diagrams but building my diagram requires looking something up in a list using findIndex, which returns Maybe Int. How do I rid myself of this blotch? TIA, Adrian.

maybe mempty id On Tue, May 14, 2013 at 05:21:44PM +0800, Adrian May wrote:
Hi there,
I have a really annoying scrap of code:
unmaybe Nothing = mempty unmaybe (Just dia) = dia
It happened because I'm using Diagrams but building my diagram requires looking something up in a list using findIndex, which returns Maybe Int.
How do I rid myself of this blotch?
TIA, Adrian.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Mats Rauhala MasseR

fromMaybe mempty
--
Karol Samborski
2013/5/14 Mats Rauhala
maybe mempty id
On Tue, May 14, 2013 at 05:21:44PM +0800, Adrian May wrote:
Hi there,
I have a really annoying scrap of code:
unmaybe Nothing = mempty unmaybe (Just dia) = dia
It happened because I'm using Diagrams but building my diagram requires looking something up in a list using findIndex, which returns Maybe Int.
How do I rid myself of this blotch?
TIA, Adrian.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Mats Rauhala MasseR
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Check out this info
http://en.wikibooks.org/wiki/Haskell/Hierarchical_libraries/Maybe
On Tue, May 14, 2013 at 11:21 AM, Adrian May wrote: Hi there, I have a really annoying scrap of code: unmaybe Nothing = mempty
unmaybe (Just dia) = dia It happened because I'm using Diagrams but building my diagram requires
looking something up in a list using findIndex, which returns Maybe Int. How do I rid myself of this blotch? TIA,
Adrian. _______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners

On Tue, May 14, 2013 at 4:21 PM, Adrian May
I have a really annoying scrap of code:
unmaybe Nothing = mempty unmaybe (Just dia) = dia
It happened because I'm using Diagrams but building my diagram requires looking something up in a list using findIndex, which returns Maybe Int.
What instance of Monoid is this? Because Int has both a Sum Int and a Product Int instance so you can't just apply unmaybe to (Just 3 :: Maybe Int). Defining unmaybe Nothing = 0 prompts the question: how will you distinguish misses versus hits on the head of the list? Presumably you don't want to. You might be interested in the totalized lookup functions defined in my private toolkit (hayoo returns nothing): -- tlookup :: (Eq a) => b -> a -> [(a, b)] -> b tlookup b a abs = fromMaybe b $ lookup a abs tlookup0 a abs = tlookup mempty a abs -- Kim-Ee

Thanks everyone. The first suggestion did the trick without needing any other modules.
What instance of Monoid is this?
I dunno, but the context is a gantt chart drawing program:
data Task = Task { name :: String, desc :: String, dur :: Days } --
tasks is a list of these and deps is a list of...
data Dep = Dep { pre :: String, post :: String } -- referring to Task's
name
-- draw the squiggles representing sequential dependencies:
beziset = foldl atop mempty $ map ((maybe mempty id).bezis) deps
bezis (Dep bef aft) =
findIndex (\t-> name t == bef) tasks >>= \bti ->
findIndex (\t-> name t == aft) tasks >>= \ati ->
let t1 = fromIntegral bti in
let d1 = finish (tasks !! bti) in --finish is begin + duration
let t2 = fromIntegral ati in
let d2 = begin (tasks !! ati) in --begin is the latest of the end
dates of the directly preceding tasks (or project kickoff)
return ( -- the following monstrosity is just about my coordinate system
fromSegments [bezier3 (r2 (1.3,0)) (r2 (d2-d1-1,-(t2-t1)*(1+gap)))
(r2 (d2-d1,-(t2-t1)*(1+gap))) ] #
translate (r2 (descspace+d1,-t1*(1+gap))) )
beziset then gets `atop`ed onto a Diagram.
bezis looks far too long as well. Any way to tidy it up? (For some perverse
reason I still don't like do notation.) (I know the bezier3 expression is
hideous but I can fix that myself.)
Adrian.
PS: In my previous job I once spent a week evaluating gantt chart drawing
softwares. Now I wrote the one I was looking for in half a day. That's
Haskell!
On 14 May 2013 20:08, Kim-Ee Yeoh
On Tue, May 14, 2013 at 4:21 PM, Adrian May < adrian.alexander.may@gmail.com> wrote:
I have a really annoying scrap of code:
unmaybe Nothing = mempty unmaybe (Just dia) = dia
It happened because I'm using Diagrams but building my diagram requires looking something up in a list using findIndex, which returns Maybe Int.
What instance of Monoid is this? Because Int has both a Sum Int and a Product Int instance so you can't just apply unmaybe to (Just 3 :: Maybe Int).
Defining unmaybe Nothing = 0 prompts the question: how will you distinguish misses versus hits on the head of the list? Presumably you don't want to.
You might be interested in the totalized lookup functions defined in my private toolkit (hayoo returns nothing):
-- tlookup :: (Eq a) => b -> a -> [(a, b)] -> b tlookup b a abs = fromMaybe b $ lookup a abs tlookup0 a abs = tlookup mempty a abs
-- Kim-Ee
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Last things first:
For some perverse reason I still don't like do notation.
You're in fine company. Many of the senior folk shun it altogether, especially in a classroom setting. See [1].
bezis looks far too long as well. Any way to tidy it up?
The list indices ati and bti are used only once: to retrieve the (first) item matching the predicate. Might Data.List.find be a better fit? Replacing findIndex with find should get rid of half of the lets that are just fromIntegral noise. This sort of falls under the broader rubric of more whitespace is better than less, all other things equal. So consecutive
let ... in let ... in
can be merged into a single multiline let, pace C&P diehards.
And finally to answer the earlier question: fromSegments returns a
PathLike-constrained value. PathLike is subclassed from Monoid.
[1] http://www.haskell.org/haskellwiki/Do_notation_considered_harmful
-- Kim-Ee
On Tue, May 14, 2013 at 9:56 PM, Adrian May
Thanks everyone. The first suggestion did the trick without needing any other modules.
What instance of Monoid is this?
I dunno, but the context is a gantt chart drawing program:
data Task = Task { name :: String, desc :: String, dur :: Days } -- tasks is a list of these and deps is a list of... data Dep = Dep { pre :: String, post :: String } -- referring to Task's name -- draw the squiggles representing sequential dependencies: beziset = foldl atop mempty $ map ((maybe mempty id).bezis) deps bezis (Dep bef aft) = findIndex (\t-> name t == bef) tasks >>= \bti -> findIndex (\t-> name t == aft) tasks >>= \ati -> let t1 = fromIntegral bti in let d1 = finish (tasks !! bti) in --finish is begin + duration let t2 = fromIntegral ati in let d2 = begin (tasks !! ati) in --begin is the latest of the end dates of the directly preceding tasks (or project kickoff) return ( -- the following monstrosity is just about my coordinate system fromSegments [bezier3 (r2 (1.3,0)) (r2 (d2-d1-1,-(t2-t1)*(1+gap))) (r2 (d2-d1,-(t2-t1)*(1+gap))) ] # translate (r2 (descspace+d1,-t1*(1+gap))) )
beziset then gets `atop`ed onto a Diagram.
bezis looks far too long as well. Any way to tidy it up? (For some perverse reason I still don't like do notation.) (I know the bezier3 expression is hideous but I can fix that myself.)
Adrian.
PS: In my previous job I once spent a week evaluating gantt chart drawing softwares. Now I wrote the one I was looking for in half a day. That's Haskell!
On 14 May 2013 20:08, Kim-Ee Yeoh
wrote: On Tue, May 14, 2013 at 4:21 PM, Adrian May < adrian.alexander.may@gmail.com> wrote:
I have a really annoying scrap of code:
unmaybe Nothing = mempty unmaybe (Just dia) = dia
It happened because I'm using Diagrams but building my diagram requires looking something up in a list using findIndex, which returns Maybe Int.
What instance of Monoid is this? Because Int has both a Sum Int and a Product Int instance so you can't just apply unmaybe to (Just 3 :: Maybe Int).
Defining unmaybe Nothing = 0 prompts the question: how will you distinguish misses versus hits on the head of the list? Presumably you don't want to.
You might be interested in the totalized lookup functions defined in my private toolkit (hayoo returns nothing):
-- tlookup :: (Eq a) => b -> a -> [(a, b)] -> b tlookup b a abs = fromMaybe b $ lookup a abs tlookup0 a abs = tlookup mempty a abs
-- Kim-Ee
_______________________________________________ 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

For some perverse reason I still don't like do notation.
You're in fine company. Many of the senior folk shun it altogether, especially in a classroom setting. See [1].
Well that's nice to know. I feel that I can see what's going on better in the non-do notation, but when I first started C I used to prefer *(p+i) to p[i] quoting the same rationale. That seems silly to me now.
bezis looks far too long as well. Any way to tidy it up?
The list indices ati and bti are used only once: to retrieve the (first) item matching the predicate. Might Data.List.find be a better fit?
No, I use them via t1 and t2 to figure out which row to put the squiggle on. The attached picture might put it all in perspective.
Replacing findIndex with find should get rid of half of the lets that are just fromIntegral noise.
Yeah but I still need the row number.
This sort of falls under the broader rubric of more whitespace is better than less, all other things equal. So consecutive
let ... in let ... in
can be merged into a single multiline let, pace C&P diehards.
True. Thanks, Adrian.
And finally to answer the earlier question: fromSegments returns a PathLike-constrained value. PathLike is subclassed from Monoid.
[1] http://www.haskell.org/haskellwiki/Do_notation_considered_harmful
-- Kim-Ee
On Tue, May 14, 2013 at 9:56 PM, Adrian May < adrian.alexander.may@gmail.com> wrote:
Thanks everyone. The first suggestion did the trick without needing any other modules.
What instance of Monoid is this?
I dunno, but the context is a gantt chart drawing program:
data Task = Task { name :: String, desc :: String, dur :: Days } -- tasks is a list of these and deps is a list of... data Dep = Dep { pre :: String, post :: String } -- referring to Task's name -- draw the squiggles representing sequential dependencies: beziset = foldl atop mempty $ map ((maybe mempty id).bezis) deps bezis (Dep bef aft) = findIndex (\t-> name t == bef) tasks >>= \bti -> findIndex (\t-> name t == aft) tasks >>= \ati -> let t1 = fromIntegral bti in let d1 = finish (tasks !! bti) in --finish is begin + duration let t2 = fromIntegral ati in let d2 = begin (tasks !! ati) in --begin is the latest of the end dates of the directly preceding tasks (or project kickoff) return ( -- the following monstrosity is just about my coordinate system fromSegments [bezier3 (r2 (1.3,0)) (r2 (d2-d1-1,-(t2-t1)*(1+gap))) (r2 (d2-d1,-(t2-t1)*(1+gap))) ] # translate (r2 (descspace+d1,-t1*(1+gap))) )
beziset then gets `atop`ed onto a Diagram.
bezis looks far too long as well. Any way to tidy it up? (For some perverse reason I still don't like do notation.) (I know the bezier3 expression is hideous but I can fix that myself.)
Adrian.
PS: In my previous job I once spent a week evaluating gantt chart drawing softwares. Now I wrote the one I was looking for in half a day. That's Haskell!
On 14 May 2013 20:08, Kim-Ee Yeoh
wrote: On Tue, May 14, 2013 at 4:21 PM, Adrian May < adrian.alexander.may@gmail.com> wrote:
I have a really annoying scrap of code:
unmaybe Nothing = mempty unmaybe (Just dia) = dia
It happened because I'm using Diagrams but building my diagram requires looking something up in a list using findIndex, which returns Maybe Int.
What instance of Monoid is this? Because Int has both a Sum Int and a Product Int instance so you can't just apply unmaybe to (Just 3 :: Maybe Int).
Defining unmaybe Nothing = 0 prompts the question: how will you distinguish misses versus hits on the head of the list? Presumably you don't want to.
You might be interested in the totalized lookup functions defined in my private toolkit (hayoo returns nothing):
-- tlookup :: (Eq a) => b -> a -> [(a, b)] -> b tlookup b a abs = fromMaybe b $ lookup a abs tlookup0 a abs = tlookup mempty a abs
-- Kim-Ee
_______________________________________________ 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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Actually, my data model with one list of tasks and another list of dependencies could get very tedious. For the example picture I posted, I could write something like: openbox >> ( readmanual <|> ( attachwires >> plugin >> turnon ) ) >> use but I'd be in trouble if, say, there was something else that could start after "attachwires" but had no other relationships to any other tasks and would run on into the "use" era. Is there any kind of super-monad that could express that? It's the same problem as trying to decompose an asymmetrical Wheatstone Bridge into serial and parallel sub-networks. Is there any solution to that? Adrian.

On Wed, May 15, 2013 at 9:58 AM, Adrian May
The list indices ati and bti are used only once: to retrieve the (first)
item matching the predicate. Might Data.List.find be a better fit?
No, I use them via t1 and t2 to figure out which row to put the squiggle on. The attached picture might put it all in perspective.
D'oh. Didn't see the later references, sorry.
Something to think about is: how would you document "my coordinate system" as you wrote in your comment? Highly visual things like these are challenging to describe even for verbal-thinking types. Probably sticking the picture in png/pdf format and linking to it in the comments is a good a solution as any. -- Kim-Ee

I seem to have come up with something:
main = putStrLn $ show $
"Foo".:.100 |:|
"Bar".:.10 >:> (
"Ket".:.20 >^> "Pod".:.1 |^|
"Zig".:.30
) >:> "Erm".:.15
>@> "Nuk".:.50
>@> "Din".:.30
says:
1:Foo=0.0->100.0
2:Bar=0.0->10.0
3:Ket=10.0->30.0
4:Pod=30.0->31.0
5:Zig=10.0->40.0
6:Erm=40.0->55.0
7:Nuk=31.0->81.0
8:Din=30.0->60.0
I'd best give names to those forks though otherwise the whole project plan
will break whenever I insert a new one. Can I give a parameter to an
operator? Like:
task1 `fork "name"` taskb
or:
task1 ( >^> "name" ) taskb
Adrian.
On 15 May 2013 20:22, Kim-Ee Yeoh
On Wed, May 15, 2013 at 9:58 AM, Adrian May < adrian.alexander.may@gmail.com> wrote:
The list indices ati and bti are used only once: to retrieve the (first)
item matching the predicate. Might Data.List.find be a better fit?
No, I use them via t1 and t2 to figure out which row to put the squiggle on. The attached picture might put it all in perspective.
D'oh. Didn't see the later references, sorry.
Something to think about is: how would you document "my coordinate system" as you wrote in your comment? Highly visual things like these are challenging to describe even for verbal-thinking types.
Probably sticking the picture in png/pdf format and linking to it in the comments is a good a solution as any.
-- Kim-Ee
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Wed, May 15, 2013 at 10:37:56PM +0800, Adrian May wrote:
I'd best give names to those forks though otherwise the whole project plan will break whenever I insert a new one. Can I give a parameter to an operator? Like:
task1 `fork "name"` taskb
task1 ( >^> "name" ) taskb
No, unfortunately neither of those is possible. -Brent

I don't suppose anybody really cares how this Gantt chart came out, but
just in case, I blogged about it:
http://nuerd.blogspot.tw/2013/05/gantt-chart-in-haskell.html
Adrian.
On 15 May 2013 23:19, Brent Yorgey
On Wed, May 15, 2013 at 10:37:56PM +0800, Adrian May wrote:
I'd best give names to those forks though otherwise the whole project
plan
will break whenever I insert a new one. Can I give a parameter to an operator? Like:
task1 `fork "name"` taskb
task1 ( >^> "name" ) taskb
No, unfortunately neither of those is possible.
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (6)
-
Adrian May
-
Brent Yorgey
-
bucephalus org
-
Karol Samborski
-
Kim-Ee Yeoh
-
Mats Rauhala