symantic-document-0.1.2.20180831: Document symantics.

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Document.Sym

Contents

Synopsis

Type Nat

newtype Nat Source #

Constructors

Nat 

Fields

Instances
Enum Nat Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

succ :: Nat -> Nat #

pred :: Nat -> Nat #

toEnum :: Int -> Nat #

fromEnum :: Nat -> Int #

enumFrom :: Nat -> [Nat] #

enumFromThen :: Nat -> Nat -> [Nat] #

enumFromTo :: Nat -> Nat -> [Nat] #

enumFromThenTo :: Nat -> Nat -> Nat -> [Nat] #

Eq Nat Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

(==) :: Nat -> Nat -> Bool #

(/=) :: Nat -> Nat -> Bool #

Integral Nat Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

quot :: Nat -> Nat -> Nat #

rem :: Nat -> Nat -> Nat #

div :: Nat -> Nat -> Nat #

mod :: Nat -> Nat -> Nat #

quotRem :: Nat -> Nat -> (Nat, Nat) #

divMod :: Nat -> Nat -> (Nat, Nat) #

toInteger :: Nat -> Integer #

Num Nat Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

(+) :: Nat -> Nat -> Nat #

(-) :: Nat -> Nat -> Nat #

(*) :: Nat -> Nat -> Nat #

negate :: Nat -> Nat #

abs :: Nat -> Nat #

signum :: Nat -> Nat #

fromInteger :: Integer -> Nat #

Ord Nat Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

compare :: Nat -> Nat -> Ordering #

(<) :: Nat -> Nat -> Bool #

(<=) :: Nat -> Nat -> Bool #

(>) :: Nat -> Nat -> Bool #

(>=) :: Nat -> Nat -> Bool #

max :: Nat -> Nat -> Nat #

min :: Nat -> Nat -> Nat #

Real Nat Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

toRational :: Nat -> Rational #

Show Nat Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

showsPrec :: Int -> Nat -> ShowS #

show :: Nat -> String #

showList :: [Nat] -> ShowS #

Class Lengthable

class Lengthable a where Source #

Minimal complete definition

length

Methods

length :: a -> Nat Source #

Instances
Lengthable Char Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

length :: Char -> Nat Source #

Lengthable Text Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

length :: Text -> Nat Source #

Lengthable Text Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

length :: Text -> Nat Source #

Lengthable [a] Source # 
Instance details

Defined in Language.Symantic.Document.Sym

Methods

length :: [a] -> Nat Source #

Class Splitable

class Monoid a => Splitable a where Source #

Minimal complete definition

null, tail, break

Methods

null :: a -> Bool Source #

tail :: a -> a Source #

break :: (Char -> Bool) -> a -> (a, a) Source #

lines :: a -> [a] Source #

words :: a -> [a] Source #

splitOnChar :: (Char -> Bool) -> a -> [a] Source #

Type Column

Type Indent

Class Textable

class (IsString d, Semigroup d) => Textable d where Source #

Methods

empty :: d Source #

charH Source #

Arguments

:: Char

XXX: MUST NOT be '\n'

-> d 

stringH Source #

Arguments

:: String

XXX: MUST NOT contain '\n'

-> d 

textH Source #

Arguments

:: Text

XXX: MUST NOT contain '\n'

-> d 

ltextH Source #

Arguments

:: Text

XXX: MUST NOT contain '\n'

-> d 

empty :: Textable (ReprOf d) => Trans d => d Source #

charH Source #

Arguments

:: Textable (ReprOf d) 
=> Trans d 
=> Char

XXX: MUST NOT be '\n'

-> d 

stringH Source #

Arguments

:: Textable (ReprOf d) 
=> Trans d 
=> String

XXX: MUST NOT contain '\n'

-> d 

textH Source #

Arguments

:: Textable (ReprOf d) 
=> Trans d 
=> Text

XXX: MUST NOT contain '\n'

-> d 

ltextH Source #

Arguments

:: Textable (ReprOf d) 
=> Trans d 
=> Text

XXX: MUST NOT contain '\n'

-> d 

newline :: d Source #

space :: d Source #

(<+>) :: d -> d -> d Source #

x <+> y = x <> space <> y

(</>) :: d -> d -> d Source #

