symantic-atom-0.0.0.20200523: Library for reading and writing Atom.

Safe HaskellNone
LanguageHaskell2010

Symantic.Atom

Contents

Synopsis

Documentation

format :: (TextConstraint repr Text, TextConstraint repr URI, TextConstraint repr Email, TextConstraint repr LanguageTag, TextConstraint repr RelName, TextConstraint repr MediaType, TextConstraint repr DateTime, Repeatable repr, Dicurryable repr, RelaxNG repr, Dimapable repr, Dimapable (Permutation repr), Optionable repr, Emptyable repr, Tupable (Permutation repr), Definable (Permutation repr)) => repr (Either Feed Entry -> c) c Source #

Main symantic to be used.

start :: (TextConstraint repr Text, TextConstraint repr URI, TextConstraint repr Email, TextConstraint repr LanguageTag, TextConstraint repr RelName, TextConstraint repr MediaType, TextConstraint repr DateTime, Repeatable repr, Dicurryable repr, RelaxNG repr, Dimapable repr, Dimapable (Permutation repr), Optionable repr, Emptyable repr, Tupable (Permutation repr), Definable (Permutation repr)) => repr (Either Feed Entry -> k) k Source #

elem :: XML repr => NCName -> repr a k -> repr a k Source #

attr :: XML repr => NCName -> repr a k -> repr a k Source #

data Common Source #

Constructors

Common 

Fields

Instances
Show Common Source # 
Instance details

Defined in Symantic.Atom

Generic Common Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep Common :: Type -> Type #

Methods

from :: Common -> Rep Common x #

to :: Rep Common x -> Common #

type Rep Common Source # 
Instance details

Defined in Symantic.Atom

type Rep Common = D1 (MetaData "Common" "Symantic.Atom" "symantic-atom-0.0.0.20200523-AFusufvAoxi4vgv6idcEnU" False) (C1 (MetaCons "Common" PrefixI True) (S1 (MetaSel (Just "base") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe URI)) :*: (S1 (MetaSel (Just "lang") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe LanguageTag)) :*: S1 (MetaSel (Just "undefs") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [(QName, Text)]))))

common :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, Dimapable (Permutation repr), Dimapable repr, Definable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Tupable (Permutation repr)) => Permutation repr (Common -> k) k Source #

undefinedAttribute :: (TextConstraint repr a, Dicurryable repr, RelaxNG repr) => repr ((QName, a) -> k) k Source #

newtype URI Source #

Constructors

URI Text 
Instances
Eq URI Source # 
Instance details

Defined in Symantic.Atom

Methods

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

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

Show URI Source # 
Instance details

Defined in Symantic.Atom

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

DecodeText URI Source # 
Instance details

Defined in Symantic.Atom

RNCText URI Source # 
Instance details

Defined in Symantic.Atom

uri :: (TextConstraint repr URI, Definable repr, Textable repr) => repr (URI -> k) k Source #

newtype LanguageTag Source #

Constructors

LanguageTag Text 
Instances
Eq LanguageTag Source # 
Instance details

Defined in Symantic.Atom

Show LanguageTag Source # 
Instance details

Defined in Symantic.Atom

DecodeText LanguageTag Source # 
Instance details

Defined in Symantic.Atom

RNCText LanguageTag Source # 
Instance details

Defined in Symantic.Atom

data Text Source #

Instances
Show Text Source # 
Instance details

Defined in Symantic.Atom

Methods

showsPrec :: Int -> Text -> ShowS #

show :: Text -> String #

showList :: [Text] -> ShowS #

Generic Text Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep Text :: Type -> Type #

Methods

from :: Text -> Rep Text x #

to :: Rep Text x -> Text #

type Rep Text Source # 
Instance details

Defined in Symantic.Atom

textConstruct :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, Dimapable repr, Dimapable (Permutation repr), Definable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Tupable (Permutation repr), Optionable repr) => repr (Text -> k) k Source #

data Person Source #

Instances
Show Person Source # 
Instance details

