Disclipline for re-use: Slim instances

Although the trigger for this comes from a thread in glasgow-haskell-users,
I think that for the general problem,
the libraries list is the right forum.
Of course, the prelude and standard libraries aspect of
haskell-prime should be influenced as well,
but I am hesitant to cross-post.
Serge D. Mechveliani
I need to print in a special way the data of [Equation], (Term, Term), [(Term, Term)], (Equation, Equation).
The first can be by defining showList in instance Show Equation. But Show has not a method of showPair. So, I need to write the function showsTermPair and to use it together with another home-made function showsListGeneric.
I have been bitten by this, too, so let me make the point more explicit: For lists, the Haskell98 report contains: | class Show a where | showsPrec :: Int -> a -> ShowS | show :: a -> String | showList :: [a] -> ShowS | | -- Mimimal complete definition: | -- show or showsPrec | showsPrec _ x s = show x ++ s | | show x = showsPrec 0 x "" | | showList [] = showString "[]" | showList (x:xs) = showChar '[' . shows x . showl xs | where showl [] = showChar ']' | showl (x:xs) = showChar ',' . shows x . | showl xs The proposed function showsListGeneric would of course be:
showsListGeneric shows [] = showString "[]" showsListGeneric shows (x:xs) = showChar '[' . shows x . showl xs where showl [] = showChar ']' showl (x:xs) = showChar ',' . shows x . showl xs
If this was defined in the prelude, then the default definition in the class declaration would become:
class Show a where -- [...]
showList = showsListGeneric shows
Similarly, for pairs the prelude has: | instance (Show a, Show b) => Show (a,b) where | showsPrec p (x,y) = showChar '(' . shows x . showChar ',' . | shows y . showChar ')' The suggested function showPair is of course:
showPair shows1 shows2 (x,y) = showChar '(' . shows1 x . showChar ',' . shows2 y . showChar ')'
Again, if this was defined in the prelude, the instance declaration would become:
instance (Show a, Show b) => Show (a,b) where showsPrec p (x,y) = showPair shows shows
The problem we encounter here is that instance declarations and default definitions contain unnamed functions, which however frequently are also useful in other contexts. Since it does not appear to be attractive or easy to introduce (into the language definition) a naming scheme for these functions, I propose to introduce the following discipline for all library developers: ********************************************* * All instance declarations should be slim. * ********************************************* I.e.: * Instance declarations (and default definitions) should never contain non-trivial function definitions. * Instance declarations (and default definitions) should only provide ``plumbing'' to make existing functions accessible via the type class resolution mechanism. * The ``plumbed'' functions should always be exported (since instances are always exported). Since the naming will not always be straight-forward, the last point is particularly important and would enable more re-use and less re-invention of mostly trivial wheels. I append the ``TextFunctors'' module which I mostly pulled out of GHC's internals; the commented-out part of the export list shows where these belong in the code base of GHC; in my opinion, they should of course also be in the standard libraries. Wolfram ======= TextFunctors.lhs ================================================ \section{Read and Show Functors} \begin{code} module TextFunctors ( module TextFunctors -- -- the exported functions should really be imported -- -- from the following locations: -- , GHC.Show.showsPrecMaybe -- , GHC.Show.showsPrecEither -- , GHC.Show.showsPrecTup2 -- , GHC.Show.showsPrecTup3 -- , GHC.Show.showsPrecTup4 -- , GHC.Show.showsPrecTup5 -- , GHC.Read.readPrecMaybe -- , GHC.Read.readPrecEither -- , GHC.Read.readPrecArray -- , GHC.Read.readPrecTup2 -- , GHC.Read.readPrecTup3 -- , GHC.Read.readPrecTup4 -- , GHC.Read.readPrecTup5 , GHC.Read.Read(..) ) where import qualified GHC.Show import qualified GHC.Read -- the following imports are necessary for the read functions: import Text.ParserCombinators.ReadPrec import Array import qualified Text.Read.Lex as L \end{code} %{{{ \subsection{Show} \subsection{Show} \begin{code} type ShowSPrec a = Int -> a -> ShowS showsPrecList :: ShowSPrec a -> ShowSPrec [a] showsPrecList showsPrec p = GHC.Show.showList__ (showsPrec 0) \end{code} \begin{code} showsPrecMaybe :: ShowSPrec a -> ShowSPrec (Maybe a) showsPrecMaybe _showsPrec _p Nothing s = showString "Nothing" s showsPrecMaybe showsPrec p (Just x) s = (showParen (p > appPrec) $ showString "Just " . showsPrec appPrec1 x) s \end{code} \begin{code} showsPrecEither :: ShowSPrec a -> ShowSPrec b -> ShowSPrec (Either a b) showsPrecEither showsPrecA showsPrecB p e s = (showParen (p > appPrec) $ case e of Left a -> showString "Left " . showsPrecA appPrec1 a Right b -> showString "Right " . showsPrecB appPrec1 b ) s \end{code} \begin{code} showsPrecTup2 showsPrecA showsPrecB _ (x,y) s = (showChar '(' . showsPrecA noPrec x . showChar ',' . showChar ' ' . showsPrecB noPrec y . showChar ')' ) s \end{code} \begin{code} showsPrecTup3 showsPrecA showsPrecB showsPrecC _ (x,y,z) s = (showChar '(' . showsPrecA noPrec x . showChar ',' . showChar ' ' . showsPrecB noPrec y . showChar ',' . showChar ' ' . showsPrecC noPrec z . showChar ')' ) s \end{code} \begin{code} showsPrecTup4 showsPrecA showsPrecB showsPrecC showsPrecD _ (x,y,z,u) s = (showChar '(' . showsPrecA noPrec x . showChar ',' . showChar ' ' . showsPrecB noPrec y . showChar ',' . showChar ' ' . showsPrecC noPrec z . showChar ',' . showChar ' ' . showsPrecD noPrec u . showChar ')' ) s \end{code} \begin{code} showsPrecTup5 showsPrecA showsPrecB showsPrecC showsPrecD showsPrecE _ (x,y,z,u,v) s = (showChar '(' . showsPrecA noPrec x . showChar ',' . showChar ' ' . showsPrecB noPrec y . showChar ',' . showChar ' ' . showsPrecC noPrec z . showChar ',' . showChar ' ' . showsPrecD noPrec u . showChar ',' . showChar ' ' . showsPrecE noPrec v . showChar ')' ) s \end{code} \begin{code} noPrec :: Int noPrec = 0 appPrec = GHC.Show.appPrec appPrec1 = GHC.Show.appPrec1 \end{code} %}}} %{{{ \subsection{Read} \subsection{Read} \begin{code} readPrecList = GHC.Read.list \end{code} \begin{code} readPrecMaybe :: ReadPrec a -> ReadPrec (Maybe a) readPrecMaybe readPrec = parens (do L.Ident "Nothing" <- lexP return Nothing +++ prec appPrec ( do L.Ident "Just" <- lexP x <- step readPrec return (Just x)) ) \end{code} \begin{code} readPrecEither :: ReadPrec a -> ReadPrec b -> ReadPrec (Either a b) readPrecEither readPrecA readPrecB = parens ( prec appPrec ( do L.Ident "Left" <- lexP x <- step readPrecA return (Left x) +++ do L.Ident "Right" <- lexP y <- step readPrecB return (Right y) ) ) \end{code} \begin{code} readPrecArray :: Ix i => ReadPrec i -> ReadPrec a -> ReadPrec (Array i a) readPrecArray readPrecI readPrecA = parens $ prec appPrec $ do L.Ident "array" <- lexP bounds <- step (readPrecTup2 readPrecI readPrecI) vals <- step (GHC.Read.list (readPrecTup2 readPrecI readPrecA)) return (array bounds vals) \end{code} \begin{code} readPrecTup2 readPrecA readPrecB = parens ( paren ( do x <- readPrecA L.Punc "," <- lexP y <- readPrecB return (x,y) ) ) \end{code} \begin{code} readPrecTup3 readPrecA readPrecB readPrecC = parens ( paren ( do x <- readPrecA L.Punc "," <- lexP y <- readPrecB L.Punc "," <- lexP z <- readPrecC return (x,y,z) ) ) \end{code} \begin{code} readPrecTup4 readPrecA readPrecB readPrecC readPrecD = parens ( paren ( do w <- readPrecA L.Punc "," <- lexP x <- readPrecB L.Punc "," <- lexP y <- readPrecC L.Punc "," <- lexP z <- readPrecD return (w,x,y,z) ) ) \end{code} \begin{code} readPrecTup5 readPrecA readPrecB readPrecC readPrecD readPrecE = parens ( paren ( do v <- readPrecA L.Punc "," <- lexP w <- readPrecB L.Punc "," <- lexP x <- readPrecC L.Punc "," <- lexP y <- readPrecD L.Punc "," <- lexP z <- readPrecE return (v,w,x,y,z) ) ) \end{code} \begin{code} paren = GHC.Read.paren parens = GHC.Read.parens lexP = GHC.Read.lexP \end{code} %}}} %{{{ EMACS lv % Local Variables: % folded-file: t % fold-internal-margins: 0 % eval: (fold-set-marks "%{{{ " "%}}}") % eval: (fold-whole-buffer) % end: %}}}

On Tue, 5 Sep 2006 kahl@cas.mcmaster.ca wrote:
********************************************* * All instance declarations should be slim. * ********************************************* I.e.:
* Instance declarations (and default definitions) should never contain non-trivial function definitions.
* Instance declarations (and default definitions) should only provide ``plumbing'' to make existing functions accessible via the type class resolution mechanism.
* The ``plumbed'' functions should always be exported (since instances are always exported).
I endorse that suggestion. What about adding some note on the Wiki's Style section?
participants (2)
-
Henning Thielemann
-
kahl@cas.mcmaster.ca