A convenient way to deal with conditional function composition?

Hello all, I have found myself writing instances of Show for some types of mine, and I did so by defining the showsPrec function, for performance reasons. I ended up with code that I find quite inelegant. Here's an example: data Move = Move { movePiece :: PieceType, moveFile :: Maybe File, moveTarget :: Square, moveIsCapture :: Bool --movePromotion :: Maybe PieceType } deriving (Eq) instance Show Move where showsPrec _ Move { movePiece = p, moveFile = f, moveTarget = s, moveIsCapture = c } = (if p /= Pawn then shows p else id) . (maybe id shows f) . (if c then ('x':) else id) . shows s I considered writing a conditional composiion combinator to avoid all the 'if foo then f else id' code. Something looking like this: f .? True g = f . g f .? False g = f I'm not sure this is the best approach though, and I would be happy to hear about your suggestions for improving the style of this code, or any other comment that you think is appropriate. Thanks, Maxime

Maxime Henrion wrote:
Hello all,
I have found myself writing instances of Show for some types of mine, and I did so by defining the showsPrec function, for performance reasons. I ended up with code that I find quite inelegant. Here's an example:
data Move = Move { movePiece :: PieceType, moveFile :: Maybe File, moveTarget :: Square, moveIsCapture :: Bool --movePromotion :: Maybe PieceType } deriving (Eq)
instance Show Move where showsPrec _ Move { movePiece = p, moveFile = f, moveTarget = s, moveIsCapture = c } = (if p /= Pawn then shows p else id) . (maybe id shows f) . (if c then ('x':) else id) . shows s
I considered writing a conditional composiion combinator to avoid all the 'if foo then f else id' code. Something looking like this:
f .? True g = f . g f .? False g = f
I'm not sure this is the best approach though, and I would be happy to hear about your suggestions for improving the style of this code, or any other comment that you think is appropriate.
Thanks, Maxime
Well, since ((.) :: ShowS -> ShowS -> ShowS) is a Monoid, you can use Writer to create the result:
import Control.Monad import Control.Monad.Writer
type Writes = Writer ShowS ()
data PieceType = Pawn | Other deriving (Eq,Show) type File = Int type Square = Int
data Move = Move { movePiece :: PieceType, moveFile :: Maybe File, moveTarget :: Square, moveIsCapture :: Bool --movePromotion :: Maybe PieceType } deriving (Eq)
instance Show Move where showsPrec = showsPrec_Move
showsPrec_Move :: Int -> Move -> ShowS showsPrec_Move _ Move { movePiece = p , moveFile = f , moveTarget = s , moveIsCapture = c } = execWriter $ do when (p/=Pawn) (tell (shows p)) maybe (return ()) (tell . shows) f when c (tell ('x':)) tell (shows s)
testMove = Move Other (Just 6) 10 True
which gives
*Main> testMove Other6x10 *Main> testMove { movePiece=Pawn } 6x10 *Main> testMove { movePiece=Pawn, moveIsCapture=False } 610

On Tue, Apr 10, 2007 at 02:33:41PM +0100, Chris Kuklewicz wrote:
Well, since ((.) :: ShowS -> ShowS -> ShowS) is a Monoid, you can use Writer to create the result:
Not portably. stefan@stefans:~$ ghc-6.4.2 -e '( ("foo"++) `Data.Monoid.mappend` ("bar"++) ) "END"' "foobarEND" stefan@stefans:~$ ghc-6.6 -e '( ("foo"++) `Data.Monoid.mappend` ("bar"++) ) "END"' "fooENDbarEND" -- 6.6 sources instance Monoid b => Monoid (a -> b) where mempty _ = mempty mappend f g x = f x `mappend` g x Stefan

