prosidy-1.6.0.2: A simple language for writing documents.
Copyright©2020 James Alexander Feldman-Crough
LicenseMPL-2.0
Maintaineralex@fldcr.com
Safe HaskellSafe
LanguageHaskell2010

Prosidy

Description

 
Synopsis

Documentation

data Offset Source #

An offset into a Source, counted by UTF-8 codepoint.

Instances

Instances details
Enum Offset Source # 
Instance details

Defined in Prosidy.Source.Units

Eq Offset Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

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

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

Ord Offset Source # 
Instance details

Defined in Prosidy.Source.Units

Show Offset Source # 
Instance details

Defined in Prosidy.Source.Units

Generic Offset Source # 
Instance details

Defined in Prosidy.Source.Units

Associated Types

type Rep Offset :: Type -> Type #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

Hashable Offset Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

hashWithSalt :: Int -> Offset -> Int #

hash :: Offset -> Int #

ToJSON Offset Source # 
Instance details

Defined in Prosidy.Source.Units

FromJSON Offset Source # 
Instance details

Defined in Prosidy.Source.Units

Binary Offset Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

put :: Offset -> Put #

get :: Get Offset #

putList :: [Offset] -> Put #

NFData Offset Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

rnf :: Offset -> () #

Pretty Offset Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

pretty :: Offset -> Doc ann #

prettyList :: [Offset] -> Doc ann #

Unbox Offset Source # 
Instance details

Defined in Prosidy.Source.LineMap

Vector Vector Offset Source # 
Instance details

Defined in Prosidy.Source.LineMap

MVector MVector Offset Source # 
Instance details

Defined in Prosidy.Source.LineMap

type Rep Offset Source # 
Instance details

Defined in Prosidy.Source.Units

