[Haskell-beginners] Unmaybe

Kim-Ee Yeoh ky3 at atamo.com
Tue May 14 18:00:55 CEST 2013


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
<adrian.alexander.may at 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 <ky3 at atamo.com> wrote:
>
>> On Tue, May 14, 2013 at 4:21 PM, Adrian May <
>> adrian.alexander.may at 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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130514/20944c24/attachment-0001.htm>


More information about the Beginners mailing list