Defined in Symantic.Atom

Generic Person Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep Person :: Type -> Type #

Methods

from :: Person -> Rep Person x #

to :: Rep Person x -> Person #

type Rep Person Source # 
Instance details

Defined in Symantic.Atom

person :: (TextConstraint repr Text, TextConstraint repr URI, TextConstraint repr Email, TextConstraint repr LanguageTag, Repeatable repr, Dicurryable repr, RelaxNG repr, Dimapable repr, Dimapable (Permutation repr), Definable (Permutation repr), Tupable (Permutation repr)) => repr (Person -> k) k Source #

newtype Email Source #

Constructors

Email Text 
Instances
Eq Email Source # 
Instance details

Defined in Symantic.Atom

Methods

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

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

Ord Email Source # 
Instance details

Defined in Symantic.Atom

Methods

compare :: Email -> Email -> Ordering #

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

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

(>) :: Email -> Email -> Bool #

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

max :: Email -> Email -> Email #

min :: Email -> Email -> Email #

Show Email Source # 
Instance details

Defined in Symantic.Atom

Methods

showsPrec :: Int -> Email -> ShowS #

show :: Email -> String #

showList :: [Email] -> ShowS #

DecodeText Email Source # 
Instance details

Defined in Symantic.Atom

RNCText Email Source # 
Instance details

Defined in Symantic.Atom

emailAddress :: (TextConstraint repr Email, Definable repr, Textable repr) => repr (Email -> k) k Source #

dateConstruct :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, TextConstraint repr DateTime, Dimapable (Permutation repr), Dimapable repr, Definable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Tupable (Permutation repr)) => repr ((Common, DateTime) -> k) k Source #

data Feed Source #

Instances
Show Feed Source # 
Instance details

Defined in Symantic.Atom

Methods

showsPrec :: Int -> Feed -> ShowS #

show :: Feed -> String #

showList :: [Feed] -> ShowS #

Generic Feed Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep Feed :: Type -> Type #

Methods

from :: Feed -> Rep Feed x #

to :: Rep Feed x -> Feed #

type Rep Feed Source # 
Instance details

Defined in Symantic.Atom

type Rep Feed = D1 (MetaData "Feed" "Symantic.Atom" "symantic-atom-0.0.0.20200523-AFusufvAoxi4vgv6idcEnU" False) (C1 (MetaCons "Feed" PrefixI True) (((S1 (MetaSel (Just "feed_authors") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Person]) :*: (S1 (MetaSel (Just "feed_categories") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Category]) :*: S1 (MetaSel (Just "feed_contributors") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Person]))) :*: ((S1 (MetaSel (Just "feed_generator") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Generator)) :*: S1 (MetaSel (Just "feed_icon") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Common, URI)))) :*: (S1 (MetaSel (Just "feed_id") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Common, URI)) :*: S1 (MetaSel (Just "feed_links") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Link])))) :*: (((S1 (MetaSel (Just "feed_logo") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Common, URI))) :*: S1 (MetaSel (Just "feed_rights") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "feed_subtitle") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "feed_title") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))) :*: ((S1 (MetaSel (Just "feed_updated") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Common, DateTime)) :*: S1 (MetaSel (Just "feed_extensions") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Extension])) :*: (S1 (MetaSel (Just "feed_entries") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Entry]) :*: S1 (MetaSel (Just "feed_common") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Common))))))

feed :: (TextConstraint repr Text, TextConstraint repr URI, TextConstraint repr Email, TextConstraint repr LanguageTag, TextConstraint repr RelName, TextConstraint repr MediaType, TextConstraint repr DateTime, Repeatable repr, Dicurryable repr, RelaxNG repr, Dimapable repr, Dimapable (Permutation repr), Definable (Permutation repr), Optionable repr, Emptyable repr, Tupable (Permutation repr)) => repr (Feed -> k) k Source #

author :: (TextConstraint repr Text, TextConstraint repr URI, TextConstraint repr Email, TextConstraint repr LanguageTag, Repeatable repr, Dicurryable repr, RelaxNG repr, Dimapable repr, Dimapable (Permutation repr), Definable (Permutation repr), Tupable (Permutation repr)) => repr (Person -> k) k Source #

data Category Source #

Instances
Show Category Source # 
Instance details

Defined in Symantic.Atom

Generic Category Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep Category :: Type -> Type #

Methods

from :: Category -> Rep Category x #

to :: Rep Category x -> Category #

type Rep Category Source # 
Instance details

Defined in Symantic.Atom

type Rep Category = D1 (MetaData "Category" "Symantic.Atom" "symantic-atom-0.0.0.20200523-AFusufvAoxi4vgv6idcEnU" False) (C1 (MetaCons "Category" PrefixI True) ((S1 (MetaSel (Just "category_term") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "category_scheme") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe URI))) :*: (S1 (MetaSel (Just "category_label") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "category_extensions") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Extension]) :*: S1 (MetaSel (Just "category_common") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Common)))))

category :: (TextConstraint repr Text, TextConstraint repr URI, TextConstraint repr LanguageTag, Repeatable repr, Dicurryable repr, RelaxNG repr, Dimapable repr, Dimapable (Permutation repr), Definable (Permutation repr), Tupable (Permutation repr)) => repr (Category -> k) k Source #

contributor :: (TextConstraint repr Text, TextConstraint repr URI, TextConstraint repr Email, TextConstraint repr LanguageTag, Repeatable repr, Dicurryable repr, RelaxNG repr, Dimapable repr, Dimapable (Permutation repr), Definable (Permutation repr), Tupable (Permutation repr)) => repr (Person -> k) k Source #

data Generator Source #

Instances
Show Generator Source # 
Instance details

Defined in Symantic.Atom

Generic Generator Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep Generator :: Type -> Type #

type Rep Generator Source # 
Instance details

Defined in Symantic.Atom

type Rep Generator = D1 (MetaData "Generator" "Symantic.Atom" "symantic-atom-0.0.0.20200523-AFusufvAoxi4vgv6idcEnU" False) (C1 (MetaCons "Generator" PrefixI True) ((S1 (MetaSel (Just "generator_uri") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe URI)) :*: S1 (MetaSel (Just "generator_version") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "generator_common") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Common) :*: S1 (MetaSel (Just "generator_text") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))

generator :: (TextConstraint repr URI, TextConstraint repr Text, TextConstraint repr LanguageTag, Dimapable repr, Dimapable (Permutation repr), Definable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Tupable (Permutation repr)) => repr (Generator -> k) k Source #

icon :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, Dimapable (Permutation repr), Dimapable repr, Definable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Tupable (Permutation repr)) => repr ((Common, URI) -> k) k Source #

id :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, Dimapable (Permutation repr), Dimapable repr, Definable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Tupable (Permutation repr)) => repr ((Common, URI) -> k) k Source #

data Link Source #

link :: (TextConstraint repr URI, TextConstraint repr RelName, TextConstraint repr MediaType, TextConstraint repr LanguageTag, TextConstraint repr Text, Repeatable repr, Dicurryable repr, RelaxNG repr, Dimapable repr, Dimapable (Permutation repr), Definable (Permutation repr), Tupable (Permutation repr)) => repr (Link -> k) k Source #

newtype RelName Source #

Constructors

RelName Text 
Instances
Eq RelName Source # 
Instance details

Defined in Symantic.Atom

Methods

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

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

Show RelName Source # 
Instance details

Defined in Symantic.Atom

DecodeText RelName Source # 
Instance details

Defined in Symantic.Atom

RNCText RelName Source # 
Instance details

Defined in Symantic.Atom

relName :: (TextConstraint repr RelName, Definable repr, Textable repr) => repr (RelName -> k) k Source #

newtype MediaType Source #

Constructors

MediaType Text 
Instances
Eq MediaType Source # 
Instance details

Defined in Symantic.Atom

Show MediaType Source # 
Instance details

Defined in Symantic.Atom

