[Haskell] Re: ANNOUNCE: HNOP 0.1

Donald Bruce Stewart dons at cse.unsw.edu.au
Sat Jul 1 04:40:55 EDT 2006


bringert:
> >  noop :: IO ()  -- generalise to other Monads?
> >
> >This would actually not be too hard to write, given my existing work,
> >and then of course the executable would simply be a thin wrapper.
> 
> As suggested above, this patch moves the core functionality to a  
> library module, Control.Nop. Furthermore, the nop function is  
> generalized to a polyvariadic function, so that you can now write for  
> example:

Ah, great. Now we can write a fast nop using ByteStrings for speed.

    import Data.ByteString.Char8
    import Control.Nop

    -- | main, do nothing quickly
    main :: IO ()
    main = nop (pack "do nothing")

Demo patch for fast-hnop attached.

-- Don
-------------- next part --------------

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 at bringert.net**20060701081705] {
adddir ./Control
addfile ./Control/Nop.hs
hunk ./Control/Nop.hs 1
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Control.Nop
+-- Copyright   :  Copyright 2006, Bjorn Bringert (bjorn at bringert.net)
+-- License     :  BSD3
+--
+-- Maintainer  :  Bjorn Bringert <bjorn at 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
}

[Add demo fast-hnop, using Data.ByteString for speed
Don Stewart <dons at cse.unsw.edu.au>**20060701083508] {
addfile ./Fast.hs
hunk ./Fast.hs 1
+module Main where
+
+import Data.ByteString.Char8
+import Control.Nop
+
+-- | main, do nothing quickly
+main :: IO ()
+main = nop (pack "do nothing")
hunk ./hnop.cabal 5
-build-depends:       base
+build-depends:       base, fps
hunk ./hnop.cabal 11
+Executable:          fast-hnop
+Main-Is:             Fast.hs
+
}

Context:

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


More information about the Haskell mailing list