Copyright | ©2020 James Alexander Feldman-Crough |
---|---|
License | MPL-2.0 |
Maintainer | alex@fldcr.com |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Document = Document {}
- documentToRegion :: Document -> Region (Series Block)
- regionToDocument :: Region (Series Block) -> Document
- data Tag a = Tag {
- tagName :: Key
- tagMetadata :: Metadata
- tagContent :: a
- tagLocation :: Maybe Location
- type BlockTag = Tag (Series Block)
- type InlineTag = Tag (Series Inline)
- type LiteralTag = Tag Text
- tagToRegion :: Tag a -> Region a
- regionToTag :: Key -> Region a -> Tag a
- data Block
- data Inline
- data Paragraph = Paragraph {}
- data Metadata = Metadata {}
- data Region a = Region {}
- data Fragment = Fragment {}
- newtype Assoc k v = Assoc (HashMap k v)
- data InvalidCharacter
- data KeyError
- data Key
- makeKey :: Text -> Either KeyError Key
- rawKey :: Key -> Text
- data SeriesNE a
- newtype Series a = Series (Seq a)
- newtype Set a = Set (HashSet a)
Documents
A full Prosidy document.
Instances
Eq Document Source # | |
Show Document Source # | |
Generic Document Source # | |
Hashable Document Source # | |
Defined in Prosidy.Types | |
ToJSON Document Source # | |
Defined in Prosidy.Types | |
FromJSON Document Source # | |
Binary Document Source # | |
NFData Document Source # | |
Defined in Prosidy.Types | |
HasContent Document Source # | |
HasMetadata Document Source # | |
type Rep Document Source # | |
Defined in Prosidy.Types type Rep Document = D1 ('MetaData "Document" "Prosidy.Types" "prosidy-1.6.0.0-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 # | |
Defined in Prosidy.Optics.Types |
Tags
A Region
, annotated with a tag name.
Tag | |
|
Instances
type LiteralTag = Tag Text Source #
A Tag
containing a single plain-text item.
Specified in Prosidy source with the #=
sigil.
Contextual enumerations
A sum type enumerating allowed types inside of a block context.
Instances
Eq Block Source # | |
Show Block Source # | |
Generic Block Source # | |
Hashable Block Source # | |
Defined in Prosidy.Types | |
ToJSON Block Source # | |
Defined in Prosidy.Types | |
FromJSON Block Source # | |
Binary Block Source # | |
NFData Block Source # | |
Defined in Prosidy.Types | |
HasLocation Block Source # | |
type Rep Block Source # | |
Defined in Prosidy.Types type Rep Block = D1 ('MetaData "Block" "Prosidy.Types" "prosidy-1.6.0.0-inplace" 'False) (C1 ('MetaCons "BlockLiteral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LiteralTag)) :+: (C1 ('MetaCons "BlockParagraph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Paragraph)) :+: C1 ('MetaCons "BlockTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BlockTag)))) |
A sum type enumerating allowed types inside of an inline context.
Break | Spacing recorded between lines or on either side of an |
InlineTag InlineTag | A |
InlineText Fragment | A fragment of plain text. |
Instances
Eq Inline Source # | |
Show Inline Source # | |
Generic Inline Source # | |
Hashable Inline Source # | |
Defined in Prosidy.Types | |
ToJSON Inline Source # | |
Defined in Prosidy.Types | |
FromJSON Inline Source # | |
Binary Inline Source # | |
NFData Inline Source # | |
Defined in Prosidy.Types | |
HasLocation Inline Source # | |
type Rep Inline Source # | |
Defined in Prosidy.Types type Rep Inline = D1 ('MetaData "Inline" "Prosidy.Types" "prosidy-1.6.0.0-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)))) |
Paragraphs
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
Eq Paragraph Source # | |
Show Paragraph Source # | |
Generic Paragraph Source # | |
Hashable Paragraph Source # | |
Defined in Prosidy.Types | |
ToJSON Paragraph Source # | |
Defined in Prosidy.Types | |
FromJSON Paragraph Source # | |
Binary Paragraph Source # | |
NFData Paragraph Source # | |
Defined in Prosidy.Types | |
HasLocation Paragraph Source # | |
HasContent Paragraph Source # | |
type Rep Paragraph Source # | |
Defined in Prosidy.Types type Rep Paragraph = D1 ('MetaData "Paragraph" "Prosidy.Types" "prosidy-1.6.0.0-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 # | |
Defined in Prosidy.Optics.Types |
Common structures
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.
Metadata | |
|
Instances
Eq Metadata Source # | |
Show Metadata Source # | |
Generic Metadata Source # | |
Semigroup Metadata Source # | |
Monoid Metadata Source # | |
Hashable Metadata Source # | |
Defined in Prosidy.Types | |
ToJSON Metadata Source # | |
Defined in Prosidy.Types | |
FromJSON Metadata Source # | |
Binary Metadata Source # | |
NFData Metadata Source # | |
Defined in Prosidy.Types | |
HasMetadata Metadata Source # | |
type Rep Metadata Source # | |
Defined in Prosidy.Types type Rep Metadata = D1 ('MetaData "Metadata" "Prosidy.Types" "prosidy-1.6.0.0-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)))) |
An untagged structural grouping of items with type a
. Regions do not
occur in parsing.
Region | |
|
Instances
Textual fragments
Plain text, possibly annotated with a Location
.
Fragment | |
|
Instances
Eq Fragment Source # | |
Show Fragment Source # | |
Generic Fragment Source # | |
Hashable Fragment Source # | |
Defined in Prosidy.Types | |
ToJSON Fragment Source # | |
Defined in Prosidy.Types | |
FromJSON Fragment Source # | |
Binary Fragment Source # | |
NFData Fragment Source # | |
Defined in Prosidy.Types | |
HasLocation Fragment Source # | |
type Rep Fragment Source # | |
Defined in Prosidy.Types type Rep Fragment = D1 ('MetaData "Fragment" "Prosidy.Types" "prosidy-1.6.0.0-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)))) |
Utility wrappers
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.
Instances
Functor (Assoc k) Source # | |
Foldable (Assoc k) Source # | |
Defined in Prosidy.Types.Assoc 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 # elem :: Eq a => a -> Assoc k a -> Bool # maximum :: Ord a => Assoc k a -> a # minimum :: Ord a => Assoc k a -> a # | |
(Eq k, Eq v) => Eq (Assoc k v) Source # | |
(Show k, Show v) => Show (Assoc k v) Source # | |
Generic (Assoc k v) Source # | |
(Eq k, Hashable k) => Semigroup (Assoc k v) Source # | |
(Eq k, Hashable k) => Monoid (Assoc k v) Source # | |
(Hashable k, Hashable v) => Hashable (Assoc k v) Source # | |
Defined in Prosidy.Types.Assoc | |
(ToJSON v, ToJSONKey k) => ToJSON (Assoc k v) Source # | |
Defined in Prosidy.Types.Assoc | |
(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (Assoc k v) Source # | |
(Eq k, Hashable k, Binary k, Binary v) => Binary (Assoc k v) Source # | |
(NFData k, NFData v) => NFData (Assoc k v) Source # | |
Defined in Prosidy.Types.Assoc | |
type Rep (Assoc k v) Source # | |
Defined in Prosidy.Types.Assoc |
data InvalidCharacter Source #
Details for errors thrown when creating Key
s with one or more invalid
characters.
Instances
Eq InvalidCharacter Source # | |
Defined in Prosidy.Types.Key (==) :: InvalidCharacter -> InvalidCharacter -> Bool # (/=) :: InvalidCharacter -> InvalidCharacter -> Bool # | |
Show InvalidCharacter Source # | |
Defined in Prosidy.Types.Key showsPrec :: Int -> InvalidCharacter -> ShowS # show :: InvalidCharacter -> String # showList :: [InvalidCharacter] -> ShowS # |
Errors returned when creating invalid keys.
InvalidCharacterError InvalidCharacter | A character provided as a |
EmptyKeyError | A string of length 0 was provided as a |
Instances
Eq KeyError Source # | |
Show KeyError Source # | |
Exception KeyError Source # | |
Defined in Prosidy.Types.Key toException :: KeyError -> SomeException # fromException :: SomeException -> Maybe KeyError # displayException :: KeyError -> String # |
A Key
is an identifier used in tags, properties, and setting names.
Instances
Eq Key Source # | |
Ord Key Source # | |
Show Key Source # | |
IsString Key Source # |
|
Defined in Prosidy.Types.Key fromString :: String -> Key # | |
Generic Key Source # | |
Hashable Key Source # | |
Defined in Prosidy.Types.Key | |
ToJSON Key Source # | |
Defined in Prosidy.Types.Key | |
ToJSONKey Key Source # | |
Defined in Prosidy.Types.Key | |
FromJSON Key Source # | |
FromJSONKey Key Source # | |
Defined in Prosidy.Types.Key | |
Binary Key Source # | |
NFData Key Source # | |
Defined in Prosidy.Types.Key | |
type Rep Key Source # | |
Defined in Prosidy.Types.Key |
A non-empty Series
.
Instances
A newtype wrapper around a sequential collection.
Currently, Series
is implemented as a Seq
, but this is not guarenteed to
be true.
Instances
A newtype wrapper around an unordered collection of unique elements.
Currently, this is implemented as a wrapper around a HashSet
.
Instances
Foldable Set Source # | |
Defined in Prosidy.Types.Set 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 # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
Eq a => Eq (Set a) Source # | |
Show a => Show (Set a) Source # | |
Generic (Set a) Source # | |
(Hashable a, Eq a) => Semigroup (Set a) Source # | |
(Hashable a, Eq a) => Monoid (Set a) Source # | |
Hashable a => Hashable (Set a) Source # | |
Defined in Prosidy.Types.Set | |
(Hashable a, Eq a, ToJSONKey a) => ToJSON (Set a) Source # | |
Defined in Prosidy.Types.Set | |
(Hashable a, Eq a, FromJSONKey a) => FromJSON (Set a) Source # | |
(Eq a, Hashable a, Binary a) => Binary (Set a) Source # | |
NFData a => NFData (Set a) Source # | |
Defined in Prosidy.Types.Set | |
type Rep (Set a) Source # | |
Defined in Prosidy.Types.Set |