DecodeText MediaType Source # 
Instance details

Defined in Symantic.Atom

RNCText MediaType Source # 
Instance details

Defined in Symantic.Atom

mediaType :: (TextConstraint repr MediaType, Definable repr, Textable repr) => repr (MediaType -> k) k Source #

:: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, Dimapable (Permutation repr), Dimapable repr, Definable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Tupable (Permutation repr)) => repr ((Common, URI) -> k) k Source #

rights :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, Dimapable repr, Dimapable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Optionable repr, Tupable (Permutation repr), Definable (Permutation repr)) => repr (Text -> k) k Source #

subtitle :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, Dimapable repr, Dimapable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Optionable repr, Tupable (Permutation repr), Definable (Permutation repr)) => repr (Text -> k) k Source #

title :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, Dimapable repr, Dimapable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Optionable repr, Tupable (Permutation repr), Definable (Permutation repr)) => repr (Text -> k) k Source #

updated :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, TextConstraint repr DateTime, Dimapable (Permutation repr), Dimapable repr, Repeatable repr, Dicurryable repr, RelaxNG repr, Tupable (Permutation repr), Definable (Permutation repr)) => repr ((Common, DateTime) -> k) k Source #

data Entry Source #

Instances
Show Entry Source # 
Instance details

Defined in Symantic.Atom

Methods

showsPrec :: Int -> Entry -> ShowS #

show :: Entry -> String #

showList :: [Entry] -> ShowS #

Generic Entry Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep Entry :: Type -> Type #

Methods

from :: Entry -> Rep Entry x #

to :: Rep Entry x -> Entry #

type Rep Entry Source # 
Instance details

Defined in Symantic.Atom

type Rep Entry = D1 (MetaData "Entry" "Symantic.Atom" "symantic-atom-0.0.0.20200523-AFusufvAoxi4vgv6idcEnU" False) (C1 (MetaCons "Entry" PrefixI True) (((S1 (MetaSel (Just "entry_authors") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Person]) :*: (S1 (MetaSel (Just "entry_categories") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Category]) :*: S1 (MetaSel (Just "entry_content") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Common, Content))))) :*: ((S1 (MetaSel (Just "entry_contributors") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Person]) :*: S1 (MetaSel (Just "entry_id") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Common, URI))) :*: (S1 (MetaSel (Just "entry_links") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Link]) :*: S1 (MetaSel (Just "entry_published") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Common, DateTime)))))) :*: ((S1 (MetaSel (Just "entry_rights") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "entry_source") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Source)) :*: S1 (MetaSel (Just "entry_summary") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "entry_title") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "entry_updated") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Common, DateTime))) :*: (S1 (MetaSel (Just "entry_extensions") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Extension]) :*: S1 (MetaSel (Just "entry_common") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Common))))))

entry :: (TextConstraint repr Text, TextConstraint repr URI, TextConstraint repr Email, TextConstraint repr LanguageTag, TextConstraint repr MediaType, TextConstraint repr RelName, TextConstraint repr DateTime, Repeatable repr, Dicurryable repr, RelaxNG repr, Dimapable repr, Dimapable (Permutation repr), Definable (Permutation repr), Optionable repr, Emptyable repr, Tupable (Permutation repr)) => repr (Entry -> k) k Source #

data Content Source #

Instances
Show Content Source # 
Instance details

Defined in Symantic.Atom

Generic Content Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep Content :: Type -> Type #

Methods

from :: Content -> Rep Content x #

to :: Rep Content x -> Content #

type Rep Content Source # 
Instance details

Defined in Symantic.Atom

content :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, TextConstraint repr MediaType, Dimapable (Permutation repr), Dimapable repr, Definable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Tupable (Permutation repr), Optionable repr, Emptyable repr) => repr ((Common, Content) -> k) k Source #

published :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, TextConstraint repr DateTime, Dimapable (Permutation repr), Dimapable repr, Repeatable repr, Dicurryable repr, RelaxNG repr, Tupable (Permutation repr), Definable (Permutation repr)) => repr ((Common, DateTime) -> k) k Source #

