| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Typst.Types
Synopsis
- data RE
- data Val
- = VNone
- | VAuto
- | VBoolean !Bool
- | VInteger !Integer
- | VFloat !Double
- | VRatio !Rational
- | VLength !Length
- | VAlignment (Maybe Horiz) (Maybe Vert)
- | VAngle !Double
- | VFraction !Double
- | VColor !Color
- | VSymbol !Symbol
- | VString !Text
- | VRegex !RE
- | VDateTime (Maybe Day) (Maybe DiffTime)
- | VContent (Seq Content)
- | VArray (Vector Val)
- | VDict (OMap Identifier Val)
- | VTermItem (Seq Content) (Seq Content)
- | VDirection Direction
- | VFunction (Maybe Identifier) (Map Identifier Val) Function
- | VArguments Arguments
- | VLabel !Text
- | VCounter !Counter
- | VSelector !Selector
- | VModule Identifier (Map Identifier Val)
- | VStyles
- | VVersion [Integer]
- | VType !ValType
- data ValType
- = TNone
- | TAuto
- | TBoolean
- | TInteger
- | TFloat
- | TRatio
- | TLength
- | TAlignment
- | TAngle
- | TFraction
- | TColor
- | TSymbol
- | TString
- | TRegex
- | TDateTime
- | TContent
- | TArray
- | TDict
- | TTermItem
- | TDirection
- | TFunction
- | TArguments
- | TModule
- | TSelector
- | TStyles
- | TLabel
- | TCounter
- | TLocation
- | TVersion
- | TType
- | TAny
- | ValType :|: ValType
- valType :: Val -> ValType
- hasType :: ValType -> Val -> Bool
- class FromVal a where
- class Negatable a where
- maybeNegate :: a -> Maybe a
- class Negatable a => Summable a where
- maybePlus :: a -> a -> Maybe a
- maybeMinus :: a -> a -> Maybe a
- class Multipliable a where
- maybeTimes :: a -> a -> Maybe a
- maybeDividedBy :: a -> a -> Maybe a
- data Selector
- data Symbol = Symbol {
- symDefault :: !Text
- symAccent :: !Bool
- symVariants :: [(Set Text, Text)]
- data Content
- newtype Function = Function (forall m. Monad m => Arguments -> MP m Val)
- data Arguments = Arguments {
- positional :: [Val]
- named :: OMap Identifier Val
- getPositionalArg :: (MonadFail m, MonadPlus m, FromVal a) => Int -> Arguments -> m a
- getNamedArg :: (MonadFail m, MonadPlus m, FromVal a) => Identifier -> Arguments -> m a
- class Compare a where
- type MP m = ParsecT [Markup] (EvalState m) m
- data Scope
- data FlowDirective
- data Operations m = Operations {
- loadBytes :: FilePath -> m ByteString
- currentUTCTime :: m UTCTime
- lookupEnvVar :: String -> m (Maybe String)
- checkExistence :: FilePath -> m Bool
- data XdgDirectory
- data EvalState m = EvalState {}
- emptyEvalState :: EvalState m
- data ShowRule = ShowRule Selector (forall m. Monad m => Content -> MP m (Seq Content))
- data Counter
- data LUnit
- data Length
- renderLength :: Bool -> Length -> Text
- data Horiz
- data Vert
- data Color
- data Direction
- newtype Identifier = Identifier Text
- lookupIdentifier :: Monad m => Identifier -> MP m Val
- joinVals :: MonadFail m => Val -> Val -> m Val
- prettyVal :: Val -> Doc
- valToContent :: Val -> Seq Content
- prettyType :: ValType -> Text
- repr :: Val -> Text
- data Attempt a
Documentation
Constructors
Constructors
class FromVal a where Source #
Instances
| FromVal Rational Source # | |
| FromVal Text Source # | |
| FromVal RE Source # | |
| FromVal Counter Source # | |
| FromVal Direction Source # | |
| FromVal Function Source # | |
| FromVal Length Source # | |
| FromVal Selector Source # | |
| FromVal Val Source # | |
| FromVal String Source # | |
| FromVal Integer Source # | |
| FromVal Bool Source # | |
| FromVal Double Source # | |
| FromVal Int Source # | |
| FromVal (Seq Content) Source # | |
| FromVal a => FromVal (Vector a) Source # | |
| FromVal a => FromVal (Maybe a) Source # | |
class Multipliable a where Source #
Instances
| Multipliable Val Source # | |
Defined in Typst.Types | |
Constructors
Constructors
| Symbol | |
Fields
| |
Constructors
| Txt !Text | |
| Lab !Text | |
| Elt | |
Fields
| |
Constructors
| Arguments | |
Fields
| |
getNamedArg :: (MonadFail m, MonadPlus m, FromVal a) => Identifier -> Arguments -> m a Source #
Constructors
| FunctionScope | |
| BlockScope |
data FlowDirective Source #
Constructors
| FlowNormal | |
| FlowBreak | |
| FlowContinue | |
| FlowReturn Bool |
Instances
| Show FlowDirective Source # | |
Defined in Typst.Types Methods showsPrec :: Int -> FlowDirective -> ShowS # show :: FlowDirective -> String # showList :: [FlowDirective] -> ShowS # | |
| Eq FlowDirective Source # | |
Defined in Typst.Types Methods (==) :: FlowDirective -> FlowDirective -> Bool # (/=) :: FlowDirective -> FlowDirective -> Bool # | |
| Ord FlowDirective Source # | |
Defined in Typst.Types Methods compare :: FlowDirective -> FlowDirective -> Ordering # (<) :: FlowDirective -> FlowDirective -> Bool # (<=) :: FlowDirective -> FlowDirective -> Bool # (>) :: FlowDirective -> FlowDirective -> Bool # (>=) :: FlowDirective -> FlowDirective -> Bool # max :: FlowDirective -> FlowDirective -> FlowDirective # min :: FlowDirective -> FlowDirective -> FlowDirective # | |
data Operations m Source #
Constructors
| Operations | |
Fields
| |
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 |
| XdgConfig | For configuration files.
It uses the |
| XdgCache | For non-essential files (e.g. cache).
It uses the |
| 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 Since: directory-1.3.7.0 |
Instances
Constructors
| EvalState | |
Fields
| |
emptyEvalState :: EvalState m Source #
Constructors
| CounterCustom !Text | |
| CounterLabel !Text | |
| CounterSelector !Selector | |
| CounterPage |
Constructors
| HorizStart | |
| HorizEnd | |
| HorizLeft | |
| HorizCenter | |
| HorizRight |
Constructors
| VertTop | |
| VertHorizon | |
| VertBottom |
Constructors
| RGB Rational Rational Rational Rational | |
| CMYK Rational Rational Rational Rational | |
| Luma Rational |
Instances
| Show Direction Source # | |
| Eq Direction Source # | |
| Ord Direction Source # | |
| FromVal Direction Source # | |
newtype Identifier Source #
Constructors
| Identifier Text |
Instances
lookupIdentifier :: Monad m => Identifier -> MP m Val Source #
prettyType :: ValType -> Text Source #
Instances
| MonadFail Attempt Source # | |
Defined in Typst.Types | |
| Applicative Attempt Source # | |
| Functor Attempt Source # | |
| Monad Attempt Source # | |
| Show a => Show (Attempt a) Source # | |
| Eq a => Eq (Attempt a) Source # | |
| Ord a => Ord (Attempt a) Source # | |