| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Symantic.Document.Sym
Contents
Synopsis
- newtype Nat = Nat {}
- unLength :: Nat -> Integer
- class Lengthable a where
- class Monoid a => Splitable a where
- type Column = Nat
- type Indent = Column
- class (IsString d, Semigroup d) => Textable d where
- class Textable d => Indentable d where
- class (Textable d, Indentable d) => Breakable d where
- class Colorable d where
- class Decorable d where
- class Trans tr where
Type Nat
Class Lengthable
class Lengthable a where Source #
Minimal complete definition
Instances
| Lengthable Char Source # | |
| Lengthable Text Source # | |
| Lengthable Text Source # | |
| Lengthable [a] Source # | |
Defined in Language.Symantic.Document.Sym | |
Class Splitable
class Monoid a => Splitable a where Source #
Methods
break :: (Char -> Bool) -> a -> (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
Arguments
| :: Char | XXX: MUST NOT be '\n' |
| -> d |
Arguments
| :: String | XXX: MUST NOT contain '\n' |
| -> d |
Arguments
| :: Text | XXX: MUST NOT contain '\n' |
| -> d |
Arguments
| :: Text | XXX: MUST NOT contain '\n' |
| -> d |
empty :: Textable (ReprOf d) => Trans d => d Source #
integer :: Integer -> d Source #
string :: String -> 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 #
Instances
Class Indentable
class Textable d => Indentable d where Source #
Methods
align :: Indentable (ReprOf d) => Trans d => d -> d Source #
incrIndent :: Indent -> d -> d Source #
( make incrIndent ind d)d uses current Indent plus ind as Indent level.
incrIndent :: Indentable (ReprOf d) => Trans d => Indent -> d -> d Source #
( make incrIndent ind d)d uses current Indent plus ind as Indent level.
withIndent :: Indent -> d -> d Source #
( make withIndent ind d)d uses ind as Indent level.
withIndent :: Indentable (ReprOf d) => Trans d => Indent -> d -> d Source #
( make withIndent ind d)d uses ind as Indent level.
withNewline :: d -> d -> d Source #
( make withNewline nl d)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 #
( make withNewline nl d)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 :: Indentable (ReprOf d) => Trans d => (Column -> d) -> d Source #
indent :: (Indent -> d) -> d Source #
indent :: Indentable (ReprOf d) => Trans d => (Indent -> d) -> d Source #
hang :: Indent -> d -> d Source #
endToEndWidth :: d -> (Column -> d) -> d Source #
( write endToEndWidth d f)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 #
breakableFill :: Indent -> d -> d Source #
( write breakableFill ind d)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
Class Breakable
class (Textable d, Indentable d) => Breakable d where Source #
Methods
breakable :: (Maybe Column -> d) -> d Source #
( write breakable f)f applied to whether breaks are activated or not.
breakable :: Breakable (ReprOf d) => Trans d => (Maybe Column -> d) -> d Source #
( write breakable f)f applied to whether breaks are activated or not.
withBreakable :: Maybe Column -> d -> d Source #
( whether to active breaks or not within withBreakable b d)d.
withBreakable :: Breakable (ReprOf d) => Trans d => Maybe Column -> d -> d Source #
( whether to active breaks or not within withBreakable b d)d.
ifBreak :: d -> d -> d Source #
(
write ifBreak onWrap onNoWrap)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 #
(
write ifBreak onWrap onNoWrap)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 #
(
write breakpoint onNoBreak onBreak d)onNoBreak then d if they fit,
onBreak otherwise.
breakpoint :: Breakable (ReprOf d) => Trans d => d -> d -> d -> d Source #
(
write breakpoint onNoBreak onBreak d)onNoBreak then d if they fit,
onBreak otherwise.
breakableEmpty :: d -> d Source #
( write breakableEmpty d)d if it fits, newline then d otherwise.
x><y = x<>breakableEmptyy
breakableSpace :: d -> d Source #
( write breakableSpace d)space then d it they fit,
newline then d otherwise.
x>+<y = x<>breakableSpacey
breakableSpaces :: Foldable f => f d -> d Source #
intercalate a breakableSpaces dsbreakableSpace
between items of ds.
intercalateHorV :: Foldable f => d -> f d -> d Source #
(
write intercalateHorV sep ds)ds with sep intercalated if the whole fits,
otherwise write align of ds with newline and sep intercalated.
Instances
Class Colorable
class Colorable d where Source #
Methods
colorable :: (Bool -> d) -> d Source #
( write colorable f)f applied to whether colors are activated or not.
colorable :: Colorable (ReprOf d) => Trans d => (Bool -> d) -> d Source #
( write colorable f)f applied to whether colors are activated or not.
withColorable :: Bool -> d -> d Source #
( whether to active colors or not within withColor b d)d.
withColorable :: Colorable (ReprOf d) => Trans d => Bool -> d -> d Source #
( whether to active colors or not within withColor b d)d.
onYellower :: d -> d Source #
onMagentaer :: 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
Class Decorable
class Decorable d where Source #
Methods
decorable :: (Bool -> d) -> d Source #
( write decorable f)f applied to whether decorations are activated or not.
decorable :: Decorable (ReprOf d) => Trans d => (Bool -> d) -> d Source #
( write decorable f)f applied to whether decorations are activated or not.
withDecorable :: Bool -> d -> d Source #
( whether to active decorations or not within withColor b d)d.
withDecorable :: Decorable (ReprOf d) => Trans d => Bool -> d -> d Source #
( whether to active decorations or not within withColor b d)d.
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
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.