FiniteCategories-0.6.4.0: Finite categories and usual categorical constructions on them.
CopyrightGuillaume Sabbagh 2022
LicenseGPL-3
Maintainerguillaumesabbagh@protonmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.IO.PrettyPrint

Description

A simple typeclass for things to be pretty printed. Categories objects and arrows should be pretty printable to be exported with graphviz. Different objects should be pretty printed into different strings or the graphviz export might be wrong.

Synopsis

Documentation

class PrettyPrint a where Source #

The typeclass of things that can be pretty printed.

pprint takes a level of verbosity as its first argument from the less verbose 'pprint 0' to the most verbose 'pprint n'.

Minimal complete definition

Nothing

Methods

pprint :: Int -> a -> String Source #

Pretty print an element of type a with a given verbosity level. 0 is the less verbose possible.

default pprint :: (Generic a, GPrettyPrint (Rep a)) => Int -> a -> String Source #

pprintWithIndentations Source #

Arguments

:: Int

The current verbosity level

-> Int

Original verbosity level

-> String

The indentation used

-> a

The object to pretty print

-> String 

Pretty print with a given level of indentation an element of type a with a given verbosity level. See pprintIndent for usage.

default pprintWithIndentations :: (Generic a, GPrettyPrint (Rep a)) => Int -> Int -> String -> a -> String Source #

pprintIndent :: Int -> a -> String Source #

Pretty print with indentation an element of type a with a given verbosity level.

Instances

Instances details
PrettyPrint DiscreteTwo Source # 
Instance details

Defined in Math.FiniteCategories.DiscreteTwo

Methods

pprint :: Int -> DiscreteTwo -> String Source #

pprintWithIndentations :: Int -> Int -> String -> DiscreteTwo -> String Source #

pprintIndent :: Int -> DiscreteTwo -> String Source #

PrettyPrint DiscreteTwoOb Source # 
Instance details

Defined in Math.FiniteCategories.DiscreteTwo

Methods

pprint :: Int -> DiscreteTwoOb -> String Source #

pprintWithIndentations :: Int -> Int -> String -> DiscreteTwoOb -> String Source #

pprintIndent :: Int -> DiscreteTwoOb -> String Source #

PrettyPrint Hat Source # 
Instance details

Defined in Math.FiniteCategories.Hat

Methods

pprint :: Int -> Hat -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Hat -> String Source #

pprintIndent :: Int -> Hat -> String Source #

PrettyPrint HatAr Source # 
Instance details

Defined in Math.FiniteCategories.Hat

Methods

pprint :: Int -> HatAr -> String Source #

pprintWithIndentations :: Int -> Int -> String -> HatAr -> String Source #

pprintIndent :: Int -> HatAr -> String Source #

PrettyPrint HatOb Source # 
Instance details

Defined in Math.FiniteCategories.Hat

Methods

pprint :: Int -> HatOb -> String Source #

pprintWithIndentations :: Int -> Int -> String -> HatOb -> String Source #

pprintIndent :: Int -> HatOb -> String Source #

PrettyPrint One Source # 
Instance details

Defined in Math.FiniteCategories.One

Methods

pprint :: Int -> One -> String Source #

pprintWithIndentations :: Int -> Int -> String -> One -> String Source #

pprintIndent :: Int -> One -> String Source #

PrettyPrint Parallel Source # 
Instance details

Defined in Math.FiniteCategories.Parallel

Methods

pprint :: Int -> Parallel -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Parallel -> String Source #

pprintIndent :: Int -> Parallel -> String Source #

PrettyPrint ParallelAr Source # 
Instance details

Defined in Math.FiniteCategories.Parallel

Methods

pprint :: Int -> ParallelAr -> String Source #

pprintWithIndentations :: Int -> Int -> String -> ParallelAr -> String Source #

pprintIndent :: Int -> ParallelAr -> String Source #

PrettyPrint ParallelOb Source # 
Instance details

Defined in Math.FiniteCategories.Parallel

Methods

pprint :: Int -> ParallelOb -> String Source #

pprintWithIndentations :: Int -> Int -> String -> ParallelOb -> String Source #

pprintIndent :: Int -> ParallelOb -> String Source #

PrettyPrint Square Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

pprint :: Int -> Square -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Square -> String Source #

pprintIndent :: Int -> Square -> String Source #

PrettyPrint SquareAr Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

pprint :: Int -> SquareAr -> String Source #

pprintWithIndentations :: Int -> Int -> String -> SquareAr -> String Source #

pprintIndent :: Int -> SquareAr -> String Source #

PrettyPrint SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

pprint :: Int -> SquareOb -> String Source #

pprintWithIndentations :: Int -> Int -> String -> SquareOb -> String Source #

pprintIndent :: Int -> SquareOb -> String Source #

PrettyPrint V Source # 
Instance details

Defined in Math.FiniteCategories.V

Methods

pprint :: Int -> V -> String Source #

pprintWithIndentations :: Int -> Int -> String -> V -> String Source #

pprintIndent :: Int -> V -> String Source #

PrettyPrint VAr Source # 
Instance details

Defined in Math.FiniteCategories.V

Methods

pprint :: Int -> VAr -> String Source #

pprintWithIndentations :: Int -> Int -> String -> VAr -> String Source #

pprintIndent :: Int -> VAr -> String Source #

PrettyPrint VOb Source # 
Instance details

Defined in Math.FiniteCategories.V

Methods

pprint :: Int -> VOb -> String Source #

pprintWithIndentations :: Int -> Int -> String -> VOb -> String Source #

pprintIndent :: Int -> VOb -> String Source #

PrettyPrint Int16 Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Int16 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Int16 -> String Source #

pprintIndent :: Int -> Int16 -> String Source #

PrettyPrint Int32 Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Int32 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Int32 -> String Source #

pprintIndent :: Int -> Int32 -> String Source #

PrettyPrint Int64 Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Int64 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Int64 -> String Source #

pprintIndent :: Int -> Int64 -> String Source #

PrettyPrint Int8 Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Int8 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Int8 -> String Source #

pprintIndent :: Int -> Int8 -> String Source #

PrettyPrint Word16 Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Word16 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Word16 -> String Source #

pprintIndent :: Int -> Word16 -> String Source #

PrettyPrint Word32 Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Word32 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Word32 -> String Source #

pprintIndent :: Int -> Word32 -> String Source #

PrettyPrint Word64 Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Word64 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Word64 -> String Source #

pprintIndent :: Int -> Word64 -> String Source #

PrettyPrint Word8 Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Word8 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Word8 -> String Source #

pprintIndent :: Int -> Word8 -> String Source #

PrettyPrint Ordering Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Ordering -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Ordering -> String Source #

pprintIndent :: Int -> Ordering -> String Source #

PrettyPrint Text Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Text -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Text -> String Source #

pprintIndent :: Int -> Text -> String Source #

PrettyPrint Integer Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Integer -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Integer -> String Source #

pprintIndent :: Int -> Integer -> String Source #

PrettyPrint Natural Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Natural -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Natural -> String Source #

pprintIndent :: Int -> Natural -> String Source #

PrettyPrint () Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> () -> String Source #

pprintWithIndentations :: Int -> Int -> String -> () -> String Source #

pprintIndent :: Int -> () -> String Source #

PrettyPrint Bool Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Bool -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Bool -> String Source #

pprintIndent :: Int -> Bool -> String Source #

PrettyPrint Char Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Char -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Char -> String Source #

pprintIndent :: Int -> Char -> String Source #

PrettyPrint Double Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Double -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Double -> String Source #

pprintIndent :: Int -> Double -> String Source #

PrettyPrint Float Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Float -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Float -> String Source #

pprintIndent :: Int -> Float -> String Source #