x </> y = x <> newline <> y

int :: Int -> d Source #

integer :: Integer -> d Source #

char :: Char -> d Source #

string :: String -> d Source #

text :: Text -> d Source #

ltext :: Text -> d Source #

catH :: Foldable f => f d -> d Source #

catV :: Foldable f => f d -> d Source #

unwords :: Foldable f => f d -> d Source #

unlines :: Foldable f => f d -> d Source #

foldrWith :: Foldable f => (d -> d -> d) -> f d -> d Source #

foldWith :: Foldable f => (d -> d) -> f d -> d Source #

intercalate :: Foldable f => d -> f d -> d Source #

between :: d -> d -> d -> d Source #

replicate :: Int -> d -> d Source #

Instances
Textable Term Source # 
Instance details

Defined in Language.Symantic.Document.Term

Textable Dimension Source # 
Instance details

Defined in Language.Symantic.Document.Term.Dimension

Textable TermIO Source # 
Instance details

Defined in Language.Symantic.Document.Term.IO

Class Indentable

class Textable d => Indentable d where Source #

Methods

align :: d -> d Source #

(align d) make d uses current Column as Indent level.

align :: Indentable (ReprOf d) => Trans d => d -> d Source #

(align d) make d uses current Column as Indent level.

incrIndent :: Indent -> d -> d Source #

(incrIndent ind d) make d uses current Indent plus ind as Indent level.

incrIndent :: Indentable (ReprOf d) => Trans d => Indent -> d -> d Source #

(incrIndent ind d) make d uses current Indent plus ind as Indent level.

withIndent :: Indent -> d -> d Source #

(withIndent ind d) make d uses ind as Indent level.

withIndent :: Indentable (ReprOf d) => Trans d => Indent -> d -> d Source #

(withIndent ind d) make d uses ind as Indent level.

withNewline :: d -> d -> d Source #

(withNewline nl d) make d uses nl as newline.

Useful values for nl are: empty, newlineWithIndent, newlineWithoutIndent.

newlineWithoutIndent :: d Source #

newlineWithIndent :: d Source #

withNewline :: Indentable (ReprOf d) => Trans d => d -> d -> d Source #

(withNewline nl d) make d uses nl as newline.

Useful values for nl are: empty, newlineWithIndent, newlineWithoutIndent.

newlineWithoutIndent :: Indentable (ReprOf d) => Trans d => d Source #

newlineWithIndent :: Indentable (ReprOf d) => Trans d => d Source #

column :: (Column -> d) -> d Source #

(column f) write f applied to the current Column.

column :: Indentable (ReprOf d) => Trans d => (Column -> d) -> d Source #

(column f) write f applied to the current Column.

indent :: (Indent -> d) -> d Source #

(indent f) write f applied to the current Indent.

indent :: Indentable (ReprOf d) => Trans d => (Indent -> d) -> d Source #

(indent f) write f applied to the current Indent.

hang :: Indent -> d -> d Source #

(hang ind d) make d uses current Column plus ind as Indent level.

endToEndWidth :: d -> (Column -> d) -> d Source #

(endToEndWidth d f) write d then f applied to the absolute value of the difference between the end Column and start Column of d.

Note that f is given the end-to-end width, which is not necessarily the maximal width.

spaces :: Indent -> d Source #

fill :: Indent -> d -> d Source #

(fill ind d) write d, then if d is not wider than ind, write the difference with spaces.

breakableFill :: Indent -> d -> d Source #

(breakableFill ind d) write d, then if d is not wider than ind, write the difference with spaces otherwise write a newline indented to to the start Column of d plus ind.

Instances
Indentable Term Source # 
Instance details

Defined in Language.Symantic.Document.Term

Indentable Dimension Source # 
Instance details

Defined in Language.Symantic.Document.Term.Dimension

Indentable TermIO Source # 
Instance details

Defined in Language.Symantic.Document.Term.IO

Class Breakable

class (Textable d, Indentable d) => Breakable d where Source #

Methods

breakable :: (Maybe Column -> d) -> d Source #

(breakable f) write f applied to whether breaks are activated or not.

breakable :: Breakable (ReprOf d) => Trans d => (Maybe Column -> d) -> d Source #

