typst-0.5.0.3: Parsing and evaluating typst syntax.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Typst.Types

Synopsis

Documentation

data RE Source #

A regular expression. Note that typst-hs does not use the same Regex engine as Typst. See issue #28.

Instances

Instances details
Show RE Source # 
Instance details

Defined in Typst.Regex

Methods

showsPrec :: Int -> RE -> ShowS #

show :: RE -> String #

showList :: [RE] -> ShowS #

Eq RE Source # 
Instance details

Defined in Typst.Regex

Methods

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

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

Ord RE Source # 
Instance details

Defined in Typst.Regex

Methods

compare :: RE -> RE -> Ordering #

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

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

(>) :: RE -> RE -> Bool #

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

max :: RE -> RE -> RE #

min :: RE -> RE -> RE #

FromVal RE Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m RE Source #

data Val Source #

A Typst value. More documentation can be found in the Foundations chapter of the Typst reference manual. A more concise (but somewhat outdated) summary can also be found in L. Mädje "Typst: a programmable markup language for typesetting", page 32-33.

Constructors

VNone

The none value, indicates the absence of any other value.

VAuto

The auto value, used to automatically set an appropriate value.

VBoolean !Bool

A bool value.

VInteger !Integer

An int value.

VFloat !Double

A float value.

VRatio !Rational

A ratio value, a proportion of a certain whole, for example 50%.

VLength !Length

A length or a relative value.

VAlignment (Maybe Horiz) (Maybe Vert)

An alignment value, indicating the alignment of some content along both the horizontal and vertical axes.

VAngle !Double

An angle value (expressed internally in degrees).

VFraction !Double

A fraction value, defining the proportions of remaing space is to be distributed, e.g. 2 fr.

VColor !Color

A color value. Not all Typst color spaces are supported; only rgb, cmyk, and luma are available. See issue #35.

VSymbol !Symbol

A symbol value, representing a Unicode symbol.

VString !Text

A UTF-8 encoded text string.

VRegex !RE

A regex (regular expression). See RE for details.

VDateTime (Maybe Day) (Maybe DiffTime)

A datetime value, a date, a time, or a combination of both.

VContent (Seq Content)

A content value, see Content for more details.

VArray (Vector Val)

An array value, for example (10, 20, 30).

VDict (OMap Identifier Val)

A dictionary value, for example (a:20, b:30).

VTermItem (Seq Content) (Seq Content) 
VDirection Direction

A direction to lay out content.

VFunction (Maybe Identifier) (Map Identifier Val) Function

A Typst function.

VArguments Arguments

Positional and named function arguments

VLabel !Text

A label to some element, for example hello.

VCounter !Counter 
VSelector !Selector 
VModule Identifier (Map Identifier Val) 
VStyles 
VVersion [Integer] 
VType !ValType 

Instances

Instances details
FromJSON Val Source # 
Instance details

Defined in Typst.Types

Show Val Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Val -> ShowS #

show :: Val -> String #

showList :: [Val] -> ShowS #

Eq Val Source # 
Instance details

Defined in Typst.Types

Methods

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

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

Ord Val Source # 
Instance details

Defined in Typst.Types

Methods

compare :: Val -> Val -> Ordering #

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

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

(>) :: Val -> Val -> Bool #

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

max :: Val -> Val -> Val #

min :: Val -> Val -> Val #

FromValue Val Source # 
Instance details

Defined in Typst.Types

Compare Val Source # 
Instance details

Defined in Typst.Types

Methods

comp :: Val -> Val -> Maybe Ordering Source #

FromVal Val Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Val Source #

Multipliable Val Source # 
Instance details

Defined in Typst.Types

Negatable Val Source # 
Instance details

Defined in Typst.Types

Summable Val Source # 
Instance details

Defined in Typst.Types

data ValType Source #

A Typst type, see documentation for Val.

Instances

Instances details
Show ValType Source # 
Instance details

