Skip to content

Instantly share code, notes, and snippets.

@gelisam
Last active December 22, 2015 10:29
Show Gist options
  • Save gelisam/6459023 to your computer and use it in GitHub Desktop.
Save gelisam/6459023 to your computer and use it in GitHub Desktop.
The ~/.hawk/prelude.hs you would need in order to run the tree command in the Hawk README.
{-# LANGUAGE FlexibleInstances, OverloadedStrings #-}
import Prelude
import qualified Data.ByteString.Lazy.Char8 as B
import qualified Data.List as L
import Data.Monoid
import Data.Tree hiding (Forest)
import System.Console.Hawk.Representable
newtype Forest a = Forest {unForest :: [Tree a]}
deriving Show
instance Functor Forest where
fmap f = Forest . (fmap.fmap) f . unForest
instance Row a => Rows (Tree a) where
repr d = display ""
where
display indent (Node x ts) = line:lines
where
line = indent <> repr' d x
lines = concatMap (display indent') ts
indent' = " " <> indent
instance Row a => Rows (Forest a) where
repr d (Forest ts) = concatMap (repr d) ts
tree :: Ord p => (a -> p) -> (a -> p) -> [a] -> Forest a
tree pid ppid xs = Forest $ unfoldForest node roots
where
roots = filter_ppid (`notElem` map pid xs) xs
node x = (x, children x)
children x = filter_ppid (== pid x) xs
filter_ppid p = filter (p . ppid)
@gelisam
Copy link
Author

gelisam commented Sep 6, 2013

You can use the tree command as follows.

> ps -eo 'pid,ppid,comm' | hawk -a 'fmap (drop 2) . tree (!! 0) (!! 1) . tail'
[...]
  login
    -bash
      ps
      hawk

This asks ps to output three columns: the process id, the parent process id, and the command. Then, hawk runs the output through three more steps. First, the headers row is stripped off by tail. Next, the remaining rows are arranged as a tree, using the first two columns as keys and parent keys. Finally, drop 2 removes those two columns from the output, resulting in a tree of commands.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment