Skip to content

Instantly share code, notes, and snippets.

@nc6
Created November 18, 2013 11:44
Show Gist options
  • Save nc6/7526489 to your computer and use it in GitHub Desktop.
Save nc6/7526489 to your computer and use it in GitHub Desktop.
Takes a file of replacements and applies it to every field in another file.
{-# LANGUAGE LambdaCase #-}
module Main where
import Control.Monad (liftM)
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy.Char8 as LB
import qualified Data.Map as Map
import Data.Maybe (fromMaybe, catMaybes)
import Data.Monoid (mconcat)
import System.Environment (getArgs)
import System.IO (openFile, hClose, IOMode(..))
lookupOrId :: Ord k => (Map.Map k k) -> k -> k
lookupOrId m k = fromMaybe k $ Map.lookup k m
rFieldSeparator :: Char
rFieldSeparator = ' '
oFieldSeparator :: Char
oFieldSeparator = ' '
usage :: String
usage = "bigsed replacements in out"
readReplacement :: B.ByteString -> Maybe (B.ByteString, B.ByteString)
readReplacement from = case B.split rFieldSeparator from of
[a,b] -> Just (a,b)
_ -> Nothing
replaceLine :: (Map.Map B.ByteString B.ByteString) -> B.ByteString -> B.ByteString
replaceLine m = B.intercalate (B.singleton oFieldSeparator) . map (lookupOrId m) . B.split oFieldSeparator
main :: IO ()
main = getArgs >>= \case
repF : inF : outF : [] -> do
allReps <- B.readFile repF
let repmap = Map.fromList . catMaybes . map (readReplacement) . B.lines $ allReps
allLines <- liftM LB.lines . LB.readFile $ inF
out <- openFile outF WriteMode
mapM_ (B.hPutStrLn out . replaceLine repmap . mconcat . LB.toChunks) $ allLines
hClose out
_ -> putStrLn usage
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment