
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