(breakable f) write f applied to whether breaks are activated or not.

withBreakable :: Maybe Column -> d -> d Source #

(withBreakable b d) whether to active breaks or not within d.

withBreakable :: Breakable (ReprOf d) => Trans d => Maybe Column -> d -> d Source #

(withBreakable b d) whether to active breaks or not within d.

ifBreak :: d -> d -> d Source #

(ifBreak onWrap onNoWrap) write onWrap if onNoWrap leads to a Column greater or equal to the one sets with withBreakable, otherwise write onNoWrap.

ifBreak :: Breakable (ReprOf d) => Trans d => d -> d -> d Source #

(ifBreak onWrap onNoWrap) write onWrap if onNoWrap leads to a Column greater or equal to the one sets with withBreakable, otherwise write onNoWrap.

breakpoint :: d -> d -> d -> d Source #

(breakpoint onNoBreak onBreak d) write onNoBreak then d if they fit, onBreak otherwise.

breakpoint :: Breakable (ReprOf d) => Trans d => d -> d -> d -> d Source #

(breakpoint onNoBreak onBreak d) write onNoBreak then d if they fit, onBreak otherwise.

breakableEmpty :: d -> d Source #

(breakableEmpty d) write d if it fits, newline then d otherwise.

(><) :: d -> d -> d Source #

x >< y = x <> breakableEmpty y

breakableSpace :: d -> d Source #

(breakableSpace d) write space then d it they fit, newline then d otherwise.

(>+<) :: d -> d -> d Source #

breakableSpaces :: Foldable f => f d -> d Source #

breakableSpaces ds intercalate a breakableSpace between items of ds.

intercalateHorV :: Foldable f => d -> f d -> d Source #

(intercalateHorV sep ds) write ds with sep intercalated if the whole fits, otherwise write align of ds with newline and sep intercalated.

Instances
Breakable Term Source # 
Instance details

Defined in Language.Symantic.Document.Term

Breakable Dimension Source # 
Instance details

Defined in Language.Symantic.Document.Term.Dimension

Breakable TermIO Source # 
Instance details

Defined in Language.Symantic.Document.Term.IO

Class Colorable

class Colorable d where Source #

Methods

colorable :: (Bool -> d) -> d Source #

(colorable f) write f applied to whether colors are activated or not.

colorable :: Colorable (ReprOf d) => Trans d => (Bool -> d) -> d Source #

(colorable f) write f applied to whether colors are activated or not.

withColorable :: Bool -> d -> d Source #

(withColor b d) whether to active colors or not within d.

withColorable :: Colorable (ReprOf d) => Trans d => Bool -> d -> d Source #

(withColor b d) whether to active colors or not within d.

reverse :: d -> d Source #

black :: d -> d Source #

red :: d -> d Source #

green :: d -> d Source #

yellow :: d -> d Source #

blue :: d -> d Source #

magenta :: d -> d Source #

cyan :: d -> d Source #

white :: d -> d Source #

blacker :: d -> d Source #

redder :: d -> d Source #

greener :: d -> d Source #

yellower :: d -> d Source #

bluer :: d -> d Source #

magentaer :: d -> d Source #

cyaner :: d -> d Source #

whiter :: d -> d Source #

onBlack :: d -> d Source #

onRed :: d -> d Source #

onGreen :: d -> d Source #

onYellow :: d -> d Source #

onBlue :: d -> d Source #

onMagenta :: d -> d Source #

onCyan :: d -> d Source #

onWhite :: d -> d Source #

onBlacker :: d -> d Source #

onRedder :: d -> d Source #

onGreener :: d -> d Source #

onYellower :: d -> d Source #

onBluer :: d -> d Source #

onMagentaer :: d -> d Source #

onCyaner :: d -> d Source #

onWhiter :: d -> d Source #

reverse :: Colorable (ReprOf d) => Trans d => d -> d Source #

black :: Colorable (ReprOf d) => Trans d => d -> d Source #

red :: Colorable (ReprOf d) => Trans d => d -> d Source #

green :: Colorable (ReprOf d) => Trans d => d -> d Source #

yellow :: Colorable (ReprOf d) => Trans d => d -> d Source #

blue :: Colorable (ReprOf d) => Trans d => d -> d Source #