Defined in Typst.Types

Eq ValType Source # 
Instance details

Defined in Typst.Types

Methods

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

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

Ord ValType Source # 
Instance details

Defined in Typst.Types

class FromVal a where Source #

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m a Source #

Instances

Instances details
FromVal Rational Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Rational Source #

FromVal Text Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Text Source #

FromVal RE Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m RE Source #

FromVal Counter Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Counter Source #

FromVal Direction Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Direction Source #

FromVal Function Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Function Source #

FromVal Length Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Length Source #

FromVal Selector Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Selector Source #

FromVal Val Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Val Source #

FromVal String Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m String Source #

FromVal Integer Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Integer Source #

FromVal Bool Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Bool Source #

FromVal Double Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Double Source #

FromVal Int Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Int Source #

FromVal (Seq Content) Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m (Seq Content) Source #

FromVal a => FromVal (Vector a) Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m (Vector a) Source #

FromVal a => FromVal (Maybe a) Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m (Maybe a) Source #

class Negatable a where Source #

Methods

maybeNegate :: a -> Maybe a Source #

Instances

Instances details
Negatable Val Source # 
Instance details

Defined in Typst.Types

class Negatable a => Summable a where Source #

Minimal complete definition

maybePlus

Methods

maybePlus :: a -> a -> Maybe a Source #

maybeMinus :: a -> a -> Maybe a Source #

Instances

Instances details
Summable Val Source # 
Instance details

Defined in Typst.Types

class Multipliable a where Source #

Methods

maybeTimes :: a -> a -> Maybe a Source #

maybeDividedBy :: a -> a -> Maybe a Source #

Instances

Instances details
Multipliable Val Source # 
Instance details

Defined in Typst.Types

data Symbol Source #

Constructors

Symbol 

Fields

Instances

Instances details
Show Symbol Source # 
Instance details

Defined in Typst.Types

Eq Symbol Source # 
Instance details

Defined in Typst.Types

Methods

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

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

data Content Source #

Instances

Instances details
IsString Content Source # 
Instance details

Defined in Typst.Types

Methods

fromString :: String -> Content #

Show Content Source # 
Instance details

Defined in Typst.Types

Eq Content Source # 
Instance details

Defined in Typst.Types

Methods

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

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

Ord Content Source # 
Instance details

Defined in Typst.Types

FromVal (Seq Content) Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m (Seq Content) Source #

newtype Function Source #

Constructors

Function (forall m. Monad m => Arguments -> MP m Val) 

Instances

Instances details
Show Function Source # 
Instance details

Defined in Typst.Types

Eq Function Source # 
Instance details

Defined in Typst.Types

FromVal Function Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Function Source #

data Arguments Source #

Constructors

Arguments 

Instances

Instances details
Monoid Arguments Source # 
Instance details

Defined in Typst.Types

Semigroup Arguments Source # 
Instance details

Defined in Typst.Types

Show Arguments Source # 
Instance details

Defined in Typst.Types

Eq Arguments Source # 
Instance details

Defined in Typst.Types

class Compare a where Source #

Methods

comp :: a -> a -> Maybe Ordering Source #

Instances

Instances details
Compare Val Source # 
Instance details

Defined in Typst.Types

Methods

comp :: Val -> Val -> Maybe Ordering Source #

type MP m = ParsecT [Markup] (EvalState m) m Source #

data Scope Source #

Constructors

FunctionScope 
BlockScope 

Instances

Instances details
Show Scope Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

Eq Scope Source # 
Instance details

Defined in Typst.Types

Methods

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

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

Ord Scope Source # 
Instance details

Defined in Typst.Types

Methods

compare :: Scope -> Scope -> Ordering #

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

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

(>) :: Scope -> Scope -> Bool #

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

max :: Scope -> Scope -> Scope #

min :: Scope -> Scope -> Scope #

data XdgDirectory #

Special directories for storing user-specific application data, configuration, and cache files, as specified by the XDG Base Directory Specification.

