-- | More concrete prettyprinting. -- this should be a separated package. {-# LANGUAGE TypeFamilies, FlexibleContexts, FlexibleInstances, CPP #-} module Math.FreeModule.PP where -------------------------------------------------------------------------------- import Data.Ratio import Math.FreeModule.Class import Math.FreeModule.Symbol import Math.FreeModule.PrettyPrint import qualified Math.FreeModule.SortedList as SL import Math.Algebra.ModP -------------------------------------------------------------------------------- class Pretty a where pretty :: a -> String pp :: Pretty a => a -> IO () pp = putStrLn . pretty -------------------------------------------------------------------------------- instance Pretty Symbol where pretty = showSymbol --instance (Pretty b, Ord b, Real c, Show c) => Pretty (SL.FreeMod b c) where -- pretty = bracket (prettyPrintRealWith pretty) instance (Pretty b, Ord b) => Pretty (SL.FreeMod b Zp) where pretty = bracket (prettyPrintArbWith pretty showZp) showZp :: Zp -> String showZp (Zp n) = show n instance (Pretty b, Ord b) => Pretty (SL.FreeMod b Integer) where pretty = bracket (prettyPrintRealWith' show pretty) instance (Pretty b, Ord b) => Pretty (SL.FreeMod b Rational) where pretty = bracket (prettyPrintRealWith' showRational pretty) showRational :: Rational -> String showRational r = if denominator r == 1 then show (numerator r) else "(" ++ show (numerator r) ++ "/" ++ show (denominator r) ++ ")" --------------------------------------------------------------------------------