[Haskell-cafe] Re: How would you replace a field in a CSV file?

apfelmus at quantentunnel.de apfelmus at quantentunnel.de
Mon Oct 2 12:39:55 EDT 2006


Pete Kazmier wrote:
> import Data.ByteString.Lazy.Char8 as B hiding (map,foldr)
> import Data.List (map)
> import Data.Map as M hiding (map)
> 
> -- This will be populated from a file
> dict = M.singleton (B.pack "Pete") (B.pack "Kazmier")
> 
> main = B.interact $ B.unlines . map doline . B.lines
>     where doline    = B.join comma . mapIndex fixup . B.split ','
>           comma     = B.singleton ','
>           fixup 3 s = M.findWithDefault s s dict
>           fixup n s = s
> 
> -- f is supplied the index of the current element being processed
> mapIndex :: (Int -> ByteString -> ByteString) -> [ByteString] ->
> [ByteString]
> mapIndex f xs = m xs 0
>     where m []      _ = []
>           m (x:xs') i = f i x : (m xs' $! i+1)

How about

import Data.ByteString.Lazy.Char8 as B hiding (map,foldr)
import Data.List (map)
import Data.Map as M hiding (map)

dict = M.singleton (B.pack "Pete") (B.pack "Kazmier")

main = B.interact $ B.unlines . map doline . B.lines
    where
    doline  = B.join comma . zipWith ($) fixup9 . B.split ','
    fixup9  = fixup 9
    fixup n = replicate n id
              ++ [\s -> M.findWithDefault s s dict] ++ repeat id

Note that fixup9 is shared intentionally across different invocations of
doline. The index n starts at 0.


Also note that because (compare :: (Byte)String -> ..) takes time
proportional to the string length, the use of Map will inevitably
introduce a constant factor. But I'm still happy you didn't use arrays
or hash tables (urgh!) :)

In any case, tries are *the* natural data structure for (in)finite maps
in functional languages, see also

Ralf Hinze. Generalizing generalized tries. Journal of Functional
Programming, 10(4):327-351, July 2000
http://www.informatik.uni-bonn.de/~ralf/publications/GGTries.ps.gz


Regards,
apfelmus



More information about the Haskell-Cafe mailing list