Note: On Windows, XdgData and XdgConfig usually map to the same directory.

Since: directory-1.2.3.0

Constructors

XdgData

For data files (e.g. images). It uses the XDG_DATA_HOME environment variable. On non-Windows systems, the default is ~/.local/share. On Windows, the default is %APPDATA% (e.g. C:/Users/<user>/AppData/Roaming). Can be considered as the user-specific equivalent of /usr/share.

XdgConfig

For configuration files. It uses the XDG_CONFIG_HOME environment variable. On non-Windows systems, the default is ~/.config. On Windows, the default is %APPDATA% (e.g. C:/Users/<user>/AppData/Roaming). Can be considered as the user-specific equivalent of /etc.

XdgCache

For non-essential files (e.g. cache). It uses the XDG_CACHE_HOME environment variable. On non-Windows systems, the default is ~/.cache. On Windows, the default is %LOCALAPPDATA% (e.g. C:/Users/<user>/AppData/Local). Can be considered as the user-specific equivalent of /var/cache.

XdgState

For data that should persist between (application) restarts, but that is not important or portable enough to the user that it should be stored in XdgData. It uses the XDG_STATE_HOME environment variable. On non-Windows sytems, the default is ~/.local/state. On Windows, the default is %LOCALAPPDATA% (e.g. C:/Users/<user>/AppData/Local).

Since: directory-1.3.7.0

Instances

Instances details
Bounded XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Enum XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Read XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Show XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Eq XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Ord XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

data ShowRule Source #

Constructors

ShowRule Selector (forall m. Monad m => Content -> MP m (Seq Content)) 

Instances

Instances details
Show ShowRule Source # 
Instance details

Defined in Typst.Types

data Counter Source #

Instances

Instances details
Show Counter Source # 
Instance details

Defined in Typst.Types

Eq Counter Source # 
Instance details

Defined in Typst.Types

Methods

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

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

Ord Counter Source # 
Instance details

Defined in Typst.Types

FromVal Counter Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Counter Source #

data LUnit Source #

Constructors

LEm 
LPt 
LIn 
LCm 
LMm 

Instances

Instances details
Show LUnit Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> LUnit -> ShowS #

show :: LUnit -> String #

showList :: [LUnit] -> ShowS #

Eq LUnit Source # 
Instance details

Defined in Typst.Types

Methods

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

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

data Length Source #

Instances

Instances details
Monoid Length Source # 
Instance details

Defined in Typst.Types

Semigroup Length Source # 
Instance details

Defined in Typst.Types

Show Length Source # 
Instance details

Defined in Typst.Types

Eq Length Source # 
Instance details

Defined in Typst.Types

Methods

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

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

FromVal Length Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Length Source #

data Horiz Source #

Instances

Instances details
Show Horiz Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Horiz -> ShowS #

show :: Horiz -> String #

showList :: [Horiz] -> ShowS #

Eq Horiz Source # 
Instance details

Defined in Typst.Types

Methods

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

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

Ord Horiz Source # 
Instance details

Defined in Typst.Types

Methods

compare :: Horiz -> Horiz -> Ordering #

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

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

(>) :: Horiz -> Horiz -> Bool #

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

max :: Horiz -> Horiz -> Horiz #

min :: Horiz -> Horiz -> Horiz #

data Vert Source #

Instances

Instances details
Show Vert Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Vert -> ShowS #

show :: Vert -> String #

showList :: [Vert] -> ShowS #

Eq Vert Source # 
Instance details

Defined in Typst.Types

Methods

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

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

Ord Vert Source # 
Instance details

Defined in Typst.Types

Methods

compare :: Vert -> Vert -> Ordering #

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

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

(>) :: Vert -> Vert -> Bool #

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

max :: Vert -> Vert -> Vert #

min :: Vert -> Vert -> Vert #

data Color Source #

Instances