Using the Endo newtype can avoid such ambiguities:
http://darcs.haskell.org/packages/base/Data/Monoid.hs
newtype Endo a = Endo { appEndo :: a -> a }
instance Monoid (Endo a) where
mempty = Endo id
Endo f `mappend` Endo g = Endo (f . g)
Endo allows you to explicitly select the monoid behavior of the
endomorphism String -> String instead of using String -> String as an
exponent. It seems 6.4.2 -> 6.6 made a change from a default Monoid
instance for (a -> a) to the more general Monoid instance for (a ->
b).
On 4/10/07, Stefan O'Rear
On Tue, Apr 10, 2007 at 02:33:41PM +0100, Chris Kuklewicz wrote:
Well, since ((.) :: ShowS -> ShowS -> ShowS) is a Monoid, you can use Writer to create the result:
Not portably.
stefan@stefans:~$ ghc-6.4.2 -e '( ("foo"++) `Data.Monoid.mappend` ("bar"++) ) "END"' "foobarEND" stefan@stefans:~$ ghc-6.6 -e '( ("foo"++) `Data.Monoid.mappend` ("bar"++) ) "END"' "fooENDbarEND"
-- 6.6 sources instance Monoid b => Monoid (a -> b) where mempty _ = mempty mappend f g x = f x `mappend` g x
Stefan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Nicolas Frisby wrote:
Not portably.
stefan@stefans:~$ ghc-6.4.2 -e '( ("foo"++) `Data.Monoid.mappend` ("bar"++) ) "END"' "foobarEND" stefan@stefans:~$ ghc-6.6 -e '( ("foo"++) `Data.Monoid.mappend` ("bar"++) ) "END"' "fooENDbarEND"
-- 6.6 sources instance Monoid b => Monoid (a -> b) where mempty _ = mempty mappend f g x = f x `mappend` g x
Stefan
Thanks for the reminder. So the fixed 6.6 code is
import Control.Monad(when) import Control.Monad.Writer(Writer,tell,execWriter) import Data.Monoid(Endo(..))
type Writes = Writer (Endo String) ()
data PieceType = Pawn | Other deriving (Eq,Show) type File = Int type Square = Int
data Move = Move { movePiece :: PieceType, moveFile :: Maybe File, moveTarget :: Square, moveIsCapture :: Bool --movePromotion :: Maybe PieceType } deriving (Eq)
instance Show Move where showsPrec = showsPrec_Move
tShow :: Show a => a -> Writes tShow = tell . Endo . shows
tChar :: Char -> Writes tChar = tell . Endo . (:)
tString :: String -> Writes tString = tell . Endo . (++)
showsPrec_Move :: Int -> Move -> ShowS showsPrec_Move _ Move { movePiece = p , moveFile = f , moveTarget = s , moveIsCapture = c } = appEndo . execWriter $ do when (p/=Pawn) (tShow p) maybe (return ()) tShow f when c (tChar 'x') tShow s
testMove = Move Other (Just 6) 10 True

Chris Kuklewicz wrote:
Nicolas Frisby wrote:
Not portably.
stefan@stefans:~$ ghc-6.4.2 -e '( ("foo"++) `Data.Monoid.mappend` ("bar"++) ) "END"' "foobarEND" stefan@stefans:~$ ghc-6.6 -e '( ("foo"++) `Data.Monoid.mappend` ("bar"++) ) "END"' "fooENDbarEND"
-- 6.6 sources instance Monoid b => Monoid (a -> b) where mempty _ = mempty mappend f g x = f x `mappend` g x
Stefan
Thanks for the reminder. So the fixed 6.6 code is
import Control.Monad(when) import Control.Monad.Writer(Writer,tell,execWriter) import Data.Monoid(Endo(..))
type Writes = Writer (Endo String) ()
data PieceType = Pawn | Other deriving (Eq,Show) type File = Int type Square = Int
data Move = Move { movePiece :: PieceType, moveFile :: Maybe File, moveTarget :: Square, moveIsCapture :: Bool --movePromotion :: Maybe PieceType } deriving (Eq)
instance Show Move where showsPrec = showsPrec_Move
tShow :: Show a => a -> Writes tShow = tell . Endo . shows
tChar :: Char -> Writes tChar = tell . Endo . (:)
tString :: String -> Writes tString = tell . Endo . (++)
showsPrec_Move :: Int -> Move -> ShowS showsPrec_Move _ Move { movePiece = p , moveFile = f , moveTarget = s , moveIsCapture = c } = appEndo . execWriter $ do when (p/=Pawn) (tShow p) maybe (return ()) tShow f when c (tChar 'x') tShow s
testMove = Move Other (Just 6) 10 True
Thanks a lot for all the nice answers, guys. I have a few remaining questions if you don't mind though. Should I expect significant performance reduction by using the Writer monad here, as opposed to the version I wrote? And, most importantly, I'd like to know how *you* would write this if you had to :-). Would you juse the Writer monad version? Thanks, Maxime
participants (4)
-
Chris Kuklewicz
-
Maxime Henrion
-
Nicolas Frisby
-
Stefan O'Rear