magenta :: Colorable (ReprOf d) => Trans d => d -> d Source #

cyan :: Colorable (ReprOf d) => Trans d => d -> d Source #

white :: Colorable (ReprOf d) => Trans d => d -> d Source #

blacker :: Colorable (ReprOf d) => Trans d => d -> d Source #

redder :: Colorable (ReprOf d) => Trans d => d -> d Source #

greener :: Colorable (ReprOf d) => Trans d => d -> d Source #

yellower :: Colorable (ReprOf d) => Trans d => d -> d Source #

bluer :: Colorable (ReprOf d) => Trans d => d -> d Source #

magentaer :: Colorable (ReprOf d) => Trans d => d -> d Source #

cyaner :: Colorable (ReprOf d) => Trans d => d -> d Source #

whiter :: Colorable (ReprOf d) => Trans d => d -> d Source #

onBlack :: Colorable (ReprOf d) => Trans d => d -> d Source #

onRed :: Colorable (ReprOf d) => Trans d => d -> d Source #

onGreen :: Colorable (ReprOf d) => Trans d => d -> d Source #

onYellow :: Colorable (ReprOf d) => Trans d => d -> d Source #

onBlue :: Colorable (ReprOf d) => Trans d => d -> d Source #

onMagenta :: Colorable (ReprOf d) => Trans d => d -> d Source #

onCyan :: Colorable (ReprOf d) => Trans d => d -> d Source #

onWhite :: Colorable (ReprOf d) => Trans d => d -> d Source #

onBlacker :: Colorable (ReprOf d) => Trans d => d -> d Source #

onRedder :: Colorable (ReprOf d) => Trans d => d -> d Source #

onGreener :: Colorable (ReprOf d) => Trans d => d -> d Source #

onYellower :: Colorable (ReprOf d) => Trans d => d -> d Source #

onBluer :: Colorable (ReprOf d) => Trans d => d -> d Source #

onMagentaer :: Colorable (ReprOf d) => Trans d => d -> d Source #

onCyaner :: Colorable (ReprOf d) => Trans d => d -> d Source #

onWhiter :: Colorable (ReprOf d) => Trans d => d -> d Source #

Instances
Colorable Term Source # 
Instance details

Defined in Language.Symantic.Document.Term

Colorable Dimension Source # 
Instance details

Defined in Language.Symantic.Document.Term.Dimension

Colorable TermIO Source # 
Instance details

Defined in Language.Symantic.Document.Term.IO

Class Decorable

class Decorable d where Source #

Methods

decorable :: (Bool -> d) -> d Source #

(decorable f) write f applied to whether decorations are activated or not.

decorable :: Decorable (ReprOf d) => Trans d => (Bool -> d) -> d Source #

(decorable f) write f applied to whether decorations are activated or not.

withDecorable :: Bool -> d -> d Source #

(withColor b d) whether to active decorations or not within d.

withDecorable :: Decorable (ReprOf d) => Trans d => Bool -> d -> d Source #

(withColor b d) whether to active decorations or not within d.

bold :: d -> d Source #

underline :: d -> d Source #

italic :: d -> d Source #

bold :: Decorable (ReprOf d) => Trans d => d -> d Source #

underline :: Decorable (ReprOf d) => Trans d => d -> d Source #

italic :: Decorable (ReprOf d) => Trans d => d -> d Source #

Class Trans

class Trans tr where Source #

Minimal complete definition

trans, unTrans

Associated Types

type ReprOf tr :: * Source #

Return the underlying tr of the transformer.

Methods

trans :: ReprOf tr -> tr Source #

Lift a tr to the transformer's.

unTrans :: tr -> ReprOf tr Source #

Unlift a tr from the transformer's.

trans1 :: (ReprOf tr -> ReprOf tr) -> tr -> tr Source #

Identity transformation for a unary symantic method.

trans2 :: (ReprOf tr -> ReprOf tr -> ReprOf tr) -> tr -> tr -> tr Source #

Identity transformation for a binary symantic method.

trans3 :: (ReprOf tr -> ReprOf tr -> ReprOf tr -> ReprOf tr) -> tr -> tr -> tr -> tr Source #

Identity transformation for a ternary symantic method.