Copyright | (c) Jon Schoning 2015 |
---|---|
Maintainer | jonschoning@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Posts = Posts {}
- data Post = Post {
- postHref :: !Text
- postDescription :: !Text
- postExtended :: !Text
- postMeta :: !Text
- postHash :: !Text
- postTime :: !UTCTime
- postShared :: !Bool
- postToRead :: !Bool
- postTags :: [Tag]
- boolFromYesNo :: Text -> Bool
- boolToYesNo :: Bool -> Text
- data PostDates = PostDates {
- postDatesUser :: !Text
- postDatesTag :: !Text
- postDatesCount :: [(Day, Int)]
- type DateCount = (Day, Int)
- data NoteList = NoteList {
- noteListCount :: !Int
- noteListItems :: [NoteListItem]
- data NoteListItem = NoteListItem {}
- data Note = Note {
- noteId :: !Text
- noteHash :: !Text
- noteTitle :: !Text
- noteText :: !Text
- noteLength :: !Int
- noteCreatedAt :: !UTCTime
- noteUpdatedAt :: !UTCTime
- readNoteTime :: MonadFail m => String -> m UTCTime
- showNoteTime :: UTCTime -> String
- type TagMap = HashMap Tag Int
- newtype JsonTagMap = ToJsonTagMap {}
- data Suggested
- = Popular [Text]
- | Recommended [Text]
- newtype DoneResult = ToDoneResult {
- fromDoneResult :: ()
- newtype TextResult = ToTextResult {}
- newtype UpdateTime = ToUpdateTime {}
- type Url = Text
- type Description = Text
- type Extended = Text
- type Tag = Text
- type Old = Tag
- type New = Tag
- type Count = Int
- type NumResults = Int
- type StartOffset = Int
- type Shared = Bool
- type Replace = Bool
- type ToRead = Bool
- type Date = Day
- type DateTime = UTCTime
- type FromDateTime = DateTime
- type ToDateTime = DateTime
- type Meta = Int
- type NoteId = Text
Posts
Instances
Eq Posts Source # | |
Data Posts Source # | |
Defined in Pinboard.ApiTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Posts -> c Posts # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Posts # dataTypeOf :: Posts -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Posts) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Posts) # gmapT :: (forall b. Data b => b -> b) -> Posts -> Posts # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Posts -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Posts -> r # gmapQ :: (forall d. Data d => d -> u) -> Posts -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Posts -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Posts -> m Posts # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Posts -> m Posts # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Posts -> m Posts # | |
Ord Posts Source # | |
Show Posts Source # | |
Generic Posts Source # | |
ToJSON Posts Source # | |
Defined in Pinboard.ApiTypes | |
FromJSON Posts Source # | |
type Rep Posts Source # | |
Defined in Pinboard.ApiTypes type Rep Posts = D1 ('MetaData "Posts" "Pinboard.ApiTypes" "pinboard-0.10.3.0-Kv2fdyIATFsJeRiOdceUOt" 'False) (C1 ('MetaCons "Posts" 'PrefixI 'True) (S1 ('MetaSel ('Just "postsDate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "postsUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "postsPosts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Post])))) |
Post | |
|
Instances
Eq Post Source # | |
Data Post Source # | |
Defined in Pinboard.ApiTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Post -> c Post # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Post # dataTypeOf :: Post -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Post) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Post) # gmapT :: (forall b. Data b => b -> b) -> Post -> Post # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Post -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Post -> r # gmapQ :: (forall d. Data d => d -> u) -> Post -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Post -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Post -> m Post # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Post -> m Post # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Post -> m Post # | |
Ord Post Source # | |
Show Post Source # | |
Generic Post Source # | |
ToJSON Post Source # | |
Defined in Pinboard.ApiTypes | |
FromJSON Post Source # | |
type Rep Post Source # | |
Defined in Pinboard.ApiTypes type Rep Post = D1 ('MetaData "Post" "Pinboard.ApiTypes" "pinboard-0.10.3.0-Kv2fdyIATFsJeRiOdceUOt" 'False) (C1 ('MetaCons "Post" 'PrefixI 'True) (((S1 ('MetaSel ('Just "postHref") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "postDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "postExtended") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "postMeta") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "postHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "postTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)) :*: (S1 ('MetaSel ('Just "postShared") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "postToRead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "postTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag])))))) |
boolFromYesNo :: Text -> Bool Source #
boolToYesNo :: Bool -> Text Source #
PostDates | |
|
Instances
Eq PostDates Source # | |
Data PostDates Source # | |
Defined in Pinboard.ApiTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PostDates -> c PostDates # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PostDates # toConstr :: PostDates -> Constr # dataTypeOf :: PostDates -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PostDates) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PostDates) # gmapT :: (forall b. Data b => b -> b) -> PostDates -> PostDates # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PostDates -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PostDates -> r # gmapQ :: (forall d. Data d => d -> u) -> PostDates -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PostDates -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PostDates -> m PostDates # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PostDates -> m PostDates # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PostDates -> m PostDates # | |
Ord PostDates Source # | |
Defined in Pinboard.ApiTypes | |
Show PostDates Source # | |
Generic PostDates Source # | |
ToJSON PostDates Source # | |
Defined in Pinboard.ApiTypes | |
FromJSON PostDates Source # | |
type Rep PostDates Source # | |
Defined in Pinboard.ApiTypes type Rep PostDates = D1 ('MetaData "PostDates" "Pinboard.ApiTypes" "pinboard-0.10.3.0-Kv2fdyIATFsJeRiOdceUOt" 'False) (C1 ('MetaCons "PostDates" 'PrefixI 'True) (S1 ('MetaSel ('Just "postDatesUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "postDatesTag") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "postDatesCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Day, Int)])))) |
Notes
NoteList | |
|
Instances
Eq NoteList Source # | |
Data NoteList Source # | |
Defined in Pinboard.ApiTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoteList -> c NoteList # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoteList # toConstr :: NoteList -> Constr # dataTypeOf :: NoteList -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoteList) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoteList) # gmapT :: (forall b. Data b => b -> b) -> NoteList -> NoteList # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoteList -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoteList -> r # gmapQ :: (forall d. Data d => d -> u) -> NoteList -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NoteList -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoteList -> m NoteList # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoteList -> m NoteList # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoteList -> m NoteList # | |
Ord NoteList Source # | |
Defined in Pinboard.ApiTypes | |
Show NoteList Source # | |
Generic NoteList Source # | |
ToJSON NoteList Source # | |
Defined in Pinboard.ApiTypes | |
FromJSON NoteList Source # | |
type Rep NoteList Source # | |
Defined in Pinboard.ApiTypes type Rep NoteList = D1 ('MetaData "NoteList" "Pinboard.ApiTypes" "pinboard-0.10.3.0-Kv2fdyIATFsJeRiOdceUOt" 'False) (C1 ('MetaCons "NoteList" 'PrefixI 'True) (S1 ('MetaSel ('Just "noteListCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "noteListItems") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [NoteListItem]))) |
data NoteListItem Source #
NoteListItem | |
|
Instances
Note | |
|
Instances
Eq Note Source # | |
Data Note Source # | |
Defined in Pinboard.ApiTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Note -> c Note # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Note # dataTypeOf :: Note -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Note) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Note) # gmapT :: (forall b. Data b => b -> b) -> Note -> Note # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Note -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Note -> r # gmapQ :: (forall d. Data d => d -> u) -> Note -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Note -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Note -> m Note # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Note -> m Note # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Note -> m Note # | |
Ord Note Source # | |
Show Note Source # | |
Generic Note Source # | |
ToJSON Note Source # | |
Defined in Pinboard.ApiTypes | |
FromJSON Note Source # | |
type Rep Note Source # | |
Defined in Pinboard.ApiTypes type Rep Note = D1 ('MetaData "Note" "Pinboard.ApiTypes" "pinboard-0.10.3.0-Kv2fdyIATFsJeRiOdceUOt" 'False) (C1 ('MetaCons "Note" 'PrefixI 'True) ((S1 ('MetaSel ('Just "noteId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "noteHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "noteTitle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "noteText") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "noteLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "noteCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "noteUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime))))) |
showNoteTime :: UTCTime -> String Source #
Tags
newtype JsonTagMap Source #
Instances
Popular [Text] | |
Recommended [Text] |
Instances
Eq Suggested Source # | |
Data Suggested Source # | |
Defined in Pinboard.ApiTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Suggested -> c Suggested # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Suggested # toConstr :: Suggested -> Constr # dataTypeOf :: Suggested -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Suggested) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Suggested) # gmapT :: (forall b. Data b => b -> b) -> Suggested -> Suggested # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Suggested -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Suggested -> r # gmapQ :: (forall d. Data d => d -> u) -> Suggested -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Suggested -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Suggested -> m Suggested # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Suggested -> m Suggested # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Suggested -> m Suggested # | |
Ord Suggested Source # | |
Defined in Pinboard.ApiTypes | |
Show Suggested Source # | |
Generic Suggested Source # | |
ToJSON Suggested Source # | |
Defined in Pinboard.ApiTypes | |
FromJSON Suggested Source # | |
type Rep Suggested Source # | |
Defined in Pinboard.ApiTypes type Rep Suggested = D1 ('MetaData "Suggested" "Pinboard.ApiTypes" "pinboard-0.10.3.0-Kv2fdyIATFsJeRiOdceUOt" 'False) (C1 ('MetaCons "Popular" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])) :+: C1 ('MetaCons "Recommended" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]))) |
Scalars
newtype DoneResult Source #
ToDoneResult | |
|
Instances
newtype TextResult Source #
Instances
newtype UpdateTime Source #
Instances
Aliases
as defined by RFC 3986. Allowed schemes are http, https, javascript, mailto, ftp and file. The Safari-specific feed scheme is allowed but will be treated as a synonym for http.
type Description = Text Source #
up to 255 characters long
up to 65536 characters long. Any URLs will be auto-linkified when displayed.
type NumResults = Int Source #
type StartOffset = Int Source #
type DateTime = UTCTime Source #
UTC timestamp in this format: 2010-12-11T19:48:02Z. Valid date range is Jan 1, 1 AD to January 1, 2100 (but see note below about future timestamps).
type FromDateTime = DateTime Source #
type ToDateTime = DateTime Source #