Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Measure
- data MathType
- data LaTeX
- data TeXArg
- (<>) :: Semigroup a => a -> a -> a
- between :: Monoid m => m -> m -> m -> m
- protectString :: String -> String
- protectText :: Text -> Text
- matchCommand :: (String -> Bool) -> LaTeX -> [(String, [TeXArg])]
- lookForCommand :: String -> LaTeX -> [[TeXArg]]
- matchEnv :: (String -> Bool) -> LaTeX -> [(String, [TeXArg], LaTeX)]
- lookForEnv :: String -> LaTeX -> [([TeXArg], LaTeX)]
- texmap :: (LaTeX -> Bool) -> (LaTeX -> LaTeX) -> LaTeX -> LaTeX
- texmapM :: (Applicative m, Monad m) => (LaTeX -> Bool) -> (LaTeX -> m LaTeX) -> LaTeX -> m LaTeX
- getBody :: LaTeX -> Maybe LaTeX
- getPreamble :: LaTeX -> LaTeX
LaTeX
datatype
Measure units defined in LaTeX. Use CustomMeasure
to use commands like textwidth
.
For instance:
rule Nothing (CustomMeasure linewidth) (Pt 2)
This will create a black box (see rule
) as wide as the text and two points tall.
Pt Double | A point is 1/72.27 inch, that means about 0.0138 inch or 0.3515 mm. |
Mm Double | Millimeter. |
Cm Double | Centimeter. |
In Double | Inch. |
Ex Double | The height of an "x" in the current font. |
Em Double | The width of an "M" in the current font. |
CustomMeasure LaTeX | You can introduce a |
Instances
Different types of syntax for mathematical expressions.
Instances
Eq MathType Source # | |
Data MathType Source # | |
Defined in Text.LaTeX.Base.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MathType -> c MathType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MathType # toConstr :: MathType -> Constr # dataTypeOf :: MathType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MathType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathType) # gmapT :: (forall b. Data b => b -> b) -> MathType -> MathType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MathType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MathType -> r # gmapQ :: (forall d. Data d => d -> u) -> MathType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MathType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MathType -> m MathType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MathType -> m MathType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MathType -> m MathType # | |
Show MathType Source # | |
Generic MathType Source # | |
Hashable MathType Source # | |
Defined in Text.LaTeX.Base.Syntax | |
type Rep MathType Source # | |
Defined in Text.LaTeX.Base.Syntax type Rep MathType = D1 ('MetaData "MathType" "Text.LaTeX.Base.Syntax" "HaTeX-3.22.3.1-GY2BvFFGzkDclUPljE2is" 'False) ((C1 ('MetaCons "Parentheses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Square" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Dollar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoubleDollar" 'PrefixI 'False) (U1 :: Type -> Type))) |
Type of LaTeX
blocks.
TeXRaw Text | Raw text. |
TeXComm String [TeXArg] | Constructor for commands. First argument is the name of the command. Second, its arguments. |
TeXCommS String | Constructor for commands with no arguments.
When rendering, no space or |
TeXEnv String [TeXArg] LaTeX | Constructor for environments. First argument is the name of the environment. Second, its arguments. Third, its content. |
TeXMath MathType LaTeX | Mathematical expressions. |
TeXLineBreak (Maybe Measure) Bool | Line break command. |
TeXBraces LaTeX | A expression between braces. |
TeXComment Text | Comments. |
TeXSeq LaTeX LaTeX | |
TeXEmpty | An empty block.
Neutral element of |
Instances
An argument for a LaTeX
command or environment.
FixArg LaTeX | Fixed argument. |
OptArg LaTeX | Optional argument. |
MOptArg [LaTeX] | Multiple optional argument. |
SymArg LaTeX | An argument enclosed between |
MSymArg [LaTeX] | Version of |
ParArg LaTeX | An argument enclosed between |
MParArg [LaTeX] | Version of |
Instances
(<>) :: Semigroup a => a -> a -> a infixr 6 #
An associative operation.
>>>
[1,2,3] <> [4,5,6]
[1,2,3,4,5,6]
between :: Monoid m => m -> m -> m -> m Source #
Calling between
c l1 l2
puts c
between l1
and l2
and
appends them.
between c l1 l2 = l1 <> c <> l2
Escaping reserved characters
Syntax analysis
:: String | Name of the command. |
-> LaTeX | LaTeX syntax tree. |
-> [[TeXArg]] | List of arguments passed to the command. |
Look into a LaTeX
syntax tree to find any call to the command with
the given name. It returns a list of arguments with which this command
is called.
lookForCommand = (fmap snd .) . matchCommand . (==)
If the returned list is empty, the command was not found. However, if the list contains empty lists, those are callings to the command with no arguments.
For example
lookForCommand "author" l
would look for the argument passed to the \author
command in l
.
lookForEnv :: String -> LaTeX -> [([TeXArg], LaTeX)] Source #
Similar to lookForCommand
, but applied to environments.
It returns a list with arguments passed and content of the
environment in each call.
lookForEnv = (fmap (\(_,as,l) -> (as,l)) .) . matchEnv . (==)
:: (LaTeX -> Bool) | Condition. |
-> (LaTeX -> LaTeX) | Function to apply when the condition matches. |
-> LaTeX | |
-> LaTeX |
The function texmap
looks for subexpressions that match a given
condition and applies a function to them.
texmap c f = runIdentity . texmapM c (pure . f)