Instances details
Show Color Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Eq Color Source # 
Instance details

Defined in Typst.Types

Methods

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

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

Ord Color Source # 
Instance details

Defined in Typst.Types

Methods

compare :: Color -> Color -> Ordering #

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

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

(>) :: Color -> Color -> Bool #

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

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

data Direction Source #

Constructors

Ltr

Left to right

Rtl

Right to left

Ttb

Top to bottom

Btt

Bottom to top

Instances

Instances details
Show Direction Source # 
Instance details

Defined in Typst.Types

Eq Direction Source # 
Instance details

Defined in Typst.Types

Ord Direction Source # 
Instance details

Defined in Typst.Types

FromVal Direction Source # 
Instance details

Defined in Typst.Types

Methods

fromVal :: (MonadPlus m, MonadFail m) => Val -> m Direction Source #

newtype Identifier Source #

Constructors

Identifier Text 

Instances

Instances details
Data Identifier Source # 
Instance details

Defined in Typst.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identifier -> c Identifier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Identifier #

toConstr :: Identifier -> Constr #

dataTypeOf :: Identifier -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Identifier) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Identifier) #

gmapT :: (forall b. Data b => b -> b) -> Identifier -> Identifier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identifier -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identifier -> r #

gmapQ :: (forall d. Data d => d -> u) -> Identifier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Identifier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier #

IsString Identifier Source # 
Instance details

Defined in Typst.Syntax

Monoid Identifier Source # 
Instance details

Defined in Typst.Syntax

Semigroup Identifier Source # 
Instance details

Defined in Typst.Syntax

Show Identifier Source # 
Instance details

Defined in Typst.Syntax

Eq Identifier Source # 
Instance details

Defined in Typst.Syntax

Ord Identifier Source # 
Instance details

Defined in Typst.Syntax

joinVals :: MonadFail m => Val -> Val -> m Val Source #

data Attempt a Source #

Constructors

Success a 
Failure String 

Instances

Instances details
MonadFail Attempt Source # 
Instance details

Defined in Typst.Types

Methods

fail :: String -> Attempt a #

Applicative Attempt Source # 
Instance details

Defined in Typst.Types

Methods

pure :: a -> Attempt a #

(<*>) :: Attempt (a -> b) -> Attempt a -> Attempt b #

liftA2 :: (a -> b -> c) -> Attempt a -> Attempt b -> Attempt c #

(*>) :: Attempt a -> Attempt b -> Attempt b #

(<*) :: Attempt a -> Attempt b -> Attempt a #

Functor Attempt Source # 
Instance details

Defined in Typst.Types

Methods

fmap :: (a -> b) -> Attempt a -> Attempt b #

(<$) :: a -> Attempt b -> Attempt a #

Monad Attempt Source # 
Instance details

Defined in Typst.Types

Methods

(>>=) :: Attempt a -> (a -> Attempt b) -> Attempt b #

(>>) :: Attempt a -> Attempt b -> Attempt b #

return :: a -> Attempt a #

Show a => Show (Attempt a) Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Attempt a -> ShowS #

show :: Attempt a -> String #

showList :: [Attempt a] -> ShowS #

Eq a => Eq (Attempt a) Source # 
Instance details

Defined in Typst.Types

Methods

(==) :: Attempt a -> Attempt a -> Bool #

(/=) :: Attempt a -> Attempt a -> Bool #

Ord a => Ord (Attempt a) Source # 
Instance details

Defined in Typst.Types

Methods

compare :: Attempt a -> Attempt a -> Ordering #

(<) :: Attempt a -> Attempt a -> Bool #

(<=) :: Attempt a -> Attempt a -> Bool #

(>) :: Attempt a -> Attempt a -> Bool #

(>=) :: Attempt a -> Attempt a -> Bool #

max :: Attempt a -> Attempt a -> Attempt a #

min :: Attempt a -> Attempt a -> Attempt a #