type Rep Offset = D1 ('MetaData "Offset" "Prosidy.Source.Units" "prosidy-1.6.0.2-inplace" 'True) (C1 ('MetaCons "Offset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))
newtype Vector Offset Source # 
Instance details

Defined in Prosidy.Source.LineMap

newtype MVector s Offset Source # 
Instance details

Defined in Prosidy.Source.LineMap

data Column Source #

A column number.

Instances

Instances details
Enum Column Source # 
Instance details

Defined in Prosidy.Source.Units

Eq Column Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

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

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

Ord Column Source # 
Instance details

Defined in Prosidy.Source.Units

Show Column Source # 
Instance details

Defined in Prosidy.Source.Units

Generic Column Source # 
Instance details

Defined in Prosidy.Source.Units

Associated Types

type Rep Column :: Type -> Type #

Methods

from :: Column -> Rep Column x #

to :: Rep Column x -> Column #

Hashable Column Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

hashWithSalt :: Int -> Column -> Int #

hash :: Column -> Int #

ToJSON Column Source # 
Instance details

Defined in Prosidy.Source.Units

FromJSON Column Source # 
Instance details

Defined in Prosidy.Source.Units

Binary Column Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

put :: Column -> Put #

get :: Get Column #

putList :: [Column] -> Put #

NFData Column Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

rnf :: Column -> () #

Pretty Column Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

pretty :: Column -> Doc ann #

prettyList :: [Column] -> Doc ann #

type Rep Column Source # 
Instance details

Defined in Prosidy.Source.Units

type Rep Column = D1 ('MetaData "Column" "Prosidy.Source.Units" "prosidy-1.6.0.2-inplace" 'True) (C1 ('MetaCons "Column" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

data Line Source #

A line number.

The Show instance for Line counts from one, while the internal implementation counts from zero.

Instances

Instances details
Enum Line Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

succ :: Line -> Line #

pred :: Line -> Line #

toEnum :: Int -> Line #

fromEnum :: Line -> Int #

enumFrom :: Line -> [Line] #

enumFromThen :: Line -> Line -> [Line] #

enumFromTo :: Line -> Line -> [Line] #

enumFromThenTo :: Line -> Line -> Line -> [Line] #

Eq Line Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

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

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

Ord Line Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

compare :: Line -> Line -> Ordering #

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

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

(>) :: Line -> Line -> Bool #

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

max :: Line -> Line -> Line #

min :: Line -> Line -> Line #

Show Line Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

Generic Line Source # 
Instance details

Defined in Prosidy.Source.Units

Associated Types

type Rep Line :: Type -> Type #

Methods

from :: Line -> Rep Line x #

to :: Rep Line x -> Line #

Hashable Line Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

hashWithSalt :: Int -> Line -> Int #

hash :: Line -> Int #

ToJSON Line Source # 
Instance details

Defined in Prosidy.Source.Units

FromJSON Line Source # 
Instance details

Defined in Prosidy.Source.Units

Binary Line Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

put :: Line -> Put #

get :: Get Line #

putList :: [Line] -> Put #

NFData Line Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

rnf :: Line -> () #

Pretty Line Source # 
Instance details

Defined in Prosidy.Source.Units

Methods

pretty :: Line -> Doc ann #

prettyList :: [Line] -> Doc ann #

type Rep Line Source # 
Instance details

Defined in Prosidy.Source.Units

type Rep Line = D1 ('MetaData "Line" "Prosidy.Source.Units" "prosidy-1.6.0.2-inplace" 'True) (C1 ('MetaCons "Line" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

data Location Source #

A location in a Source, with the line and column number computed lazily.

Instances

Instances details
Eq Location Source # 
Instance details

Defined in Prosidy.Source

Show Location Source # 
Instance details

Defined in Prosidy.Source

Generic Location Source # 
Instance details

Defined in Prosidy.Source

Associated Types

type Rep Location :: Type -> Type #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

Hashable Location Source # 
Instance details

Defined in Prosidy.Source

Methods

hashWithSalt :: Int -> Location -> Int #

hash :: Location -> Int #

Binary Location Source # 
Instance details

Defined in Prosidy.Source

Methods

put :: Location -> Put #

get :: Get Location #

putList :: [Location] -> Put #

NFData Location Source # 
Instance details

Defined in Prosidy.Source

Methods

rnf :: Location -> () #

Pretty Location Source # 
Instance details

Defined in Prosidy.Source

Methods

pretty :: Location -> Doc ann #

prettyList :: [Location] -> Doc ann #

HasLocation Location Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Location Location Source #

type Rep Location Source # 
Instance details

Defined in Prosidy.Source

type Rep Location = D1 ('MetaData "Location" "Prosidy.Source" "prosidy-1.6.0.2-inplace" 'False) (C1 ('MetaCons "Location" 'PrefixI 'True) ((S1 ('MetaSel ('Just "locationSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Source) :*: S1 ('MetaSel ('Just "locationOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Offset)) :*: (S1 ('MetaSel ('Just "locationLine") 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 Line) :*: S1 ('MetaSel ('Just "locationColumn") 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 Column))))

data Source Source #

Information about Prosidy source file.

The Show instance for ths class does not include the LineMap or Text fields, as those are rather noisy.

Instances

Instances details
Eq Source Source # 
Instance details

Defined in Prosidy.Source

Methods

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

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

Show Source Source # 
Instance details

Defined in Prosidy.Source

Generic Source Source # 
Instance details

Defined in Prosidy.Source

Associated Types

type Rep Source :: Type -> Type #

Methods

from :: Source -> Rep Source x #

to :: Rep Source x -> Source #

Hashable Source Source # 
Instance details

Defined in Prosidy.Source

Methods

hashWithSalt :: Int -> Source -> Int #

hash :: Source -> Int #

Binary Source Source # 
Instance details

Defined in Prosidy.Source

Methods

put :: Source -> Put #

get :: Get Source #

putList :: [Source] -> Put #

NFData Source Source # 
Instance details

Defined in Prosidy.Source

Methods

rnf :: Source -> () #

Pretty Source Source # 
Instance details

Defined in Prosidy.Source

Methods

pretty :: Source -> Doc ann #

prettyList :: [Source] -> Doc ann #

type Rep Source Source # 
Instance details

Defined in Prosidy.Source

type Rep Source = D1 ('MetaData "Source" "Prosidy.Source" "prosidy-1.6.0.2-inplace" 'False) (C1 ('MetaCons "Source" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String) :*: (S1 ('MetaSel ('Just "sourceText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "sourceLineMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LineMap))))

newtype Assoc k v Source #

An associative mapping of keys to values.

Currently implemented as a HashMap, this newtype wrapper allows us to:

1) Add non-orphan instances to the underlying structure. 2) Change the underlying type if needed.

Constructors

Assoc (HashMap k v) 

Instances

Instances details
Functor (Assoc k) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

fmap :: (a -> b) -> Assoc k a -> Assoc k b #

(<$) :: a -> Assoc k b -> Assoc k a #

Foldable (Assoc k) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

fold :: Monoid m => Assoc k m -> m #

foldMap :: Monoid m => (a -> m) -> Assoc k a -> m #

foldMap' :: Monoid m => (a -> m) -> Assoc k a -> m #

foldr :: (a -> b -> b) -> b -> Assoc k a -> b #

foldr' :: (a -> b -> b) -> b -> Assoc k a -> b #

foldl :: (b -> a -> b) -> b -> Assoc k a -> b #

foldl' :: (b -> a -> b) -> b -> Assoc k a -> b #

foldr1 :: (a -> a -> a) -> Assoc k a -> a #

foldl1 :: (a -> a -> a) -> Assoc k a -> a #

toList :: Assoc k a -> [a] #

null :: Assoc k a -> Bool #

length :: Assoc k a -> Int #

elem :: Eq a => a -> Assoc k a -> Bool #

maximum :: Ord a => Assoc k a -> a #

minimum :: Ord a => Assoc k a -> a #

sum :: Num a => Assoc k a -> a #

product :: Num a => Assoc k a -> a #

(Eq k, Eq v) => Eq (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

(==) :: Assoc k v -> Assoc k v -> Bool #

(/=) :: Assoc k v -> Assoc k v -> Bool #

(Show k, Show v) => Show (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

showsPrec :: Int -> Assoc k v -> ShowS #

show :: Assoc k v -> String #

showList :: [Assoc k v] -> ShowS #

Generic (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Associated Types

type Rep (Assoc k v) :: Type -> Type #

Methods

from :: Assoc k v -> Rep (Assoc k v) x #

to :: Rep (Assoc k v) x -> Assoc k v #

(Eq k, Hashable k) => Semigroup (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

(<>) :: Assoc k v -> Assoc k v -> Assoc k v #

sconcat :: NonEmpty (Assoc k v) -> Assoc k v #

stimes :: Integral b => b -> Assoc k v -> Assoc k v #

(Eq k, Hashable k) => Monoid (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

mempty :: Assoc k v #

mappend :: Assoc k v -> Assoc k v -> Assoc k v #

mconcat :: [Assoc k v] -> Assoc k v #

(Hashable k, Hashable v) => Hashable (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

hashWithSalt :: Int -> Assoc k v -> Int #

hash :: Assoc k v -> Int #

(ToJSON v, ToJSONKey k) => ToJSON (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

toJSON :: Assoc k v -> Value #

toEncoding :: Assoc k v -> Encoding #

toJSONList :: [Assoc k v] -> Value #

toEncodingList :: [Assoc k v] -> Encoding #

(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

parseJSON :: Value -> Parser (Assoc k v) #

parseJSONList :: Value -> Parser [Assoc k v] #

(Eq k, Hashable k, Binary k, Binary v) => Binary (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

put :: Assoc k v -> Put #

get :: Get (Assoc k v) #

putList :: [Assoc k v] -> Put #

(NFData k, NFData v) => NFData (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

rnf :: Assoc k v -> () #

(Pretty k, Pretty v) => Pretty (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

Methods

pretty :: Assoc k v -> Doc ann #

prettyList :: [Assoc k v] -> Doc ann #

type Rep (Assoc k v) Source # 
Instance details

Defined in Prosidy.Types.Assoc

type Rep (Assoc k v) = D1 ('MetaData "Assoc" "Prosidy.Types.Assoc" "prosidy-1.6.0.2-inplace" 'True) (C1 ('MetaCons "Assoc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap k v))))

data InvalidCharacter Source #

Details for errors thrown when creating Keys with one or more invalid characters.

data KeyError Source #

Errors returned when creating invalid keys.

Constructors

InvalidCharacterError InvalidCharacter

A character provided as a Key's name was invalid.

EmptyKeyError

A string of length 0 was provided as a Key's name.

Instances

Instances details
Eq KeyError Source # 
Instance details

Defined in Prosidy.Types.Key

Show KeyError Source # 
Instance details

Defined in Prosidy.Types.Key

Exception KeyError Source # 
Instance details

Defined in Prosidy.Types.Key

data Key Source #

A Key is an identifier used in tags, properties, and setting names.

Instances

Instances details
Eq Key Source # 
Instance details

Defined in Prosidy.Types.Key

Methods

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

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

Ord Key Source # 
Instance details

Defined in Prosidy.Types.Key

Methods

compare :: Key -> Key -> Ordering #

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

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

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key Source # 
Instance details

Defined in Prosidy.Types.Key

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key Source #

Key exposes an IsString instance, but beware! Invalid strings will throw a pure exception.

Instance details

Defined in Prosidy.Types.Key

Methods

fromString :: String -> Key #

Generic Key Source # 
Instance details

Defined in Prosidy.Types.Key

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Hashable Key Source # 
Instance details

Defined in Prosidy.Types.Key

Methods

hashWithSalt :: Int -> Key -> Int #

hash :: Key -> Int #

ToJSON Key Source # 
Instance details

Defined in Prosidy.Types.Key

ToJSONKey Key Source # 
Instance details

Defined in Prosidy.Types.Key

FromJSON Key Source # 
Instance details

Defined in Prosidy.Types.Key

FromJSONKey Key Source # 
Instance details

Defined in Prosidy.Internal.JSON

Binary Key Source # 
Instance details

Defined in Prosidy.Types.Key

Methods

put :: Key -> Put #

get :: Get Key #

putList :: [Key] -> Put #

NFData Key Source # 
Instance details

Defined in Prosidy.Types.Key

Methods

rnf :: Key -> () #

Pretty Key Source # 
Instance details

Defined in Prosidy.Types.Key

Methods

pretty :: Key -> Doc ann #

prettyList :: [Key] -> Doc ann #

type Rep Key Source # 
Instance details

Defined in Prosidy.Types.Key

type Rep Key = D1 ('MetaData "Key" "Prosidy.Types.Key" "prosidy-1.6.0.2-inplace" 'True) (C1 ('MetaCons "Key" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

makeKey :: Text -> Either KeyError Key Source #

Create a new Key, checking its validity.

rawKey :: Key -> Text Source #

Convert a Key into its Text representation.

data SeriesNE a Source #

A non-empty Series.

Instances

Instances details
Functor SeriesNE Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

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

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

Applicative SeriesNE Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

pure :: a -> SeriesNE a #

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

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

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

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

Foldable SeriesNE Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

fold :: Monoid m => SeriesNE m -> m #

foldMap :: Monoid m => (a -> m) -> SeriesNE a -> m #

foldMap' :: Monoid m => (a -> m) -> SeriesNE a -> m #

foldr :: (a -> b -> b) -> b -> SeriesNE a -> b #

foldr' :: (a -> b -> b) -> b -> SeriesNE a -> b #

foldl :: (b -> a -> b) -> b -> SeriesNE a -> b #

foldl' :: (b -> a -> b) -> b -> SeriesNE a -> b #

foldr1 :: (a -> a -> a) -> SeriesNE a -> a #

foldl1 :: (a -> a -> a) -> SeriesNE a -> a #

toList :: SeriesNE a -> [a] #

null :: SeriesNE a -> Bool #

length :: SeriesNE a -> Int #

elem :: Eq a => a -> SeriesNE a -> Bool #

maximum :: Ord a => SeriesNE a -> a #

minimum :: Ord a => SeriesNE a -> a #

sum :: Num a => SeriesNE a -> a #

product :: Num a => SeriesNE a -> a #

Traversable SeriesNE Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

traverse :: Applicative f => (a -> f b) -> SeriesNE a -> f (SeriesNE b) #

sequenceA :: Applicative f => SeriesNE (f a) -> f (SeriesNE a) #

mapM :: Monad m => (a -> m b) -> SeriesNE a -> m (SeriesNE b) #

sequence :: Monad m => SeriesNE (m a) -> m (SeriesNE a) #

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

Defined in Prosidy.Types.Series

Methods

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

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

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

Defined in Prosidy.Types.Series

Methods

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

show :: SeriesNE a -> String #

showList :: [SeriesNE a] -> ShowS #

Generic (SeriesNE a) Source # 
Instance details

Defined in Prosidy.Types.Series

Associated Types

type Rep (SeriesNE a) :: Type -> Type #

Methods

from :: SeriesNE a -> Rep (SeriesNE a) x #

to :: Rep (SeriesNE a) x -> SeriesNE a #

Semigroup (SeriesNE a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

(<>) :: SeriesNE a -> SeriesNE a -> SeriesNE a #

sconcat :: NonEmpty (SeriesNE a) -> SeriesNE a #

stimes :: Integral b => b -> SeriesNE a -> SeriesNE a #

Hashable a => Hashable (SeriesNE a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

hashWithSalt :: Int -> SeriesNE a -> Int #

hash :: SeriesNE a -> Int #

ToJSON a => ToJSON (SeriesNE a) Source # 
Instance details

Defined in Prosidy.Types.Series

FromJSON a => FromJSON (SeriesNE a) Source # 
Instance details

Defined in Prosidy.Types.Series

Binary a => Binary (SeriesNE a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

put :: SeriesNE a -> Put #

get :: Get (SeriesNE a) #

putList :: [SeriesNE a] -> Put #

NFData a => NFData (SeriesNE a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

rnf :: SeriesNE a -> () #

Pretty a => Pretty (SeriesNE a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

pretty :: SeriesNE a -> Doc ann #

prettyList :: [SeriesNE a] -> Doc ann #

type Rep (SeriesNE a) Source # 
Instance details

Defined in Prosidy.Types.Series

type Rep (SeriesNE a) = D1 ('MetaData "SeriesNE" "Prosidy.Types.Series" "prosidy-1.6.0.2-inplace" 'True) (C1 ('MetaCons "SeriesNE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq a))))

newtype Series a Source #

A newtype wrapper around a sequential collection.

Currently, Series is implemented as a Seq, but this is not guarenteed to be true.

Constructors

Series (Seq a) 

Instances

Instances details
Functor Series Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

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

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

Applicative Series Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

pure :: a -> Series a #

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

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

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

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

Foldable Series Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

fold :: Monoid m => Series m -> m #

foldMap :: Monoid m => (a -> m) -> Series a -> m #

foldMap' :: Monoid m => (a -> m) -> Series a -> m #

foldr :: (a -> b -> b) -> b -> Series a -> b #

foldr' :: (a -> b -> b) -> b -> Series a -> b #

foldl :: (b -> a -> b) -> b -> Series a -> b #

foldl' :: (b -> a -> b) -> b -> Series a -> b #

foldr1 :: (a -> a -> a) -> Series a -> a #

foldl1 :: (a -> a -> a) -> Series a -> a #

toList :: Series a -> [a] #

null :: Series a -> Bool #

length :: Series a -> Int #

elem :: Eq a => a -> Series a -> Bool #

maximum :: Ord a => Series a -> a #

minimum :: Ord a => Series a -> a #

sum :: Num a => Series a -> a #

product :: Num a => Series a -> a #

Traversable Series Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

traverse :: Applicative f => (a -> f b) -> Series a -> f (Series b) #

sequenceA :: Applicative f => Series (f a) -> f (Series a) #

mapM :: Monad m => (a -> m b) -> Series a -> m (Series b) #

sequence :: Monad m => Series (m a) -> m (Series a) #

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

Defined in Prosidy.Types.Series

Methods

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

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

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

Defined in Prosidy.Types.Series

Methods

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

show :: Series a -> String #

showList :: [Series a] -> ShowS #

Generic (Series a) Source # 
Instance details

Defined in Prosidy.Types.Series

Associated Types

type Rep (Series a) :: Type -> Type #

Methods

from :: Series a -> Rep (Series a) x #

to :: Rep (Series a) x -> Series a #

Semigroup (Series a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

(<>) :: Series a -> Series a -> Series a #

sconcat :: NonEmpty (Series a) -> Series a #

stimes :: Integral b => b -> Series a -> Series a #

Monoid (Series a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

mempty :: Series a #

mappend :: Series a -> Series a -> Series a #

mconcat :: [Series a] -> Series a #

Hashable a => Hashable (Series a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

hashWithSalt :: Int -> Series a -> Int #

hash :: Series a -> Int #

ToJSON a => ToJSON (Series a) Source # 
Instance details

Defined in Prosidy.Types.Series

FromJSON a => FromJSON (Series a) Source # 
Instance details

Defined in Prosidy.Types.Series

Binary a => Binary (Series a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

put :: Series a -> Put #

get :: Get (Series a) #

putList :: [Series a] -> Put #

NFData a => NFData (Series a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

rnf :: Series a -> () #

Pretty a => Pretty (Series a) Source # 
Instance details

Defined in Prosidy.Types.Series

Methods

pretty :: Series a -> Doc ann #

prettyList :: [Series a] -> Doc ann #

type Rep (Series a) Source # 
Instance details

Defined in Prosidy.Types.Series

type Rep (Series a) = D1 ('MetaData "Series" "Prosidy.Types.Series" "prosidy-1.6.0.2-inplace" 'True) (C1 ('MetaCons "Series" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq a))))

newtype Set a Source #

A newtype wrapper around an unordered collection of unique elements.

Currently, this is implemented as a wrapper around a HashSet.

Constructors

Set (HashSet a) 

Instances

Instances details
Foldable Set Source # 
Instance details

Defined in Prosidy.Types.Set

Methods

fold :: Monoid m => Set m -> m #

foldMap :: Monoid m => (a -> m) -> Set a -> m #

foldMap' :: Monoid m => (a -> m) -> Set a -> m #

foldr :: (a -> b -> b) -> b -> Set a -> b #

foldr' :: (a -> b -> b) -> b -> Set a -> b #

foldl :: (b -> a -> b) -> b -> Set a -> b #

foldl' :: (b -> a -> b) -> b -> Set a -> b #

foldr1 :: (a -> a -> a) -> Set a -> a #

foldl1 :: (a -> a -> a) -> Set a -> a #

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

elem :: Eq a => a -> Set a -> Bool #

maximum :: Ord a => Set a -> a #

minimum :: Ord a => Set a -> a #

sum :: Num a => Set a -> a #

product :: Num a => Set a -> a #

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

Defined in Prosidy.Types.Set

Methods

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

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

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

Defined in Prosidy.Types.Set

Methods

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

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Generic (Set a) Source # 
Instance details

Defined in Prosidy.Types.Set

Associated Types

type Rep (Set a) :: Type -> Type #

Methods

from :: Set a -> Rep (Set a) x #

to :: Rep (Set a) x -> Set a #

(Hashable a, Eq a) => Semigroup (Set a) Source # 
Instance details

Defined in Prosidy.Types.Set

Methods

(<>) :: Set a -> Set a -> Set a #

sconcat :: NonEmpty (Set a) -> Set a #

stimes :: Integral b => b -> Set a -> Set a #

(Hashable a, Eq a) => Monoid (Set a) Source # 
Instance details

Defined in Prosidy.Types.Set

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

Hashable a => Hashable (Set a) Source # 
Instance details

Defined in Prosidy.Types.Set

Methods

hashWithSalt :: Int -> Set a -> Int #

hash :: Set a -> Int #

(Hashable a, Eq a, ToJSONKey a) => ToJSON (Set a) Source # 
Instance details

Defined in Prosidy.Internal.JSON

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

(Hashable a, Eq a, FromJSONKey a) => FromJSON (Set a) Source # 
Instance details

Defined in Prosidy.Internal.JSON

Methods

parseJSON :: Value -> Parser (Set a) #

parseJSONList :: Value -> Parser [Set a] #

(Eq a, Hashable a, Binary a) => Binary (Set a) Source # 
Instance details

Defined in Prosidy.Types.Set

Methods

put :: Set a -> Put #

get :: Get (Set a) #

putList :: [Set a] -> Put #

NFData a => NFData (Set a) Source # 
Instance details

Defined in Prosidy.Types.Set

Methods

rnf :: Set a -> () #

Pretty a => Pretty (Set a) Source # 
Instance details

Defined in Prosidy.Types.Set

Methods

pretty :: Set a -> Doc ann #

prettyList :: [Set a] -> Doc ann #

type Rep (Set a) Source # 
Instance details

Defined in Prosidy.Types.Set

type Rep (Set a) = D1 ('MetaData "Set" "Prosidy.Types.Set" "prosidy-1.6.0.2-inplace" 'True) (C1 ('MetaCons "Set" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet a))))

type LiteralRegion = Region Text Source #

A Region containing a single plain-text item. Like LiteralTag, without a tag name.

type LiteralTag = Tag Text Source #

A Tag containing a single plain-text item. Specified in Prosidy source with the #= sigil.

type InlineRegion = Region (Series Inline) Source #

A Region containing a zero or more Inline items. Like InlineTag, without a tag name.

type InlineTag = Tag (Series Inline) Source #

A Tag containing zero or more Inline items. Specified in Prosidy source with the # sigil.

type BlockRegion = Region (Series Block) Source #

A Region containing a zero or more Block items. Like BlockTag, without a tag name.

type BlockTag = Tag (Series Block) Source #

A Tag containing zero or more Block items. Specified in Prosidy source with the #- sigil.

data Tag a Source #

A Region, annotated with a tag name.

Constructors

Tag 

Instances

Instances details
Functor Tag Source # 
Instance details

Defined in Prosidy.Types

Methods

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

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

Foldable Tag Source # 
Instance details

Defined in Prosidy.Types

Methods

fold :: Monoid m => Tag m -> m #

foldMap :: Monoid m => (a -> m) -> Tag a -> m #

foldMap' :: Monoid m => (a -> m) -> Tag a -> m #

foldr :: (a -> b -> b) -> b -> Tag a -> b #

foldr' :: (a -> b -> b) -> b -> Tag a -> b #

foldl :: (b -> a -> b) -> b -> Tag a -> b #

foldl' :: (b -> a -> b) -> b -> Tag a -> b #

foldr1 :: (a -> a -> a) -> Tag a -> a #

foldl1 :: (a -> a -> a) -> Tag a -> a #

toList :: Tag a -> [a] #

null :: Tag a -> Bool #

length :: Tag a -> Int #

elem :: Eq a => a -> Tag a -> Bool #

maximum :: Ord a => Tag a -> a #

minimum :: Ord a => Tag a -> a #

sum :: Num a => Tag a -> a #

product :: Num a => Tag a -> a #

Traversable Tag Source # 
Instance details

Defined in Prosidy.Types

Methods

traverse :: Applicative f => (a -> f b) -> Tag a -> f (Tag b) #

sequenceA :: Applicative f => Tag (f a) -> f (Tag a) #

mapM :: Monad m => (a -> m b) -> Tag a -> m (Tag b) #

sequence :: Monad m => Tag (m a) -> m (Tag a) #

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

Defined in Prosidy.Types

Methods

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

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

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

Defined in Prosidy.Types

Methods

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

show :: Tag a -> String #

showList :: [Tag a] -> ShowS #

Generic (Tag a) Source # 
Instance details

Defined in Prosidy.Types

Associated Types

type Rep (Tag a) :: Type -> Type #

Methods

from :: Tag a -> Rep (Tag a) x #

to :: Rep (Tag a) x -> Tag a #

Hashable a => Hashable (Tag a) Source # 
Instance details

Defined in Prosidy.Types

Methods

hashWithSalt :: Int -> Tag a -> Int #

hash :: Tag a -> Int #

ToJSON a => ToJSON (Tag a) Source # 
Instance details

Defined in Prosidy.Internal.JSON

Methods

toJSON :: Tag a -> Value #

toEncoding :: Tag a -> Encoding #

toJSONList :: [Tag a] -> Value #

toEncodingList :: [Tag a] -> Encoding #

FromJSON a => FromJSON (Tag a) Source # 
Instance details

Defined in Prosidy.Internal.JSON

Methods

parseJSON :: Value -> Parser (Tag a) #

parseJSONList :: Value -> Parser [Tag a] #

Binary a => Binary (Tag a) Source # 
Instance details

Defined in Prosidy.Types

Methods

put :: Tag a -> Put #

get :: Get (Tag a) #

putList :: [Tag a] -> Put #

NFData a => NFData (Tag a) Source # 
Instance details

Defined in Prosidy.Types

Methods

rnf :: Tag a -> () #

Pretty a => Pretty (Tag a) Source # 
Instance details

Defined in Prosidy.Types

Methods

pretty :: Tag a -> Doc ann #

prettyList :: [Tag a] -> Doc ann #

HasLocation (Tag a) Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' (Tag a) Location Source #

HasContent (Tag a) Source # 
Instance details

Defined in Prosidy.Optics.Types

Associated Types

type Content (Tag a) Source #

Methods

content :: Lens' (Tag a) (Content (Tag a)) Source #

HasMetadata (Tag a) Source # 
Instance details

Defined in Prosidy.Optics.Types

Methods

metadata :: Lens' (Tag a) Metadata Source #

type Rep (Tag a) Source # 
Instance details

Defined in Prosidy.Types

type Content (Tag a) Source # 
Instance details

Defined in Prosidy.Optics.Types

type Content (Tag a) = a

data Region a Source #

An untagged structural grouping of items with type a. Regions do not occur in parsing.

Instances

Instances details
Functor Region Source # 
Instance details

Defined in Prosidy.Types

Methods

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

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

Foldable Region Source # 
Instance details

Defined in Prosidy.Types

Methods

fold :: Monoid m => Region m -> m #

foldMap :: Monoid m => (a -> m) -> Region a -> m #

foldMap' :: Monoid m => (a -> m) -> Region a -> m #

foldr :: (a -> b -> b) -> b -> Region a -> b #

foldr' :: (a -> b -> b) -> b -> Region a -> b #

foldl :: (b -> a -> b) -> b -> Region a -> b #

foldl' :: (b -> a -> b) -> b -> Region a -> b #

foldr1 :: (a -> a -> a) -> Region a -> a #

foldl1 :: (a -> a -> a) -> Region a -> a #

toList :: Region a -> [a] #

null :: Region a -> Bool #

length :: Region a -> Int #

elem :: Eq a => a -> Region a -> Bool #

maximum :: Ord a => Region a -> a #

minimum :: Ord a => Region a -> a #

sum :: Num a => Region a -> a #

product :: Num a => Region a -> a #

Traversable Region Source # 
Instance details

Defined in Prosidy.Types

Methods

traverse :: Applicative f => (a -> f b) -> Region a -> f (Region b) #

sequenceA :: Applicative f => Region (f a) -> f (Region a) #

mapM :: Monad m => (a -> m b) -> Region a -> m (Region b) #

sequence :: Monad m => Region (m a) -> m (Region a) #

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

Defined in Prosidy.Types

Methods

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

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

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

Defined in Prosidy.Types

Methods

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

show :: Region a -> String #

showList :: [Region a] -> ShowS #

Generic (Region a) Source # 
Instance details

Defined in Prosidy.Types

Associated Types

type Rep (Region a) :: Type -> Type #

Methods

from :: Region a -> Rep (Region a) x #

to :: Rep (Region a) x -> Region a #

Hashable a => Hashable (Region a) Source # 
Instance details

Defined in Prosidy.Types

Methods

hashWithSalt :: Int -> Region a -> Int #

hash :: Region a -> Int #

ToJSON a => ToJSON (Region a) Source # 
Instance details

Defined in Prosidy.Internal.JSON

Binary a => Binary (Region a) Source # 
Instance details

Defined in Prosidy.Types

Methods

put :: Region a -> Put #

get :: Get (Region a) #

putList :: [Region a] -> Put #

NFData a => NFData (Region a) Source # 
Instance details

Defined in Prosidy.Types

Methods

rnf :: Region a -> () #

Pretty a => Pretty (Region a) Source # 
Instance details

Defined in Prosidy.Types

Methods

pretty :: Region a -> Doc ann #

prettyList :: [Region a] -> Doc ann #

HasLocation (Region a) Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' (Region a) Location Source #

HasContent (Region a) Source # 
Instance details

Defined in Prosidy.Optics.Types

Associated Types

type Content (Region a) Source #

Methods

content :: Lens' (Region a) (Content (Region a)) Source #

HasMetadata (Region a) Source # 
Instance details

Defined in Prosidy.Optics.Types

Methods

metadata :: Lens' (Region a) Metadata Source #

type Rep (Region a) Source # 
Instance details

Defined in Prosidy.Types

type Rep (Region a) = D1 ('MetaData "Region" "Prosidy.Types" "prosidy-1.6.0.2-inplace" 'False) (C1 ('MetaCons "Region" 'PrefixI 'True) (S1 ('MetaSel ('Just "regionMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Metadata) :*: (S1 ('MetaSel ('Just "regionContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "regionLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Location)))))
type Content (Region a) Source # 
Instance details

Defined in Prosidy.Optics.Types

type Content (Region a) = a

data Paragraph Source #

A non-empty collection of Inline items. A Paragraph represents the border between block and inline contexts. All ancestors of a paragraph are block items or a document, and all children are inline items.

Instances

Instances details
Eq Paragraph Source # 
Instance details

Defined in Prosidy.Types

Show Paragraph Source # 
Instance details

Defined in Prosidy.Types

Generic Paragraph Source # 
Instance details

Defined in Prosidy.Types

Associated Types

type Rep Paragraph :: Type -> Type #

Hashable Paragraph Source # 
Instance details

Defined in Prosidy.Types

ToJSON Paragraph Source # 
Instance details

Defined in Prosidy.Internal.JSON

FromJSON Paragraph Source # 
Instance details

Defined in Prosidy.Internal.JSON

Binary Paragraph Source # 
Instance details

Defined in Prosidy.Types

NFData Paragraph Source # 
Instance details

Defined in Prosidy.Types

Methods

rnf :: Paragraph -> () #

Pretty Paragraph Source # 
Instance details

Defined in Prosidy.Types

Methods

pretty :: Paragraph -> Doc ann #

prettyList :: [Paragraph] -> Doc ann #

HasLocation Paragraph Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Paragraph Location Source #

HasContent Paragraph Source # 
Instance details

Defined in Prosidy.Optics.Types

Associated Types

type Content Paragraph Source #

type Rep Paragraph Source # 
Instance details

Defined in Prosidy.Types

type Rep Paragraph = D1 ('MetaData "Paragraph" "Prosidy.Types" "prosidy-1.6.0.2-inplace" 'False) (C1 ('MetaCons "Paragraph" 'PrefixI 'True) (S1 ('MetaSel ('Just "paragraphContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (SeriesNE Inline)) :*: S1 ('MetaSel ('Just "paragraphLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Location))))
type Content Paragraph Source # 
Instance details

Defined in Prosidy.Optics.Types

data Metadata Source #

A set of properties and settings, associated with a Region.

The namespaces of properties and settings are distinct; a property can share a name with a setting without conflict.

Constructors

Metadata 

Fields

Instances

Instances details
Eq Metadata Source # 
Instance details

Defined in Prosidy.Types

Show Metadata Source # 
Instance details

Defined in Prosidy.Types

Generic Metadata Source # 
Instance details

Defined in Prosidy.Types

Associated Types

type Rep Metadata :: Type -> Type #

Methods

from :: Metadata -> Rep Metadata x #

to :: Rep Metadata x -> Metadata #

Semigroup Metadata Source # 
Instance details

Defined in Prosidy.Types

Monoid Metadata Source # 
Instance details

Defined in Prosidy.Types

Hashable Metadata Source # 
Instance details

Defined in Prosidy.Types

Methods

hashWithSalt :: Int -> Metadata -> Int #

hash :: Metadata -> Int #

ToJSON Metadata Source # 
Instance details

Defined in Prosidy.Internal.JSON

FromJSON Metadata Source # 
Instance details

Defined in Prosidy.Internal.JSON

Binary Metadata Source # 
Instance details

Defined in Prosidy.Types

Methods

put :: Metadata -> Put #

get :: Get Metadata #

putList :: [Metadata] -> Put #

NFData Metadata Source # 
Instance details

Defined in Prosidy.Types

Methods

rnf :: Metadata -> () #

Pretty Metadata Source # 
Instance details

Defined in Prosidy.Types

Methods

pretty :: Metadata -> Doc ann #

prettyList :: [Metadata] -> Doc ann #

HasMetadata Metadata Source # 
Instance details

Defined in Prosidy.Optics.Types

type Rep Metadata Source # 
Instance details

Defined in Prosidy.Types

type Rep Metadata = D1 ('MetaData "Metadata" "Prosidy.Types" "prosidy-1.6.0.2-inplace" 'False) (C1 ('MetaCons "Metadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "metadataProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set Key)) :*: S1 ('MetaSel ('Just "metadataSettings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Assoc Key Text))))

data Inline Source #

A sum type enumerating allowed types inside of an inline context.

Constructors

Break

Spacing recorded between lines or on either side of an Inline Tag. Although we could represent this as Text, Prosidy defines a special node for this case so that authors in CJK languages (or other languages without explicit spaces between words) may simply ignore these spaces in their output.

InlineTag InlineTag

A Tag which contains only Inline items. These tags begin with the # sigil in source.

InlineText Fragment

A fragment of plain text.

Instances

Instances details
Eq Inline Source # 
Instance details

Defined in Prosidy.Types

Methods

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

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

Show Inline Source # 
Instance details

Defined in Prosidy.Types

Generic Inline Source # 
Instance details

Defined in Prosidy.Types

Associated Types

type Rep Inline :: Type -> Type #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Hashable Inline Source # 
Instance details

Defined in Prosidy.Types

Methods

hashWithSalt :: Int -> Inline -> Int #

hash :: Inline -> Int #

ToJSON Inline Source # 
Instance details

Defined in Prosidy.Internal.JSON

FromJSON Inline Source # 
Instance details

Defined in Prosidy.Internal.JSON

Binary Inline Source # 
Instance details

Defined in Prosidy.Types

Methods

put :: Inline -> Put #

get :: Get Inline #

putList :: [Inline] -> Put #

NFData Inline Source # 
Instance details

Defined in Prosidy.Types

Methods

rnf :: Inline -> () #

Pretty Inline Source # 
Instance details

Defined in Prosidy.Types

Methods

pretty :: Inline -> Doc ann #

prettyList :: [Inline] -> Doc ann #

HasLocation Inline Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Inline Location Source #

type Rep Inline Source # 
Instance details

Defined in Prosidy.Types

type Rep Inline = D1 ('MetaData "Inline" "Prosidy.Types" "prosidy-1.6.0.2-inplace" 'False) (C1 ('MetaCons "Break" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InlineTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InlineTag)) :+: C1 ('MetaCons "InlineText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Fragment))))

data Fragment Source #

Plain text, possibly annotated with a Location.

Constructors

Fragment 

Fields

Instances

Instances details
Eq Fragment Source # 
Instance details

Defined in Prosidy.Types

Show Fragment Source # 
Instance details

Defined in Prosidy.Types

Generic Fragment Source # 
Instance details

Defined in Prosidy.Types

Associated Types

type Rep Fragment :: Type -> Type #

Methods

from :: Fragment -> Rep Fragment x #

to :: Rep Fragment x -> Fragment #

Hashable Fragment Source # 
Instance details

Defined in Prosidy.Types

Methods

hashWithSalt :: Int -> Fragment -> Int #

hash :: Fragment -> Int #

ToJSON Fragment Source # 
Instance details

Defined in Prosidy.Internal.JSON

FromJSON Fragment Source # 
Instance details

Defined in Prosidy.Internal.JSON

Binary Fragment Source # 
Instance details

Defined in Prosidy.Types

Methods

put :: Fragment -> Put #

get :: Get Fragment #

putList :: [Fragment] -> Put #

NFData Fragment Source # 
Instance details

Defined in Prosidy.Types

Methods

rnf :: Fragment -> () #

Pretty Fragment Source # 
Instance details

Defined in Prosidy.Types

Methods

pretty :: Fragment -> Doc ann #

prettyList :: [Fragment] -> Doc ann #

HasLocation Fragment Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Fragment Location Source #

type Rep Fragment Source # 
Instance details

Defined in Prosidy.Types

type Rep Fragment = D1 ('MetaData "Fragment" "Prosidy.Types" "prosidy-1.6.0.2-inplace" 'False) (C1 ('MetaCons "Fragment" 'PrefixI 'True) (S1 ('MetaSel ('Just "fragmentText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "fragmentLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Location))))

data Document Source #

A full Prosidy document.

Instances

Instances details
Eq Document Source # 
Instance details

Defined in Prosidy.Types

Show Document Source # 
Instance details

Defined in Prosidy.Types

Generic Document Source # 
Instance details

Defined in Prosidy.Types

Associated Types

type Rep Document :: Type -> Type #

Methods

from :: Document -> Rep Document x #

to :: Rep Document x -> Document #

Hashable Document Source # 
Instance details

Defined in Prosidy.Types

Methods

hashWithSalt :: Int -> Document -> Int #

hash :: Document -> Int #

ToJSON Document Source # 
Instance details

Defined in Prosidy.Internal.JSON

FromJSON Document Source # 
Instance details

Defined in Prosidy.Internal.JSON

Binary Document Source # 
Instance details

Defined in Prosidy.Types

Methods

put :: Document -> Put #

get :: Get Document #

putList :: [Document] -> Put #

NFData Document Source # 
Instance details

Defined in Prosidy.Types

Methods

rnf :: Document -> () #

Pretty Document Source # 
Instance details

Defined in Prosidy.Types

Methods

pretty :: Document -> Doc ann #

prettyList :: [Document] -> Doc ann #

HasContent Document Source # 
Instance details

Defined in Prosidy.Optics.Types

Associated Types

type Content Document Source #

HasMetadata Document Source # 
Instance details

Defined in Prosidy.Optics.Types

type Rep Document Source # 
Instance details

Defined in Prosidy.Types

type Rep Document = D1 ('MetaData "Document" "Prosidy.Types" "prosidy-1.6.0.2-inplace" 'False) (C1 ('MetaCons "Document" 'PrefixI 'True) (S1 ('MetaSel ('Just "documentMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Metadata) :*: S1 ('MetaSel ('Just "documentContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Series Block))))
type Content Document Source # 
Instance details

Defined in Prosidy.Optics.Types

data Block Source #

A sum type enumerating allowed types inside of a block context.

Instances

Instances details
Eq Block Source # 
Instance details

Defined in Prosidy.Types

Methods

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

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

Show Block Source # 
Instance details

Defined in Prosidy.Types

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block Source # 
Instance details

Defined in Prosidy.Types

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

Hashable Block Source # 
Instance details

Defined in Prosidy.Types

Methods

hashWithSalt :: Int -> Block -> Int #

hash :: Block -> Int #

ToJSON Block Source # 
Instance details

Defined in Prosidy.Internal.JSON

FromJSON Block Source # 
Instance details

Defined in Prosidy.Internal.JSON

Binary Block Source # 
Instance details

Defined in Prosidy.Types

Methods

put :: Block -> Put #

get :: Get Block #

putList :: [Block] -> Put #

NFData Block Source # 
Instance details

Defined in Prosidy.Types

Methods

rnf :: Block -> () #

Pretty Block Source # 
Instance details

Defined in Prosidy.Types

Methods

pretty :: Block -> Doc ann #

prettyList :: [Block] -> Doc ann #

HasLocation Block Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Block Location Source #

type Rep Block Source # 
Instance details

Defined in Prosidy.Types

documentToRegion :: Document -> Region (Series Block) Source #

Convert a Document to a Region. The resulting Region will never have a Location attached.

regionToDocument :: Region (Series Block) -> Document Source #

Convert a Region to a Document. Any Location on the Region will be discarded.

tagToRegion :: Tag a -> Region a Source #

Convert a Tag to a Region by discarding the tag's name.

regionToTag :: Key -> Region a -> Tag a Source #

Convert a Region to a Tag by providing a tag name.

newtype Failure Source #

A parsing error.

Instances

Instances details
Show Failure Source # 
Instance details

Defined in Prosidy.Parse

Exception Failure Source # 
Instance details

Defined in Prosidy.Parse

parseDocument :: FilePath -> Text -> Either Failure Document Source #

Parses a Prosidy Document from its source.

The FilePath parameter is only used for error reporting.

readDocument :: FilePath -> IO Document Source #

Reads a Prosidy Document from the given FilePath.

Errors will be thrown as exceptions. Use parseDocument for a pure implementation.

parseDocumentMetadata :: FilePath -> Text -> Either Failure Metadata Source #

Parses a Prosidy document's header Metadata from source, stopping when the header ends.

The FilePath parameter is only used for error reporting.

readDocumentMetadata :: FilePath -> IO Metadata Source #

Reads a Prosidy document's Metadata header from the given FilePath.

Errors will be thrown as exceptions. Use parseDocumentMetadata for a pure implementation.

prettyFailure :: Failure -> String Source #

Pretty-print a Failure into a message acceptable for displaying to users.

class HasLocation t where Source #

A classy optic for selecting the Location from a value. Note that location is affine: a Location can't be attached to a value which does not -- already have one, and not all values with an instance of HasLocation have a location.

Methods

location :: Affine' t Location Source #

Instances

Instances details
HasLocation Location Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Location Location Source #

HasLocation Paragraph Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Paragraph Location Source #

HasLocation Inline Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Inline Location Source #

HasLocation Fragment Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Fragment Location Source #

HasLocation Block Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' Block Location Source #

HasLocation (Tag a) Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' (Tag a) Location Source #

HasLocation (Region a) Source # 
Instance details

Defined in Prosidy.Optics.Source

Methods

location :: Affine' (Region a) Location Source #

offset :: HasLocation l => Affine' l Offset Source #

Focus on the Offset from a value parsed from a source file. If the Offset is modified, note that the resulting column and line will also be modified as they are denormalizations of this value.

column :: (HasLocation l, Contravariant f, Applicative f) => Optic' (->) f l Column Source #

Fetch the Column from a value parsed from a source file. Modifications are not allowed as the offset and line may become inconsistent.

line :: (HasLocation l, Contravariant f, Applicative f) => Optic' (->) f l Line Source #

Fetch the Line from a value parsed from a source file. Modifications are not allowed as the offset and column may become inconsistent.

source :: (HasLocation l, Contravariant f, Applicative f) => Optic' (->) f l Source Source #

Fetch the Source a value was parsed from. Modifications are not allowed as the line, offset, and column may become inconsistent.

sparse :: Iso' Location SparseLocation Source #

An isomorphism between Location and SparseLocation. This is allowed because although a Location has strictly more data than a SparseLocation, those values are denormalizations of values within SparseLocation.

class HasContent t where Source #

An optic for selecting children of an item in a recursive structure.

Associated Types

type Content t Source #

The type of all of the children collectively. For instance, type Content Document = Series Block, as Document has zero or more contained Blocks.

Methods

content :: Lens' t (Content t) Source #

Instances

Instances details
HasContent Paragraph Source # 
Instance details

Defined in Prosidy.Optics.Types

Associated Types

type Content Paragraph Source #

HasContent Document Source # 
Instance details

Defined in Prosidy.Optics.Types

Associated Types

type Content Document Source #

HasContent (Tag a) Source # 
Instance details

Defined in Prosidy.Optics.Types

Associated Types

type Content (Tag a) Source #

Methods

content :: Lens' (Tag a) (Content (Tag a)) Source #

HasContent (Region a) Source # 
Instance details

Defined in Prosidy.Optics.Types

Associated Types

type Content (Region a) Source #

Methods

content :: Lens' (Region a) (Content (Region a)) Source #

class HasMetadata t where Source #

A classy optic for focusing on items with Metadata, including Tags, Regions, and Documents.

Methods

metadata :: Lens' t Metadata Source #

Instances

Instances details
HasMetadata Metadata Source # 
Instance details

Defined in Prosidy.Optics.Types

HasMetadata Document Source # 
Instance details

Defined in Prosidy.Optics.Types

HasMetadata (Tag a) Source # 
Instance details

Defined in Prosidy.Optics.Types

Methods

metadata :: Lens' (Tag a) Metadata Source #

HasMetadata (Region a) Source # 
Instance details

Defined in Prosidy.Optics.Types

Methods

metadata :: Lens' (Region a) Metadata Source #

properties :: HasMetadata m => Lens' m (Set Key) Source #

Fetch all properties from items which contain metadata.

settings :: HasMetadata m => Lens' m (Assoc Key Text) Source #

Fetch all settings defined on items which contain metadata.

hasProperty :: HasMetadata m => Key -> Lens' m Bool Source #

Check if a property is attached to an item with metadata. Using this optic as a setter will add a property if set to True and remove the property when set to False.

atSetting :: HasMetadata m => Key -> Lens' m (Maybe Text) Source #

Select a setting from an item attached to metadata. Returns Nothing if no value is set.

tag :: Lens' (Tag a) Key Source #

Focus on the name of a Tag.

fragment :: Lens' Fragment Text Source #

Get the contents of a Fragment.

tagged :: Key -> Prism' (Tag a) (Region a) Source #

Focus on the inner Region of Tags with a name. This can be used to filter Tags to a specific subset for manipulation.

_BlockTag :: Prism' Block BlockTag Source #

Focus only on block tags.

_BlockParagraph :: Prism' Block Paragraph Source #

Focus only on paragraphs'

_BlockLiteral :: Prism' Block LiteralTag Source #

Focus only on literal tags.

_InlineTag :: Prism' Inline InlineTag Source #

Focus only on inline tags.

_Text :: Prism' Inline Fragment Source #

Focus only on text nodes.

_Break :: Prism' Inline () Source #

Focus only on breaks.

key :: Prism' Text Key Source #

A Prism from Text into a valid Key.

_Assoc :: Iso (Assoc k v) (Assoc k' v') (HashMap k v) (HashMap k' v') Source #

An isomorphism between Prosidy's Assoc wrapper and HashMap.

_NonEmpty :: Prism' (Series a) (SeriesNE a) Source #

A prism between possibly-empty and non-empty containers.

_Series :: Iso (Series a) (Series b) (Seq a) (Seq b) Source #

An isomorpism between Prosidy's Series wrapper and Seq.

_SeriesNE :: Prism' (Seq a) (SeriesNE a) Source #

A prism from a non-empty Seq into a SeriesNE.

_Set :: Iso (Set a) (Set b) (HashSet a) (HashSet b) Source #

An isomorphism between Prosidy's Set wrapper and HashSet.