[Haskell-cafe] Re: Software Tools in Haskell

apfelmus apfelmus at quantentunnel.de
Thu Dec 13 05:40:48 EST 2007


Tommy M McGuire wrote:
> apfelmus wrote:
>>
>>   tabwidth = 4
>>
>>      -- tabstop !! (col-1) == there is a tabstop at column  col
>>      -- This is an infinite list, so no need to limit the line width
>>   tabstops  = map (\col -> col `mod` tabwidth == 1) [1..]
>>
>>      -- calculate spaces needed to fill to the next tabstop in advance
>>   tabspaces = snd $ mapAccumR addspace [] tabstops
>>   addspace cs isstop = let cs'=' ':cs in (if isstop then [] else cs',cs')
> 
> Are you using mapAccumR (mapAccumR? (!)) to share space among the space 
> strings?

Sharing is a good idea! But  mapAccumR  has nothing to do with it, I 
just used it to encode the recursion, as replacement for a  fold  so to 
speak.

>  If so, wouldn't this be better:
> 
> tabstops = map (\col -> col `mod` tabwidth == 1) [1..tabwidth]
> tabspaces = cycle $ snd $ mapAccumR addspace [] tabstops

Yes. We can make the code even simpler :)

   tabspaces = cycle . init . tails . replicate tabwidth $ ' '

and the  tabstops  list is gone.

> On the other hand, wouldn't this make for less head scratching:
> 
> tabspaces = map (\col -> replicate (spacesFor col) ' ') [1..]
>   where
>   spacesFor col = tabwidth - ((col - 1) `mod` tabwidth)

Yes and no. The very idea of introducing the  tabspaces  list in the 
first place is to avoid explicit indices altogether, a single  zipWith 
is responsible for aligning columns. So, it's only natural to avoid 
indices for the definition of  tabspaces , too.

A side effect of separating  tabspaces  from the main loop is that we 
can do all kind of irregular tabstop spacing or different fill 
characters and the like solely by changing this list.

>>   main = interact $ unlines . map detabLine . lines
>>      where
>>      detabLine = concat $ zipWith replace tabspaces
> 
> I think you mean "concat . zipWith...".   (You're doing this from 
> memory, aren't you?)

Yes and yes :)

>>      replace cs '\t' = cs     -- replace with adequate number of spaces
>>      replace _  char = [char] -- pass through
>>
>>
>> How about that?
> 
> It doesn't produce the same output, [...]
> It's counting tabs before expanding rather than after?

Yes, I noticed it too late, it's so wrong (>_<) :)

Here's a correct version:

   perLine f = interact $ unlines . map f . lines

   main = perLine (detabLine tabspaces)
      where
      detabLine _      []        = []
      detabLine (w:ws) ('\t':cs) = detabLine (w:ws) (w ++ cs)
      detabLine (w:ws) (c   :cs) = c:detabLine ws cs

Or even

   main = interact $ detab tabspaces
      where
      detab _      []        = []
      detab _      ('\n':cs) = '\n':detab tabspaces cs
      detab (w:ws) ('\t':cs) =      detab (w:ws) (w ++ cs)
      detab (_:ws) (c   :cs) =    c:detab ws cs

This can't be expressed with  zip  anymore since the alignment of the 
list of spaces and the text changes when encountering a tab.


@dons: I guess that  detab  would probably be a very interesting (and 
even useful) study example for generalizing stream fusion, since it's 
more like  concatMap  than  map .


Regards,
apfelmus



More information about the Haskell-Cafe mailing list