
New patches:

[Moved the definition of the nop function to a library module, Control.Nop. Reimplemented Main.hs using Control.Nop. Generalized the nop function to a polyvariadic function.
bjorn@bringert.net**20060701081705] {
adddir ./Control
addfile ./Control/Nop.hs
hunk ./Control/Nop.hs 1
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Control.Nop
+-- Copyright   :  Copyright 2006, Bjorn Bringert (bjorn@bringert.net)
+-- License     :  BSD3
+--
+-- Maintainer  :  Bjorn Bringert <bjorn@bringert.net>
+-- Stability   :  experimental
+-- Portability :  portable
+--
+-- This is a generalization of Ashley Yakeley's original HNOP
+-- program to a polyvariadic function, which still does nothing.
+-- The result is either an IO action which does nothing,
+-- or pure nothingness.
+-- 
+-----------------------------------------------------------------------------
+module Control.Nop where
+
+-- | The class of functions which do nothing.
+class Nop a where
+    -- | Do nothing. 
+    --   The most useful familiy of 'nop' functions is probably:
+    -- @nop :: a1 -> ... -> an -> IO ()@
+    nop :: a
+
+instance Nop () where
+    nop = ()
+
+instance Nop a => Nop (IO a) where
+    nop = return nop
+
+instance Nop b => Nop (a -> b) where
+    nop _ = nop
+
hunk ./Main.hs 4
+import Control.Nop
+
hunk ./Main.hs 8
-main = return ()
+main = nop
hunk ./hnop.cabal 6
+Exposed-modules: Control.Nop
}

Context:

[remove unnecessary Makefile
Ashley Yakeley <ashley@semantic.org>**20060630191533] 
[use correct GHC options pragma
Ashley Yakeley <ashley@semantic.org>**20060630191505] 
[fix up cabal file
Ashley Yakeley <ashley@semantic.org>**20060630075323] 
[haddock-ise hnop
dons@cse.unsw.edu.au**20060630073608] 
[cabalise hnop
dons@cse.unsw.edu.au**20060630073543] 
[initial version
Ashley Yakeley <ashley@semantic.org>**20060630034031] 
Patch bundle hash:
0e6747fd5f11b6599cac9d98c269b981a8f95af9