PrettyPrint Int Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Int -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Int -> String Source #

pprintIndent :: Int -> Int -> String Source #

PrettyPrint Word Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Word -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Word -> String Source #

pprintIndent :: Int -> Word -> String Source #

(PrettyPrint t, Eq t) => PrettyPrint (Exponential t) Source # 
Instance details

Defined in Math.CartesianClosedCategory

Methods

pprint :: Int -> Exponential t -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Exponential t -> String Source #

pprintIndent :: Int -> Exponential t -> String Source #

PrettyPrint (FinSet a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

pprint :: Int -> FinSet a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> FinSet a -> String Source #

pprintIndent :: Int -> FinSet a -> String Source #

(PrettyPrint a, Eq a) => PrettyPrint (Function a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

pprint :: Int -> Function a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Function a -> String Source #

pprintIndent :: Int -> Function a -> String Source #

PrettyPrint (Galaxy a) Source # 
Instance details

Defined in Math.Categories.Galaxy

Methods

pprint :: Int -> Galaxy a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Galaxy a -> String Source #

pprintIndent :: Int -> Galaxy a -> String Source #

PrettyPrint a => PrettyPrint (StarIdentity a) Source # 
Instance details

Defined in Math.Categories.Galaxy

Methods

pprint :: Int -> StarIdentity a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> StarIdentity a -> String Source #

pprintIndent :: Int -> StarIdentity a -> String Source #

PrettyPrint c => PrettyPrint (Op c) Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

pprint :: Int -> Op c -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Op c -> String Source #

pprintIndent :: Int -> Op c -> String Source #

PrettyPrint m => PrettyPrint (OpMorphism m) Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

pprint :: Int -> OpMorphism m -> String Source #

pprintWithIndentations :: Int -> Int -> String -> OpMorphism m -> String Source #

pprintIndent :: Int -> OpMorphism m -> String Source #

PrettyPrint (OrdinalCategory a) Source # 
Instance details

Defined in Math.Categories.OrdinalCategory

Methods

pprint :: Int -> OrdinalCategory a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> OrdinalCategory a -> String Source #

pprintIndent :: Int -> OrdinalCategory a -> String Source #

PrettyPrint a => PrettyPrint (IsSmallerThan a) Source # 
Instance details

Defined in Math.Categories.TotalOrder

Methods

pprint :: Int -> IsSmallerThan a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> IsSmallerThan a -> String Source #

pprintIndent :: Int -> IsSmallerThan a -> String Source #

PrettyPrint (TotalOrder a) Source # 
Instance details

Defined in Math.Categories.TotalOrder

Methods

pprint :: Int -> TotalOrder a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> TotalOrder a -> String Source #

pprintIndent :: Int -> TotalOrder a -> String Source #

(PrettyPrint a, Eq a) => PrettyPrint (Set a) Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Set a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Set a -> String Source #

pprintIndent :: Int -> Set a -> String Source #

PrettyPrint a => PrettyPrint (Set a) Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Set a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Set a -> String Source #

pprintIndent :: Int -> Set a -> String Source #

PrettyPrint a => PrettyPrint (Maybe a) Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Maybe a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Maybe a -> String Source #

pprintIndent :: Int -> Maybe a -> String Source #

PrettyPrint a => PrettyPrint [a] Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> [a] -> String Source #

pprintWithIndentations :: Int -> Int -> String -> [a] -> String Source #

pprintIndent :: Int -> [a] -> String Source #

(PrettyPrint n, PrettyPrint e) => PrettyPrint (Arrow n e) Source # 
Instance details

Defined in Math.Categories.FinGrph

Methods

pprint :: Int -> Arrow n e -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Arrow n e -> String Source #

pprintIndent :: Int -> Arrow n e -> String Source #

PrettyPrint (FinGrph n e) Source # 
Instance details

Defined in Math.Categories.FinGrph

Methods

pprint :: Int -> FinGrph n e -> String Source #

pprintWithIndentations :: Int -> Int -> String -> FinGrph n e -> String Source #

pprintIndent :: Int -> FinGrph n e -> String Source #

(PrettyPrint n, PrettyPrint e, Eq n, Eq e) => PrettyPrint (Graph n e) Source # 
Instance details

Defined in Math.Categories.FinGrph

Methods

pprint :: Int -> Graph n e -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Graph n e -> String Source #

pprintIndent :: Int -> Graph n e -> String Source #

(PrettyPrint n, PrettyPrint e, Eq n, Eq e) => PrettyPrint (GraphHomomorphism n e) Source # 
Instance details

Defined in Math.Categories.FinGrph

Methods

pprint :: Int -> GraphHomomorphism n e -> String Source #

pprintWithIndentations :: Int -> Int -> String -> GraphHomomorphism n e -> String Source #

pprintIndent :: Int -> GraphHomomorphism n e -> String Source #

PrettyPrint (FinSketch n e) Source # 
Instance details

Defined in Math.Categories.FinSketch

Methods

pprint :: Int -> FinSketch n e -> String Source #

pprintWithIndentations :: Int -> Int -> String -> FinSketch n e -> String Source #

pprintIndent :: Int -> FinSketch n e -> String Source #

(PrettyPrint n, PrettyPrint e, Eq e, Eq n) => PrettyPrint (LightConstruction n e) Source # 
Instance details

Defined in Math.Categories.FinSketch

Methods

pprint :: Int -> LightConstruction n e -> String Source #

pprintWithIndentations :: Int -> Int -> String -> LightConstruction n e -> String Source #

pprintIndent :: Int -> LightConstruction n e -> String Source #

(PrettyPrint n, PrettyPrint e, Eq n, Eq e) => PrettyPrint (Sketch n e) Source # 
Instance details

Defined in Math.Categories.FinSketch

Methods

pprint :: Int -> Sketch n e -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Sketch n e -> String Source #

pprintIndent :: Int -> Sketch n e -> String Source #

(PrettyPrint n, PrettyPrint e, Eq e, Eq n) => PrettyPrint (SketchError n e) Source # 
Instance details

Defined in Math.Categories.FinSketch

Methods

pprint :: Int -> SketchError n e -> String Source #

pprintWithIndentations :: Int -> Int -> String -> SketchError n e -> String Source #

pprintIndent :: Int -> SketchError n e -> String Source #

(PrettyPrint e, PrettyPrint n, Eq e, Eq n) => PrettyPrint (SketchMorphism n e) Source # 
Instance details

Defined in Math.Categories.FinSketch

Methods

pprint :: Int -> SketchMorphism n e -> String Source #

pprintWithIndentations :: Int -> Int -> String -> SketchMorphism n e -> String Source #

pprintIndent :: Int -> SketchMorphism n e -> String Source #

(PrettyPrint n, PrettyPrint e, Eq e, Eq n) => PrettyPrint (SketchMorphismError n e) Source # 
Instance details

Defined in Math.Categories.FinSketch

Methods

pprint :: Int -> SketchMorphismError n e -> String Source #

pprintWithIndentations :: Int -> Int -> String -> SketchMorphismError n e -> String Source #

pprintIndent :: Int -> SketchMorphismError n e -> String Source #

(PrettyPrint i, PrettyPrint t, Eq i) => PrettyPrint (Colimit i t) Source # 
Instance details

Defined in Math.CocompleteCategory

Methods

pprint :: Int -> Colimit i t -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Colimit i t -> String Source #

pprintIndent :: Int -> Colimit i t -> String Source #

(PrettyPrint oIndex, PrettyPrint t, Eq oIndex) => PrettyPrint (Limit oIndex t) Source # 
Instance details

Defined in Math.CompleteCategory

Methods

pprint :: Int -> Limit oIndex t -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Limit oIndex t -> String Source #

pprintIndent :: Int -> Limit oIndex t -> String Source #

(PrettyPrint a, PrettyPrint b, Eq a, Eq b) => PrettyPrint (CGMorphism a b) Source # 
Instance details

Defined in Math.FiniteCategories.CompositionGraph

Methods

pprint :: Int -> CGMorphism a b -> String Source #

pprintWithIndentations :: Int -> Int -> String -> CGMorphism a b -> String Source #

pprintIndent :: Int -> CGMorphism a b -> String Source #

(PrettyPrint a, PrettyPrint b, Eq a, Eq b) => PrettyPrint (CompositionGraph a b) Source # 
Instance details

Defined in Math.FiniteCategories.CompositionGraph

Methods

pprint :: Int -> CompositionGraph a b -> String Source #

pprintWithIndentations :: Int -> Int -> String -> CompositionGraph a b -> String Source #

pprintIndent :: Int -> CompositionGraph a b -> String Source #

(PrettyPrint a, PrettyPrint b, Eq a, Eq b) => PrettyPrint (SCGMorphism a b) Source # 
Instance details

Defined in Math.FiniteCategories.SafeCompositionGraph

Methods

pprint :: Int -> SCGMorphism a b -> String Source #

pprintWithIndentations :: Int -> Int -> String -> SCGMorphism a b -> String Source #

pprintIndent :: Int -> SCGMorphism a b -> String Source #

(PrettyPrint a, PrettyPrint b, Eq a, Eq b) => PrettyPrint (SafeCompositionGraph a b) Source # 
Instance details

Defined in Math.FiniteCategories.SafeCompositionGraph

Methods

pprint :: Int -> SafeCompositionGraph a b -> String Source #

pprintWithIndentations :: Int -> Int -> String -> SafeCompositionGraph a b -> String Source #

pprintIndent :: Int -> SafeCompositionGraph a b -> String Source #

(PrettyPrint m, PrettyPrint o) => PrettyPrint (FiniteCategoryError m o) Source # 
Instance details

Defined in Math.FiniteCategoryError

Methods

pprint :: Int -> FiniteCategoryError m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> FiniteCategoryError m o -> String Source #

pprintIndent :: Int -> FiniteCategoryError m o -> String Source #

(PrettyPrint a, Eq a, PrettyPrint b, Eq b) => PrettyPrint (Map a b) Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Map a b -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Map a b -> String Source #

pprintIndent :: Int -> Map a b -> String Source #

(PrettyPrint a, PrettyPrint b) => PrettyPrint (Either a b) Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> Either a b -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Either a b -> String Source #

pprintIndent :: Int -> Either a b -> String Source #

(PrettyPrint a, PrettyPrint b) => PrettyPrint (a, b) Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> (a, b) -> String Source #

pprintWithIndentations :: Int -> Int -> String -> (a, b) -> String Source #

pprintIndent :: Int -> (a, b) -> String Source #

(PrettyPrint c, PrettyPrint o, PrettyPrint m, Eq o, Eq m) => PrettyPrint (CandidateExponentialObjectCategory c m o) Source # 
Instance details

Defined in Math.CartesianClosedCategory

Methods

pprint :: Int -> CandidateExponentialObjectCategory c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> CandidateExponentialObjectCategory c m o -> String Source #

pprintIndent :: Int -> CandidateExponentialObjectCategory c m o -> String Source #

(PrettyPrint o, PrettyPrint c, PrettyPrint m, Eq o, Eq m) => PrettyPrint (CandidateExponentialObjectMorphism c m o) Source # 
Instance details

Defined in Math.CartesianClosedCategory

Methods

pprint :: Int -> CandidateExponentialObjectMorphism c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> CandidateExponentialObjectMorphism c m o -> String Source #

pprintIndent :: Int -> CandidateExponentialObjectMorphism c m o -> String Source #

(PrettyPrint o, PrettyPrint c, PrettyPrint m, Eq o, Eq m) => PrettyPrint (Tripod c m o) Source # 
Instance details

Defined in Math.CartesianClosedCategory

Methods

pprint :: Int -> Tripod c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Tripod c m o -> String Source #

pprintIndent :: Int -> Tripod c m o -> String Source #

(PrettyPrint o1, PrettyPrint o2, PrettyPrint m3) => PrettyPrint (CommaObject o1 o2 m3) Source # 
Instance details

Defined in Math.Categories.CommaCategory

Methods

pprint :: Int -> CommaObject o1 o2 m3 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> CommaObject o1 o2 m3 -> String Source #

pprintIndent :: Int -> CommaObject o1 o2 m3 -> String Source #

PrettyPrint (FinCat c m o) Source # 
Instance details

Defined in Math.Categories.FinCat

Methods

pprint :: Int -> FinCat c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> FinCat c m o -> String Source #

pprintIndent :: Int -> FinCat c m o -> String Source #

PrettyPrint c => PrettyPrint (ExponentialCategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.ExponentialCategory

Methods

pprint :: Int -> ExponentialCategory c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> ExponentialCategory c m o -> String Source #

pprintIndent :: Int -> ExponentialCategory c m o -> String Source #

(PrettyPrint m, PrettyPrint c, PrettyPrint o, Eq o, Eq m) => PrettyPrint (ExponentialCategoryMorphism c m o) Source # 
Instance details

Defined in Math.FiniteCategories.ExponentialCategory

Methods

pprint :: Int -> ExponentialCategoryMorphism c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> ExponentialCategoryMorphism c m o -> String Source #

pprintIndent :: Int -> ExponentialCategoryMorphism c m o -> String Source #

(PrettyPrint o, PrettyPrint c, PrettyPrint m, Eq o, Eq m) => PrettyPrint (ExponentialCategoryObject c m o) Source # 
Instance details

Defined in Math.FiniteCategories.ExponentialCategory

Methods

pprint :: Int -> ExponentialCategoryObject c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> ExponentialCategoryObject c m o -> String Source #

pprintIndent :: Int -> ExponentialCategoryObject c m o -> String Source #

(PrettyPrint c, PrettyPrint o, Eq o) => PrettyPrint (FullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

pprint :: Int -> FullSubcategory c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> FullSubcategory c m o -> String Source #

pprintIndent :: Int -> FullSubcategory c m o -> String Source #

(PrettyPrint c, PrettyPrint o, Eq o) => PrettyPrint (InheritedFullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

pprint :: Int -> InheritedFullSubcategory c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> InheritedFullSubcategory c m o -> String Source #

pprintIndent :: Int -> InheritedFullSubcategory c m o -> String Source #

(PrettyPrint c, PrettyPrint o, PrettyPrint m, Eq o, Eq m) => PrettyPrint (InheritedSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.Subcategory

Methods

pprint :: Int -> InheritedSubcategory c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> InheritedSubcategory c m o -> String Source #

pprintIndent :: Int -> InheritedSubcategory c m o -> String Source #

(PrettyPrint c, PrettyPrint o, PrettyPrint m, Eq o, Eq m) => PrettyPrint (Subcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.Subcategory

Methods

pprint :: Int -> Subcategory c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Subcategory c m o -> String Source #

pprintIndent :: Int -> Subcategory c m o -> String Source #

(PrettyPrint a, PrettyPrint b, PrettyPrint c) => PrettyPrint (a, b, c) Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> (a, b, c) -> String Source #

pprintWithIndentations :: Int -> Int -> String -> (a, b, c) -> String Source #

pprintIndent :: Int -> (a, b, c) -> String Source #

(PrettyPrint a, PrettyPrint b, PrettyPrint c, PrettyPrint d) => PrettyPrint (a, b, c, d) Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> (a, b, c, d) -> String Source #

pprintWithIndentations :: Int -> Int -> String -> (a, b, c, d) -> String Source #

pprintIndent :: Int -> (a, b, c, d) -> String Source #

(PrettyPrint m1, PrettyPrint m2, PrettyPrint o1, PrettyPrint o2, PrettyPrint m3) => PrettyPrint (CommaMorphism o1 o2 m1 m2 m3) Source # 
Instance details

Defined in Math.Categories.CommaCategory

Methods

pprint :: Int -> CommaMorphism o1 o2 m1 m2 m3 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> CommaMorphism o1 o2 m1 m2 m3 -> String Source #

pprintIndent :: Int -> CommaMorphism o1 o2 m1 m2 m3 -> String Source #

(PrettyPrint a, PrettyPrint b, PrettyPrint c, PrettyPrint d, PrettyPrint e) => PrettyPrint (a, b, c, d, e) Source # 
Instance details

Defined in Math.IO.PrettyPrint

Methods

pprint :: Int -> (a, b, c, d, e) -> String Source #

pprintWithIndentations :: Int -> Int -> String -> (a, b, c, d, e) -> String Source #

pprintIndent :: Int -> (a, b, c, d, e) -> String Source #

(PrettyPrint c1, PrettyPrint c2, PrettyPrint o1, PrettyPrint o2, PrettyPrint m1, PrettyPrint m2, Eq o1, Eq o2, Eq m1, Eq m2) => PrettyPrint (Diagram c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in Math.Categories.FunctorCategory

Methods

pprint :: Int -> Diagram c1 m1 o1 c2 m2 o2 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Diagram c1 m1 o1 c2 m2 o2 -> String Source #

pprintIndent :: Int -> Diagram c1 m1 o1 c2 m2 o2 -> String Source #

(PrettyPrint o1, PrettyPrint m1, PrettyPrint o2, PrettyPrint m2, Eq o1, Eq m1, Eq o2, Eq m2) => PrettyPrint (DiagramError c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in Math.Categories.FunctorCategory

Methods

pprint :: Int -> DiagramError c1 m1 o1 c2 m2 o2 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> DiagramError c1 m1 o1 c2 m2 o2 -> String Source #

pprintIndent :: Int -> DiagramError c1 m1 o1 c2 m2 o2 -> String Source #

(PrettyPrint c1, PrettyPrint c2) => PrettyPrint (FunctorCategory c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in Math.Categories.FunctorCategory

Methods

pprint :: Int -> FunctorCategory c1 m1 o1 c2 m2 o2 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> FunctorCategory c1 m1 o1 c2 m2 o2 -> String Source #

pprintIndent :: Int -> FunctorCategory c1 m1 o1 c2 m2 o2 -> String Source #

(PrettyPrint c1, PrettyPrint c2, PrettyPrint o1, PrettyPrint o2, PrettyPrint m1, PrettyPrint m2, Eq o1, Eq o2, Eq m1, Eq m2) => PrettyPrint (NaturalTransformation c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in Math.Categories.FunctorCategory

Methods

pprint :: Int -> NaturalTransformation c1 m1 o1 c2 m2 o2 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> NaturalTransformation c1 m1 o1 c2 m2 o2 -> String Source #

pprintIndent :: Int -> NaturalTransformation c1 m1 o1 c2 m2 o2 -> String Source #

(Eq o1, PrettyPrint c1, PrettyPrint c2, PrettyPrint m2, PrettyPrint o1, PrettyPrint m1) => PrettyPrint (NaturalTransformationError c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in Math.Categories.FunctorCategory

Methods

pprint :: Int -> NaturalTransformationError c1 m1 o1 c2 m2 o2 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> NaturalTransformationError c1 m1 o1 c2 m2 o2 -> String Source #

pprintIndent :: Int -> NaturalTransformationError c1 m1 o1 c2 m2 o2 -> String Source #

(PrettyPrint c, PrettyPrint cIndex, PrettyPrint oIndex, PrettyPrint mIndex, PrettyPrint o, PrettyPrint m, Eq o, Eq m, Eq oIndex, Eq c, Eq mIndex, FiniteCategory c m o, Morphism m o) => PrettyPrint (LimitCategory cIndex mIndex oIndex c m o) Source # 
Instance details

Defined in Math.FiniteCategories.LimitCategory

Methods

pprint :: Int -> LimitCategory cIndex mIndex oIndex c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> LimitCategory cIndex mIndex oIndex c m o -> String Source #

pprintIndent :: Int -> LimitCategory cIndex mIndex oIndex c m o -> String Source #

(PrettyPrint c1, PrettyPrint c3, PrettyPrint o1, PrettyPrint o3, PrettyPrint m1, PrettyPrint m3, PrettyPrint c2, PrettyPrint o2, PrettyPrint m2, Eq o1, Eq o3, Eq m1, Eq m3, Eq o2, Eq m2) => PrettyPrint (CommaCategory c1 m1 o1 c2 m2 o2 c3 m3 o3) Source # 
Instance details

Defined in Math.Categories.CommaCategory

Methods

pprint :: Int -> CommaCategory c1 m1 o1 c2 m2 o2 c3 m3 o3 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> CommaCategory c1 m1 o1 c2 m2 o2 c3 m3 o3 -> String Source #

pprintIndent :: Int -> CommaCategory c1 m1 o1 c2 m2 o2 c3 m3 o3 -> String Source #

(Eq o2, Eq o3, Eq m2, Eq m3, PrettyPrint c2, PrettyPrint c3, PrettyPrint o2, PrettyPrint o3, PrettyPrint m2, PrettyPrint m3, PrettyPrint c1) => PrettyPrint (PostcomposedFunctorCategory c1 m1 o1 c2 m2 o2 c3 m3 o3) Source # 
Instance details

Defined in Math.Categories.FunctorCategory

Methods

pprint :: Int -> PostcomposedFunctorCategory c1 m1 o1 c2 m2 o2 c3 m3 o3 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> PostcomposedFunctorCategory c1 m1 o1 c2 m2 o2 c3 m3 o3 -> String Source #

pprintIndent :: Int -> PostcomposedFunctorCategory c1 m1 o1 c2 m2 o2 c3 m3 o3 -> String Source #

(Eq o1, Eq o2, Eq m1, Eq m2, PrettyPrint c1, PrettyPrint c2, PrettyPrint o1, PrettyPrint o2, PrettyPrint m1, PrettyPrint m2, PrettyPrint c3) => PrettyPrint (PrecomposedFunctorCategory c1 m1 o1 c2 m2 o2 c3 m3 o3) Source # 
Instance details

Defined in Math.Categories.FunctorCategory

Methods

pprint :: Int -> PrecomposedFunctorCategory c1 m1 o1 c2 m2 o2 c3 m3 o3 -> String Source #

pprintWithIndentations :: Int -> Int -> String -> PrecomposedFunctorCategory c1 m1 o1 c2 m2 o2 c3 m3 o3 -> String Source #

pprintIndent :: Int -> PrecomposedFunctorCategory c1 m1 o1 c2 m2 o2 c3 m3 o3 -> String Source #

pp :: PrettyPrint a => Int -> a -> IO () Source #

PutStrLn composed with pprint. Takes a verbosity level as its first argument.

ppi :: PrettyPrint a => Int -> a -> IO () Source #

PutStrLn composed with pprintIndent. Takes a verbosity level as its first argument.

indentation :: Int -> String -> String Source #

Add indentation at the begining of a string.

pprintFunction :: (PrettyPrint a, PrettyPrint b) => Int -> (a -> b) -> [a] -> String Source #

Pretty print a function on a specific domain.

Orphan instances

Simplifiable Text Source # 
Instance details

Methods

simplify :: Text -> Text #