Simple Unix tools: Difference between revisions
(please won't someone think of the apostrophes?) |
(improve the code in general, add type sigs, remove mislieading cat definition, and add a busybox style of running from a commandline) |
||
Line 12: | Line 12: | ||
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 | 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 | $ ghc --make UnixTools.hs | ||
The given Haskell codes presents yet a third way of doing things: much like the BusyBox[http://en.wikipedia.org/wiki/BusyBox] suite of Unix tools, it is possible to compile a single monolithic binary and have it detect what name it is run by and then act appropriately. This is the approach the following code takes: you can compile it and then make symbolic links (like "ln -s UnixTools echo") and then run those commands ("echo foo | ./echo" would produce output of "foo"). | |||
<haskell> | <haskell> | ||
-- Some Unix-like tools written in simple, clean Haskell | -- Some Unix-like tools written in simple, clean Haskell | ||
-- | module Main | ||
-- | where | ||
import Data.List ( sort, nub, intersperse, delete, isPrefixOf, foldl' ) | |||
import Data.Char ( toUpper, isSpace, ord ) | |||
--import System.IO --not needed yet | |||
import Text.Printf ( printf ) | |||
import System.Environment ( getProgName ) | |||
main = do | |||
calledBy <- getProgName | |||
case calledBy of | |||
"blank" -> io blank | |||
"cksum" -> cksum | |||
"clean" -> io clean'' | |||
"echo" -> interact id -- not perfect. what if echoed thing is an argument and not on stdin? | |||
"drop" -> interact drop' | |||
"grep" -> io grep | |||
"grep -v" -> io grep_v | |||
"head" -> io (return . head') | |||
"join" -> io join | |||
"num" -> io num | |||
--"remove" -> io remove "str" | |||
"revw" -> io revw | |||
"reverse" -> io rev | |||
"reverseword" -> io revw | |||
"rpt" -> io rpt | |||
"sort" -> interact sort | |||
"space" -> io space | |||
"tac" -> interact tac | |||
"take" -> io take' | |||
"tail" -> io (return . tail') | |||
--"tr" -> interact tr | |||
--"tr -d" -> interact (trd . unwords) | |||
"unspace" -> io unspace | |||
"upper" -> interact upper | |||
"uniq" -> interact uniq | |||
"wc_c" -> interact wc_c | |||
"wc_l" -> interact wc_l | |||
"wc_w" -> interact wc_w | |||
-- First, two helpers | -- First, two helpers | ||
-- | io :: ([String] -> [String]) -> IO () | ||
io f | io f = interact (unlines . f . lines) | ||
showln :: Int -> String | |||
showln = (++ "\n") . show | showln = (++ "\n") . show | ||
-- Sort a file | -- Sort a file | ||
- | sort' :: String -> String | ||
sort' = | sort' = sort | ||
-- remove duplicate lines from a file (like uniq) | -- remove duplicate lines from a file (like uniq) | ||
- | uniq :: String -> String | ||
uniq | uniq = nub | ||
-- repeat the input file infinitely | |||
-- repeat the input file infinitely | rpt :: [a] -> [a] | ||
- | rpt = cycle | ||
rpt | |||
-- Return the head -10 line of a file | -- Return the head -10 line of a file | ||
- | take' :: [String] -> [String] | ||
take' = | take' = take 10 | ||
-- Remove the first 10 lines of a file | -- Remove the first 10 lines of a file | ||
- | drop' :: String -> String | ||
drop' = | drop' = drop 10 | ||
-- Return the head -1 line of a file | -- Return the head -1 line of a file | ||
- | head' :: [String] -> String | ||
head' = | head' = head | ||
-- Return the tail -1 line of a file | -- Return the tail -1 line of a file | ||
- | tail' :: [String] -> String | ||
tail' = | tail' = last | ||
-- Reverse lines in a file (tac) | -- Reverse lines in a file (tac) | ||
- | tac :: String -> String | ||
tac | tac = reverse | ||
-- Reverse characters on each line (rev) | -- Reverse characters on each line (rev) | ||
- | rev :: [String] -> [String] | ||
rev | rev = map reverse | ||
-- Reverse words on each line | -- Reverse words on each line | ||
- | revw :: [String] -> [String] | ||
revw | revw = map (unwords. reverse . words) | ||
-- Count number of characters in a file (like wc -c) | -- Count number of characters in a file (like wc -c) | ||
- | wc_c :: String -> String | ||
wc_c | wc_c = showln . length | ||
-- Count number of lines in a file, like wc -l | -- Count number of lines in a file, like wc -l | ||
- | wc_l :: String -> String | ||
wc_l | wc_l = showln . length . lines | ||
-- Count number of words in a file (like wc -w) | -- Count number of words in a file (like wc -w) | ||
- | wc_w :: String -> String | ||
wc_w | wc_w = showln . length . words | ||
-- double space a file | -- double space a file | ||
- | space :: [String] -> [String] | ||
space | space = intersperse "" | ||
-- undo double space | -- undo double space | ||
- | unspace :: [String] -> [String] | ||
unspace = | unspace = filter (not.null) | ||
-- remove the first occurrence of the line "str" | |||
-- remove the first | remove :: String -> [String] -> [String] | ||
-- | remove a = delete a | ||
remove = | |||
-- make a string all upper case | |||
-- make a | upper :: String -> String | ||
- | upper = map toUpper | ||
upper = | |||
-- remove leading space from each line | -- remove leading space from each line | ||
- | clean :: [String] -> [String] | ||
clean = | clean = map (dropWhile isSpace) | ||
-- remove trailing whitespace | -- remove trailing whitespace | ||
- | clean' :: [String] -> [String] | ||
clean' = | clean' = (map f) | ||
where f = reverse . dropWhile isSpace . reverse | |||
-- delete leading and trailing whitespace | -- delete leading and trailing whitespace | ||
- | clean'' :: [String] -> [String] | ||
clean'' = | clean'' = map (f . f) | ||
where f = reverse . dropWhile isSpace | |||
-- insert blank space at beginning of each line | -- insert blank space at beginning of each line | ||
- | blank :: [String] -> [String] | ||
blank = | blank = map (s ++) | ||
where s = replicate 8 ' ' | |||
-- join lines of a file | -- join lines of a file | ||
- | join :: [String] -> [String] | ||
join | join = return . concat | ||
-- Translate the letter 'e' to '*', like tr 'e' '*' (or y// in sed) | -- Translate the letter 'e' to '*', like tr 'e' '*' (or y// in sed) | ||
-- | tr :: Char -> Char -> IO () | ||
tr a b = interact (map f) | |||
where f c = if c == a then b else c | |||
-- Delete characters from a string. | |||
-- | trd :: Char -> IO () | ||
- | trd a = tr a ' ' | ||
tr | |||
-- grep lines matching "^foo" from a file | -- grep lines matching "^foo" from a file | ||
- | grep :: [String] -> [String] | ||
grep | grep = filter (isPrefixOf "foo") | ||
-- grep lines that don't match "^foo" (grep -v) | -- grep lines that don't match "^foo" (grep -v) | ||
- | grep_v :: [String] -> [String] | ||
grep_v = | grep_v = filter (not . isPrefixOf "foo") | ||
-- number each line of a file | -- number each line of a file | ||
- | num :: [String] -> [String] | ||
num | num = zipWith (printf "%3d %s") [(1::Int)..] | ||
-- Compute a simple cksum of a file | -- Compute a simple cksum of a file | ||
cksum :: IO () | |||
cksum = interact $ showln . foldl' k 5381 | cksum = interact $ showln . foldl' k 5381 | ||
where k h c = h * 33 + ord c | |||
</haskell> | </haskell> |
Revision as of 04:38, 11 March 2007
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
The given Haskell codes presents yet a third way of doing things: much like the BusyBox[1] suite of Unix tools, it is possible to compile a single monolithic binary and have it detect what name it is run by and then act appropriately. This is the approach the following code takes: you can compile it and then make symbolic links (like "ln -s UnixTools echo") and then run those commands ("echo foo | ./echo" would produce output of "foo").
-- Some Unix-like tools written in simple, clean Haskell
module Main
where
import Data.List ( sort, nub, intersperse, delete, isPrefixOf, foldl' )
import Data.Char ( toUpper, isSpace, ord )
--import System.IO --not needed yet
import Text.Printf ( printf )
import System.Environment ( getProgName )
main = do
calledBy <- getProgName
case calledBy of
"blank" -> io blank
"cksum" -> cksum
"clean" -> io clean''
"echo" -> interact id -- not perfect. what if echoed thing is an argument and not on stdin?
"drop" -> interact drop'
"grep" -> io grep
"grep -v" -> io grep_v
"head" -> io (return . head')
"join" -> io join
"num" -> io num
--"remove" -> io remove "str"
"revw" -> io revw
"reverse" -> io rev
"reverseword" -> io revw
"rpt" -> io rpt
"sort" -> interact sort
"space" -> io space
"tac" -> interact tac
"take" -> io take'
"tail" -> io (return . tail')
--"tr" -> interact tr
--"tr -d" -> interact (trd . unwords)
"unspace" -> io unspace
"upper" -> interact upper
"uniq" -> interact uniq
"wc_c" -> interact wc_c
"wc_l" -> interact wc_l
"wc_w" -> interact wc_w
-- First, two helpers
io :: ([String] -> [String]) -> IO ()
io f = interact (unlines . f . lines)
showln :: Int -> String
showln = (++ "\n") . show
-- Sort a file
sort' :: String -> String
sort' = sort
-- remove duplicate lines from a file (like uniq)
uniq :: String -> String
uniq = nub
-- repeat the input file infinitely
rpt :: [a] -> [a]
rpt = cycle
-- Return the head -10 line of a file
take' :: [String] -> [String]
take' = take 10
-- Remove the first 10 lines of a file
drop' :: String -> String
drop' = drop 10
-- Return the head -1 line of a file
head' :: [String] -> String
head' = head
-- Return the tail -1 line of a file
tail' :: [String] -> String
tail' = last
-- Reverse lines in a file (tac)
tac :: String -> String
tac = reverse
-- Reverse characters on each line (rev)
rev :: [String] -> [String]
rev = map reverse
-- Reverse words on each line
revw :: [String] -> [String]
revw = map (unwords. reverse . words)
-- Count number of characters in a file (like wc -c)
wc_c :: String -> String
wc_c = showln . length
-- Count number of lines in a file, like wc -l
wc_l :: String -> String
wc_l = showln . length . lines
-- Count number of words in a file (like wc -w)
wc_w :: String -> String
wc_w = showln . length . words
-- double space a file
space :: [String] -> [String]
space = intersperse ""
-- undo double space
unspace :: [String] -> [String]
unspace = filter (not.null)
-- remove the first occurrence of the line "str"
remove :: String -> [String] -> [String]
remove a = delete a
-- make a string all upper case
upper :: String -> String
upper = map toUpper
-- remove leading space from each line
clean :: [String] -> [String]
clean = map (dropWhile isSpace)
-- remove trailing whitespace
clean' :: [String] -> [String]
clean' = (map f)
where f = reverse . dropWhile isSpace . reverse
-- delete leading and trailing whitespace
clean'' :: [String] -> [String]
clean'' = map (f . f)
where f = reverse . dropWhile isSpace
-- insert blank space at beginning of each line
blank :: [String] -> [String]
blank = map (s ++)
where s = replicate 8 ' '
-- join lines of a file
join :: [String] -> [String]
join = return . concat
-- Translate the letter 'e' to '*', like tr 'e' '*' (or y// in sed)
tr :: Char -> Char -> IO ()
tr a b = interact (map f)
where f c = if c == a then b else c
-- Delete characters from a string.
trd :: Char -> IO ()
trd a = tr a ' '
-- grep lines matching "^foo" from a file
grep :: [String] -> [String]
grep = filter (isPrefixOf "foo")
-- grep lines that don't match "^foo" (grep -v)
grep_v :: [String] -> [String]
grep_v = filter (not . isPrefixOf "foo")
-- number each line of a file
num :: [String] -> [String]
num = zipWith (printf "%3d %s") [(1::Int)..]
-- Compute a simple cksum of a file
cksum :: IO ()
cksum = interact $ showln . foldl' k 5381
where k h c = h * 33 + ord c
Where to now?
- Haskell.org
- The Haskell standard list library, with docs
- Alternative implementations of the wc program
- Learn how to test Haskell code
- More Haskell code
- Haskell for shell scripting
- Export list functions to the shell with h4sh