Difference between revisions of "Simple Unix tools"

From HaskellWiki
Jump to navigation Jump to search
(simple unix tools)
 
(style)
Line 2: Line 2:
   
 
This is intended as a beginners tutorial for learning Haskell from a
 
This is intended as a beginners tutorial for learning Haskell from a
"Lets just solve things already!" point of view.
+
"Lets just solve things already!" point of view. The examples should
  +
help give a flavour of the beauty and expressiveness of Haskell
  +
programming.
   
 
<haskell>
 
<haskell>
Line 22: Line 24:
 
-- The 'cat' program
 
-- The 'cat' program
 
--
 
--
cat = input id
+
cat = input id
   
 
--
 
--
 
-- Sort a file
 
-- Sort a file
 
--
 
--
sort' = input sort
+
sort' = input sort
   
 
--
 
--
 
-- Reverse a file (tac)
 
-- Reverse a file (tac)
 
--
 
--
tac = input reverse
+
tac = input reverse
   
 
--
 
--
 
-- Return the head -10 line of a file
 
-- Return the head -10 line of a file
 
--
 
--
head' = input $ take 10
+
head' = input $ take 10
   
 
--
 
--
 
-- Remove the first 10 lines of a file
 
-- Remove the first 10 lines of a file
 
--
 
--
drop' = input $ drop 10
+
drop' = input $ drop 10
   
 
--
 
--
 
-- Return the tail -1 line of a file
 
-- Return the tail -1 line of a file
 
--
 
--
tail' = input $ (:[]) . last
+
tail' = input $ (:[]) . last
   
 
--
 
--
 
-- remove duplicate lines from a file (like uniq)
 
-- remove duplicate lines from a file (like uniq)
 
--
 
--
uniq = input nub
+
uniq = input nub
   
 
--
 
--
 
-- double space a file
 
-- double space a file
 
--
 
--
space = input $ intersperse []
+
space = input $ intersperse ""
   
 
--
 
--
 
-- repeat the input file infintely
 
-- repeat the input file infintely
 
--
 
--
iterate = interact cycle
+
rpt = interact cycle
   
 
--
 
--
Line 87: Line 89:
 
-- Translate the letter 'e' to '*', like tr 'e' '*' (or y// in sed)
 
-- Translate the letter 'e' to '*', like tr 'e' '*' (or y// in sed)
 
--
 
--
y = interact $ map f
+
y = interact $ map f
 
where f 'e' = '*'
 
where f 'e' = '*'
 
f c = c
 
f c = c
Line 93: Line 95:
 
-- Filter the letter 'e' from a file, like tr -d 'e'
 
-- Filter the letter 'e' from a file, like tr -d 'e'
 
--
 
--
tr = interact $ filter (/= 'e')
+
tr = interact $ filter (/= 'e')
   
 
--
 
--
 
-- Count number of characters in a file (like wc -c)
 
-- Count number of characters in a file (like wc -c)
 
--
 
--
wc_c = interact $ show . length
+
wc_c = interact $ show . length
   
 
--
 
--
 
-- Count number of lines in a file, like wc -l
 
-- Count number of lines in a file, like wc -l
 
--
 
--
wc_l = interact $ show . length . lines
+
wc_l = interact $ show . length . lines
   
 
--
 
--
 
-- Count number of words in a file (like wc -w)
 
-- Count number of words in a file (like wc -w)
 
--
 
--
wc_w = interact $ show . length . words
+
wc_w = interact $ show . length . words
   
 
--
 
--
 
-- grep lines matching "^foo" from a file
 
-- grep lines matching "^foo" from a file
 
--
 
--
grep = input $ filter (isPrefixOf "foo")
+
grep = input $ filter (isPrefixOf "foo")
   
 
--
 
--
 
-- grep lines that don't match "^foo" (grep -v)
 
-- grep lines that don't match "^foo" (grep -v)
 
--
 
--
grep_v= input $ filter (not . isPrefixOf "foo")
+
grep_v = input $ filter (not . isPrefixOf "foo")
   
 
--
 
--
 
-- number each line of a file
 
-- number each line of a file
 
--
 
--
num = input $ zipWith ((. (' ':)) . shows) [1..]
+
num = input $ zipWith ((. (' ':)) . shows) [1..]
   
 
--
 
--
 
-- Compute a simple cksum of a file
 
-- Compute a simple cksum of a file
 
--
 
--
main = interact $ printf "%u\n" . foldl' k 5381
+
main = interact $ printf "%u\n" . foldl' k 5381
 
where k h c = h * 33 + fromIntegral (ord c) :: Int
 
where k h c = h * 33 + fromIntegral (ord c) :: Int
 
</haskell>
 
</haskell>

Revision as of 06:54, 22 September 2006

Simple unix tools written in Haskell.

This is intended as a beginners tutorial for learning Haskell from a "Lets just solve things already!" point of view. The examples should help give a flavour of the beauty and expressiveness of Haskell programming.

--
-- Some unix-like tools written in elegant Haskell
--

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

-- 
-- First, a useful helper
--
input f = interact (unlines . f . lines)

--
-- The 'cat' program
--
cat     = input id

--
-- Sort a file
--
sort'   = input sort

-- 
-- Reverse a file (tac)
--
tac     = input reverse

--
-- Return the head -10 line of a file
--
head'   = input $ take 10

--
-- Remove the first 10 lines of a file
--
drop'   = input $ drop 10

--
-- Return the tail -1 line of a file
--
tail'   = input $ (:[]) . last

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

--
-- double space a file
--
space   = input $ intersperse ""

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

--
-- remove the first occurence of the line "str"
--
remove  = input $ delete "str"

--
-- make a file all upper case
--
upper   = interact $ map toUpper

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

--
-- join lines of a file
--
join    = input $ (:[]) . 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')

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

--
-- Count number of lines in a file, like wc -l
--
wc_l    = interact $ show . length . lines

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

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

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

--
-- number each line of a file
--
num     = input $ zipWith ((. (' ':)) . shows) [1..]

--
-- Compute a simple cksum of a file
--
main    = interact $ printf "%u\n" . foldl' k 5381
    where k h c = h * 33 + fromIntegral (ord c) :: Int