summary :: (TextConstraint repr URI, TextConstraint repr LanguageTag, TextConstraint repr Text, Dimapable repr, Dimapable (Permutation repr), Repeatable repr, Dicurryable repr, RelaxNG repr, Optionable repr, Tupable (Permutation repr), Definable (Permutation repr)) => repr (Text -> k) k Source #

data Source Source #

Instances
Show Source Source # 
Instance details

Defined in Symantic.Atom

Generic Source Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep Source :: Type -> Type #

Methods

from :: Source -> Rep Source x #

to :: Rep Source x -> Source #

type Rep Source Source # 
Instance details

Defined in Symantic.Atom

type Rep Source = D1 (MetaData "Source" "Symantic.Atom" "symantic-atom-0.0.0.20200523-AFusufvAoxi4vgv6idcEnU" False) (C1 (MetaCons "Source" PrefixI True) (((S1 (MetaSel (Just "source_authors") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Person]) :*: (S1 (MetaSel (Just "source_categories") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Category]) :*: S1 (MetaSel (Just "source_contributors") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Person]))) :*: ((S1 (MetaSel (Just "source_generator") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Generator)) :*: S1 (MetaSel (Just "source_icon") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Common, URI)))) :*: (S1 (MetaSel (Just "source_id") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Common, URI))) :*: S1 (MetaSel (Just "source_links") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Link])))) :*: ((S1 (MetaSel (Just "source_logo") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Common, URI))) :*: (S1 (MetaSel (Just "source_rights") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "source_subtitle") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "source_title") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "source_updated") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Common, DateTime)))) :*: (S1 (MetaSel (Just "source_extensions") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Extension]) :*: S1 (MetaSel (Just "source_common") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Common))))))

source :: (TextConstraint repr Text, TextConstraint repr URI, TextConstraint repr Email, TextConstraint repr LanguageTag, TextConstraint repr RelName, TextConstraint repr MediaType, TextConstraint repr DateTime, Repeatable repr, Dicurryable repr, RelaxNG repr, Dimapable repr, Dimapable (Permutation repr), Definable (Permutation repr), Optionable repr, Tupable (Permutation repr)) => repr (Source -> k) k Source #

extension :: (TextConstraint repr a, TextConstraint repr Text, Dicurryable repr, RelaxNG repr, Repeatable repr, Dimapable repr) => repr ((QName, ([(QName, a)], [Tree AnyNode])) -> k) k Source #

data AnyNode Source #

Instances
Show AnyNode Source # 
Instance details

Defined in Symantic.Atom

Generic AnyNode Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep AnyNode :: Type -> Type #

Methods

from :: AnyNode -> Rep AnyNode x #

to :: Rep AnyNode x -> AnyNode #

type Rep AnyNode Source # 
Instance details

Defined in Symantic.Atom

anyNode :: (TextConstraint repr Text, Dimapable repr, Dicurryable repr, RelaxNG repr, Repeatable repr) => repr (Tree AnyNode -> k) k Source #

data XHTMLNode Source #

Instances
Show XHTMLNode Source # 
Instance details

Defined in Symantic.Atom

Generic XHTMLNode Source # 
Instance details

Defined in Symantic.Atom

Associated Types

type Rep XHTMLNode :: Type -> Type #

type Rep XHTMLNode Source # 
Instance details

Defined in Symantic.Atom

xhtmlNode :: (TextConstraint repr Text, Dimapable repr, Dicurryable repr, RelaxNG repr, Repeatable repr) => repr (Tree XHTMLNode -> k) k Source #

divXHTML :: (TextConstraint repr Text, Dimapable repr, Repeatable repr, Dicurryable repr, RelaxNG repr) => repr (Tree XHTMLNode -> k) k Source #

Orphan instances

DecodeText DateTime Source # 
Instance details

RNCText DateTime Source # 
Instance details

IsString str => MonadFail (Either str) Source # 
Instance details

Methods

fail :: String -> Either str a #