Simple Unix tools

From HaskellWiki
Revision as of 22:34, 10 March 2007 by Gwern (talk | contribs) (please won't someone think of the apostrophes?)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

Simple Unix commandline tools written in Haskell.

This is intended as a beginner's tutorial for learning Haskell from a "Let's just solve things already!" point of view. The examples should help give a flavor of the beauty and expressiveness of Haskell programming.

These functions can be executed as one liners from a shell. For example, to use the Haskell version of 'wc':

$ cat file.txt | ghc -e 'wc_l' UnixTools.hs

Or, one could define 'main' to be a chosen tool/function (add a line to the effect that "main = wc_l") and then compile the tool with $ ghc --make UnixTools.hs

--
-- Some Unix-like tools written in simple, clean Haskell
--
--

import Data.List
import Data.Char
import System.IO
import Text.Printf

-- 
-- First, two helpers
--
io f    = interact (unlines . f . lines)
showln  = (++ "\n") . show

--
-- The 'cat' program
--
cat     = interact id

--
-- Sort a file
--
sort'   = io sort

--
-- remove duplicate lines from a file (like uniq)
--
uniq    = io nub

-- 
-- repeat the input file infinitely 
--
rpt     = interact cycle

--
-- Return the head -10 line of a file
--
take'   = io (take 10)

--
-- Remove the first 10 lines of a file
--
drop'   = io (drop 10)

--
-- Return the head -1 line of a file
--
head'   = io (return . head)

--
-- Return the tail -1 line of a file
--
tail'   = io (return . last)

-- 
-- Reverse lines in a file (tac)
--
tac     = io reverse

--
-- Reverse characters on each line (rev)
--
rev     = io (map reverse)

--
-- Reverse words on each line
--
revw    = io $ map (unwords. reverse . words)

--
-- Count number of characters in a file (like wc -c)
--
wc_c    = interact (showln . length)

--
-- Count number of lines in a file, like wc -l
--
wc_l    = interact (showln . length . lines)

--
-- Count number of words in a file (like wc -w)
--
wc_w    = interact (showln . length . words)

--
-- double space a file
--
space   = io (intersperse "")

-- 
-- undo double space
--
unspace = io $ filter (not.null)

--
-- remove the first occurence of the line "str"
--
remove  = io (delete "str")

--
-- make a file all upper case
--
upper   = interact (map toUpper)

--
-- remove leading space from each line
--
clean   = io $ map (dropWhile isSpace)

--
-- remove trailing whitespace
--
clean'  = io (map f)
    where f = reverse . dropWhile isSpace . reverse

--
-- delete leading and trailing whitespace
--
clean'' = io $ map (f . f)
    where f = reverse . dropWhile isSpace

--
-- insert blank space at beginning of each line
--
blank   = io $ map (s ++)
    where s = replicate 8 ' '

--
-- join lines of a file
--
join    = io (return . concat)

--
-- Translate the letter 'e' to '*', like tr 'e' '*' (or y// in sed)
--
y       = interact (map f)
    where f 'e' = '*'
          f  c  =  c
--
-- Filter the letter 'e' from a file, like tr -d 'e'
--
tr      = interact $ filter (/= 'e')

--
-- grep lines matching "^foo" from a file
--
grep    = io $ filter (isPrefixOf "foo")

--
-- grep lines that don't match "^foo" (grep -v)
--
grep_v  = io $ filter (not . isPrefixOf "foo")

--
-- number each line of a file
--
num     = io $ zipWith (printf "%3d %s") [(1::Int)..]

--
-- Compute a simple cksum of a file
--
cksum   = interact $ showln . foldl' k 5381
    where k h c = h * 33 + ord c


Where to now?