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

Typst.Types

Documentation

data RE Source #

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 #

Constructors

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 

Instances

Instances details
FromJSON Val Source # 
Instance details

Defined in Typst.Types

Methods

parseJSON :: Value -> Parser Val

parseJSONList :: Value -> Parser [Val]

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

Methods

fromValue :: Value -> Matcher Val

listFromValue :: Value -> Matcher [Val]

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

Methods

maybeTimes :: Val -> Val -> Maybe Val Source #

maybeDividedBy :: Val -> Val -> Maybe Val Source #

Negatable Val Source # 
Instance details

Defined in Typst.Types

Methods

maybeNegate :: Val -> Maybe Val Source #

Summable Val Source # 
Instance details

Defined in Typst.Types

Methods

maybePlus :: Val -> Val -> Maybe Val Source #

maybeMinus :: Val -> Val -> Maybe Val Source #

data ValType Source #

Instances

Instances details
Show ValType Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> ValType -> ShowS

show :: ValType -> String

showList :: [ValType] -> ShowS

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

Methods

compare :: ValType -> ValType -> Ordering

(<) :: ValType -> ValType -> Bool

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

(>) :: ValType -> ValType -> Bool

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

max :: ValType -> ValType -> ValType

min :: ValType -> ValType -> ValType

hasType :: ValType -> Val -> Bool Source #

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

Methods

maybeNegate :: Val -> Maybe Val Source #

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

Methods

maybePlus :: Val -> Val -> Maybe Val Source #

maybeMinus :: Val -> Val -> Maybe Val Source #

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

Methods

maybeTimes :: Val -> Val -> Maybe Val Source #

maybeDividedBy :: Val -> Val -> Maybe Val Source #

data Selector Source #

Instances

Instances details
Show Selector Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Selector -> ShowS

show :: Selector -> String

showList :: [Selector] -> ShowS

Eq Selector Source # 
Instance details

Defined in Typst.Types

Methods

(==) :: Selector -> Selector -> Bool

(/=) :: Selector -> Selector -> Bool

Ord Selector Source # 
Instance details

Defined in Typst.Types

Methods

compare :: Selector -> Selector -> Ordering

(<) :: Selector -> Selector -> Bool

(<=) :: Selector -> Selector -> Bool

(>) :: Selector -> Selector -> Bool

(>=) :: Selector -> Selector -> Bool

max :: Selector -> Selector -> Selector

min :: Selector -> Selector -> Selector

FromVal Selector Source # 
Instance details

Defined in Typst.Types

Methods

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

data Symbol Source #

Constructors

Symbol 

Fields

Instances

Instances details
Show Symbol Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Symbol -> ShowS

show :: Symbol -> String

showList :: [Symbol] -> ShowS

Eq Symbol Source # 
Instance details

Defined in Typst.Types

Methods

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

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

data Content Source #

Constructors

Txt !Text 
Lab !Text 
Elt 

Fields

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

Methods

showsPrec :: Int -> Content -> ShowS

show :: Content -> String

showList :: [Content] -> ShowS

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

Methods

compare :: Content -> Content -> Ordering

(<) :: Content -> Content -> Bool

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

(>) :: Content -> Content -> Bool

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

max :: Content -> Content -> Content

min :: Content -> Content -> Content

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

Methods

showsPrec :: Int -> Function -> ShowS

show :: Function -> String

showList :: [Function] -> ShowS

Eq Function Source # 
Instance details

Defined in Typst.Types

Methods

(==) :: Function -> Function -> Bool

(/=) :: Function -> Function -> Bool

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

Methods

(<>) :: Arguments -> Arguments -> Arguments

sconcat :: NonEmpty Arguments -> Arguments

stimes :: Integral b => b -> Arguments -> Arguments

Show Arguments Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Arguments -> ShowS

show :: Arguments -> String

showList :: [Arguments] -> ShowS

Eq Arguments Source # 
Instance details

Defined in Typst.Types

Methods

(==) :: Arguments -> Arguments -> Bool

(/=) :: Arguments -> Arguments -> Bool

getPositionalArg :: (MonadFail m, MonadPlus m, FromVal a) => Int -> Arguments -> m a Source #

