[Haskell-cafe] Best practices for modular programming in Haskell

Claus Reinke claus.reinke at talk21.com
Thu Mar 17 18:18:55 EST 2005


as an aside/work-around: you are aware of  ":browse", ":info", and 
the like? e.g., in ghci (6.2.1; I think ":info" should be even better in 6.4):

Prelude> :browse Control.Concurrent.MVar
data MVar a =
modifyMVar :: forall a b. MVar a -> (a -> IO (a, b)) -> IO b
modifyMVar_ :: forall a. MVar a -> (a -> IO a) -> IO ()
readMVar :: forall a. MVar a -> IO a
swapMVar :: forall a. MVar a -> a -> IO a
withMVar :: forall a b. MVar a -> (a -> IO b) -> IO b
addMVarFinalizer :: forall a. MVar a -> IO () -> IO ()
isEmptyMVar :: forall a. MVar a -> IO Bool
newEmptyMVar :: forall a. IO (MVar a)
newMVar :: forall a. a -> IO (MVar a)
putMVar :: forall a. MVar a -> a -> IO ()
takeMVar :: forall a. MVar a -> IO a
tryPutMVar :: forall a. MVar a -> a -> IO Bool
tryTakeMVar :: forall a. MVar a -> IO (Maybe a)

Prelude> :info Num
-- Num is a class
class (Eq a, Show a) => Num a where {
    (-) :: a -> a -> a {- has default method -};
    (*) :: a -> a -> a;
    (+) :: a -> a -> a;
    negate :: a -> a {- has default method -};
    signum :: a -> a;
    abs :: a -> a;
    fromInteger :: Integer -> a;
    }

it is also not to difficult to use ":browse" from within a good editor to 
auto-generate an explicit export or import interface, by turning the
type parts into comments. I used to do such hacks based on Hugs,
but haven't updated them for a long time (ultimately, many of the
things one would want to do with export/import lists should find
their way into HaRe, the Haskell Refactorer, but that is work in 
progress: http://www.cs.kent.ac.uk/projects/refactor-fp/hare.html ).

hth,
claus

> > It wouldn't be too hard to add a plain ASCII backend to Haddock that
> > generates the interfaces for modules without the implementation - that
> > would address Benjamin's concern to some extent.
> 
> Yes, that would be most helpful.
> 
> It's still not quite perfect because there is a typesetting step between
> what the programmer is writing in the .hs file and the way the generated
> interface looks -- people have to actually go to the trouble of running
> Haddock and double-checking that their interfaces look the way they intend.
> But I expect that this would become habitual pretty quickly, for those that
> care about this kind of interface documentation.
> 
>     - Benjamin




More information about the Haskell-Cafe mailing list