| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Text.LaTeX.Base.Syntax
Description
- data Measure
- data MathType- = Parentheses
- | Square
- | Dollar
 
- data LaTeX
- data TeXArg
- (<>) :: Monoid 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.
Constructors
| 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  | 
Different types of syntax for mathematical expressions.
Constructors
| Parentheses | |
| Square | |
| Dollar | 
Type of LaTeX blocks.
Constructors
| 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
| Eq LaTeX Source # | |
| Show LaTeX Source # | |
| IsString LaTeX Source # | Method  | 
| Monoid LaTeX Source # | Method  | 
| Arbitrary LaTeX Source # | |
| LaTeXC LaTeX Source # | This instance just sets  | 
| Render LaTeX Source # | |
| Texy LaTeX Source # | |
An argument for a LaTeX command or environment.
Constructors
| 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  | 
Escaping reserved characters
Syntax analysis
Arguments
| :: 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 . (==)
Arguments
| :: (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)