Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Definition of the LaTeXC
class, used to combine the classic applicative and
the latter monadic interfaces of HaTeX 3. The user can define new instances
as well, adding flexibility to the way HaTeX is used.
Synopsis
- class (Monoid l, IsString l) => LaTeXC l where
- class Semigroup a => Monoid a where
- fromLaTeX :: LaTeXC l => LaTeX -> l
- liftL :: LaTeXC l => (LaTeX -> LaTeX) -> l -> l
- liftL2 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX) -> l -> l -> l
- liftL3 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l
- liftL4 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l
- liftL5 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l
- liftL6 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l
- liftL7 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l -> l
- liftL8 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l -> l -> l
- liftL9 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l
- comm0 :: LaTeXC l => String -> l
- comm1 :: LaTeXC l => String -> l -> l
- comm2 :: LaTeXC l => String -> l -> l -> l
- comm3 :: LaTeXC l => String -> l -> l -> l -> l
- comm4 :: LaTeXC l => String -> l -> l -> l -> l -> l
- comm5 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l
- comm6 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l
- comm7 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l
- comm8 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l
- comm9 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l
- commS :: LaTeXC l => String -> l
- fixComm :: LaTeXC l => String -> [l] -> l
- optFixComm :: LaTeXC l => String -> Int -> [l] -> l
- env0 :: LaTeXC l => String -> l -> l
- env1 :: LaTeXC l => String -> l -> l -> l
- env2 :: LaTeXC l => String -> l -> l -> l -> l
- env3 :: LaTeXC l => String -> l -> l -> l -> l -> l
- env4 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l
- env5 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l
- env6 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l
- env7 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l
- env8 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l
- env9 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l
- fixEnv :: LaTeXC l => String -> [l] -> l -> l
- braces :: LaTeXC l => l -> l
- squareBraces :: LaTeXC l => l -> l
- raw :: LaTeXC l => Text -> l
Documentation
class (Monoid l, IsString l) => LaTeXC l where Source #
Instances
LaTeXC LaTeX Source # | This instance just sets |
(Monad m, a ~ ()) => LaTeXC (LaTeXT m a) Source # | |
(Applicative m, LaTeXC (m a), Semigroup (m a), a ~ ()) => LaTeXC (ReferenceQueryT r m a) Source # | |
Defined in Text.LaTeX.Packages.BibLaTeX liftListL :: ([LaTeX] -> LaTeX) -> [ReferenceQueryT r m a] -> ReferenceQueryT r m a Source # |
class Semigroup a => Monoid a where #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:
- Right identity
x
<>
mempty
= x- Left identity
mempty
<>
x = x- Associativity
x
(<>
(y<>
z) = (x<>
y)<>
zSemigroup
law)- Concatenation
mconcat
=foldr
(<>
)mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
NOTE: Semigroup
is a superclass of Monoid
since base-4.11.0.0.
Identity of mappend
>>>
"Hello world" <> mempty
"Hello world"
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.
Should it be implemented manually, since mappend
= (<>
)mappend
is a synonym for
(<>
), it is expected that the two functions are defined the same
way. In a future GHC release mappend
will be removed from Monoid
.
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
>>>
mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"
Instances
Monoid LaTeX Source # | Method |
Monoid TeXCheck Source # | |
Monoid All | Since: base-2.1 |
Monoid Any | Since: base-2.1 |
Monoid ByteString | |
Defined in Data.ByteString.Internal mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
Monoid ByteString | |
Defined in Data.ByteString.Lazy.Internal mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
Monoid ShortByteString | |
Defined in Data.ByteString.Short.Internal mappend :: ShortByteString -> ShortByteString -> ShortByteString # mconcat :: [ShortByteString] -> ShortByteString # | |
Monoid IntSet | |
Monoid ByteArray | |
Monoid Ordering | Since: base-2.1 |
Monoid Doc | |
Monoid Builder | |
Monoid () | Since: base-2.1 |
Monoid a => Monoid (Identity a) | Since: base-4.9.0.0 |
Ord a => Monoid (Max a) | Since: base-4.8.0.0 |
Ord a => Monoid (Min a) | Since: base-4.8.0.0 |
Monoid (First a) | Since: base-2.1 |
Monoid (Last a) | Since: base-2.1 |
(Ord a, Bounded a) => Monoid (Max a) | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a) | Since: base-4.9.0.0 |
Monoid m => Monoid (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup mempty :: WrappedMonoid m # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # mconcat :: [WrappedMonoid m] -> WrappedMonoid m # | |
Monoid a => Monoid (Dual a) | Since: base-2.1 |
Monoid (Endo a) | Since: base-2.1 |
Num a => Monoid (Product a) | Since: base-2.1 |
Num a => Monoid (Sum a) | Since: base-2.1 |
Monoid p => Monoid (Par1 p) | Since: base-4.12.0.0 |
Monoid (IntMap a) | |
Monoid (Seq a) | |
Monoid (MergeSet a) | |
Ord a => Monoid (Set a) | |
Monoid a => Monoid (IO a) | Since: base-4.9.0.0 |
Monoid a => Monoid (Matrix a) | |
Monoid (Doc a) | |
Monoid (Doc ann) |
|
Monoid (Array a) | |
Monoid a => Monoid (Q a) | Since: template-haskell-2.17.0.0 |
Monoid (Vector a) | |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Monoid a => Monoid (a) | Since: base-4.15 |
Monoid [a] | Since: base-2.1 |
(Monad m, Monoid a) => Monoid (LaTeXT m a) Source # | |
Monoid (Proxy s) | Since: base-4.7.0.0 |
Monoid (U1 p) | Since: base-4.12.0.0 |
Ord k => Monoid (Map k v) | |
Monoid b => Monoid (a -> b) | Since: base-2.1 |
(Monoid a, Monoid b) => Monoid (a, b) | Since: base-2.1 |
(Applicative m, Semigroup (m a), Monoid (m a), a ~ ()) => Monoid (ReferenceQueryT r m a) Source # | |
Defined in Text.LaTeX.Packages.BibLaTeX mempty :: ReferenceQueryT r m a # mappend :: ReferenceQueryT r m a -> ReferenceQueryT r m a -> ReferenceQueryT r m a # mconcat :: [ReferenceQueryT r m a] -> ReferenceQueryT r m a # | |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
(Applicative f, Monoid a) => Monoid (Ap f a) | Since: base-4.12.0.0 |
Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 |
Monoid (f p) => Monoid (Rec1 f p) | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | Since: base-2.1 |
(Monoid (f a), Monoid (g a)) => Monoid (Product f g a) | Since: base-4.16.0.0 |
(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) | Since: base-4.12.0.0 |
Monoid c => Monoid (K1 i c p) | Since: base-4.12.0.0 |
(Monoid a, Semigroup (ParsecT s u m a)) => Monoid (ParsecT s u m a) | The Since: parsec-3.1.12 |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | Since: base-2.1 |
Monoid (f (g a)) => Monoid (Compose f g a) | Since: base-4.16.0.0 |
Monoid (f (g p)) => Monoid ((f :.: g) p) | Since: base-4.12.0.0 |
Monoid (f p) => Monoid (M1 i c f p) | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | Since: base-2.1 |
Combinators
From LaTeX
Lifting
Lifting functions from LaTeX
functions to functions over any instance of LaTeXC
.
In general, the implementation is as follows:
liftLN f x1 ... xN = liftListL (\[x1,...,xN] -> f x1 ... xN) [x1,...,xN]
liftL2 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX) -> l -> l -> l Source #
Variant of liftL
with a two arguments function.
liftL3 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l Source #
Variant of liftL
with a three arguments function.
liftL4 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l Source #
Variant of liftL
with a four arguments function.
liftL5 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l Source #
Variant of liftL
with a five arguments function.
liftL6 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l Source #
Variant of liftL
with a six arguments function.
liftL7 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l -> l Source #
Variant of liftL
with a seven arguments function.
liftL8 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #
Variant of liftL
with an eight arguments function.
liftL9 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #
Variant of liftL
with a nine arguments function.
Others
comm0 :: LaTeXC l => String -> l Source #
A simple (without arguments) and handy command generator using the name of the command.
comm0 str = fromLaTeX $ TeXComm str []
comm1 :: LaTeXC l => String -> l -> l Source #
A one parameter command generator using the name of the command. The parameter will be rendered as a fixed argument.
comm1 str = liftL $ \l -> TeXComm str [FixArg l]
comm2 :: LaTeXC l => String -> l -> l -> l Source #
A two parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.
comm2 str = liftL2 $ \l1 l2 -> TeXComm str [FixArg l1, FixArg l2]
comm3 :: LaTeXC l => String -> l -> l -> l -> l Source #
A three parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.
comm3 str = liftL3 $ \l1 l2 l3 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3]
comm4 :: LaTeXC l => String -> l -> l -> l -> l -> l Source #
A four parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.
comm4 str = liftL4 $ \l1 l2 l3 l4 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4]
comm5 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l Source #
A five parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.
comm5 str = liftL5 $ \l1 l2 l3 l4 l5 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4, FixArg l5]
comm6 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l Source #
A six parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.
comm6 str = liftL6 $ \l1 l2 l3 l4 l5 l6 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4, FixArg l5, FixArg l6]
comm7 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l Source #
A seven parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.
comm7 str = liftL7 $ \l1 l2 l3 l4 l5 l6 l7 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4, FixArg l5, FixArg l6, FixArg l7]
comm8 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #
An eight parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.
comm8 str = liftL8 $ \l1 l2 l3 l4 l5 l6 l7 l8 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4, FixArg l5, FixArg l6, FixArg l7, FixArgs l8]
comm9 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #
A nine parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.
comm9 str = liftL9 $ \l1 l2 l3 l4 l5 l6 l7 l8 l9 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4, FixArg l5, FixArg l6, FixArg l7, FixArgs l8, l9]
fixComm :: LaTeXC l => String -> [l] -> l Source #
Call a LaTeX command where all the arguments in the list are fixed arguments.
optFixComm :: LaTeXC l => String -> Int -> [l] -> l Source #
Call a LaTeX command with the first n
arguments as optional ones,
followed by fixed arguments. Most LaTeX commands are structured with first a
sequence of optional arguments, followed by a sequence of fixed arguments.
env0 :: LaTeXC l => String -> l -> l Source #
Define an environment, without any parameters that are passed to the environment.
env1 :: LaTeXC l => String -> l -> l -> l Source #
Define an environment, with one fixed parameter that is passed to the environment.
env2 :: LaTeXC l => String -> l -> l -> l -> l Source #
Define an environment, with two fixed parameters that is passed to the environment.
env3 :: LaTeXC l => String -> l -> l -> l -> l -> l Source #
Define an environment, with three fixed parameters that is passed to the environment.
env4 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l Source #
Define an environment, with four fixed parameters that is passed to the environment.
env5 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l Source #
Define an environment, with five fixed parameters that is passed to the environment.
env6 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l Source #
Define an environment, with six fixed parameters that is passed to the environment.
env7 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #
Define an environment, with seven fixed parameters that is passed to the environment.
env8 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #
Define an environment, with eight fixed parameters that is passed to the environment.
env9 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #
Define an environment, with nine fixed parameters that is passed to the environment.
fixEnv :: LaTeXC l => String -> [l] -> l -> l Source #
Create a LaTeX environment where all the arguments in the list are fixed arguments.
braces :: LaTeXC l => l -> l Source #
A lifted version of the TeXBraces
constructor.
braces = liftL TeXBraces
squareBraces :: LaTeXC l => l -> l Source #
raw :: LaTeXC l => Text -> l Source #
Insert a raw piece of Text
.
This functions doesn't escape LaTeX
reserved characters,
it insert the text just as it is received.
Warning: This function is unsafe, in the sense that it does not check that the input text is a valid LaTeX block. Make sure any braces, commands or environments are properly closed.