getNamedArg :: (MonadFail m, MonadPlus m, FromVal a) => Identifier -> Arguments -> m a Source #

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 FlowDirective Source #

Instances

Instances details
Show FlowDirective Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> FlowDirective -> ShowS

show :: FlowDirective -> String

showList :: [FlowDirective] -> ShowS

Eq FlowDirective Source # 
Instance details

Defined in Typst.Types

Ord FlowDirective Source # 
Instance details

Defined in Typst.Types

data Operations m Source #

Constructors

Operations 

Fields

data XdgDirectory #

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

Methods

readsPrec :: Int -> ReadS XdgDirectory

readList :: ReadS [XdgDirectory]

readPrec :: ReadPrec XdgDirectory

readListPrec :: ReadPrec [XdgDirectory]

Show XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Methods

showsPrec :: Int -> XdgDirectory -> ShowS

show :: XdgDirectory -> String

showList :: [XdgDirectory] -> ShowS

Eq XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Methods

(==) :: XdgDirectory -> XdgDirectory -> Bool

(/=) :: XdgDirectory -> XdgDirectory -> Bool

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

Methods

showsPrec :: Int -> ShowRule -> ShowS

show :: ShowRule -> String

showList :: [ShowRule] -> ShowS

data Counter Source #

Instances

Instances details
Show Counter Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Counter -> ShowS

show :: Counter -> String

showList :: [Counter] -> ShowS

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

Methods

compare :: Counter -> Counter -> Ordering

(<) :: Counter -> Counter -> Bool

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

(>) :: Counter -> Counter -> Bool

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

max :: Counter -> Counter -> Counter

min :: Counter -> Counter -> Counter

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 #

Constructors

LExact Double LUnit 
LRatio !Rational 
LSum Length Length 

Instances

Instances details
Monoid Length Source # 
Instance details

Defined in Typst.Types

Semigroup Length Source # 
Instance details

Defined in Typst.Types

Methods

(<>) :: Length -> Length -> Length

sconcat :: NonEmpty Length -> Length

stimes :: Integral b => b -> Length -> Length

Show Length Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Length -> ShowS

show :: Length -> String

showList :: [Length] -> ShowS

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 #

renderLength :: Bool -> Length -> Text 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 #

Constructors

RGB Rational Rational Rational Rational 
CMYK Rational Rational Rational Rational 
Luma Rational 

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 
Rtl 
Ttb 
Btt 

Instances

Instances details
Show Direction Source # 
Instance details

Defined in Typst.Types

Methods

showsPrec :: Int -> Direction -> ShowS

show :: Direction -> String

showList :: [Direction] -> ShowS

Eq Direction Source # 
Instance details

Defined in Typst.Types

Methods

(==) :: Direction -> Direction -> Bool

(/=) :: Direction -> Direction -> Bool

Ord Direction Source # 
Instance details

Defined in Typst.Types

Methods

compare :: Direction -> Direction -> Ordering

(<) :: Direction -> Direction -> Bool

(<=) :: Direction -> Direction -> Bool

(>) :: Direction -> Direction -> Bool

(>=) :: Direction -> Direction -> Bool

max :: Direction -> Direction -> Direction

min :: Direction -> Direction -> Direction

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

Methods

fromString :: String -> Identifier

Monoid Identifier Source # 
Instance details

Defined in Typst.Syntax

Semigroup Identifier Source # 
Instance details

Defined in Typst.Syntax

Methods

(<>) :: Identifier -> Identifier -> Identifier

sconcat :: NonEmpty Identifier -> Identifier

stimes :: Integral b => b -> Identifier -> Identifier

Show Identifier Source # 
Instance details

Defined in Typst.Syntax

Methods

showsPrec :: Int -> Identifier -> ShowS

show :: Identifier -> String

showList :: [Identifier] -> ShowS

Eq Identifier Source # 
Instance details

Defined in Typst.Syntax

Methods

(==) :: Identifier -> Identifier -> Bool

(/=) :: Identifier -> Identifier -> Bool

Ord Identifier Source # 
Instance details

Defined in Typst.Syntax

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

prettyVal :: Val -> Doc Source #

repr :: Val -> Text 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