airtable-api-0.3.2.4: Requesting and introspecting Tables within an Airtable project.

Safe HaskellNone
LanguageHaskell2010

Airtable.Table

Contents

Synopsis

Record

data Record a Source #

An airtable record.

Constructors

Record 

Instances

Functor Record Source # 

Methods

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

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

Eq a => Eq (Record a) Source # 

Methods

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

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

Ord a => Ord (Record a) Source # 

Methods

compare :: Record a -> Record a -> Ordering #

(<) :: Record a -> Record a -> Bool #

(<=) :: Record a -> Record a -> Bool #

(>) :: Record a -> Record a -> Bool #

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

max :: Record a -> Record a -> Record a #

min :: Record a -> Record a -> Record a #

Read a => Read (Record a) Source # 
Show a => Show (Record a) Source # 

Methods

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

show :: Record a -> String #

showList :: [Record a] -> ShowS #

Generic (Record a) Source # 

Associated Types

type Rep (Record a) :: * -> * #

Methods

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

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

ToJSON a => ToJSON (Record a) Source # 
FromJSON a => FromJSON (Record a) Source # 
HasRecordId (Record a) Source # 

Methods

toRecId :: Record a -> RecordID Source #

type Rep (Record a) Source # 
type Rep (Record a) = D1 (MetaData "Record" "Airtable.Table" "airtable-api-0.3.2.4-1b5HaNvaRlv8BV4bY4128D" False) (C1 (MetaCons "Record" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "recordId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RecordID)) ((:*:) (S1 (MetaSel (Just Symbol "recordObj") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Just Symbol "createdTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)))))

RecordID

newtype RecordID Source #

Airtable's record ID for use in indexing records

Constructors

RecordID Text 

Instances

Eq RecordID Source # 
Ord RecordID Source # 
Read RecordID Source # 
Show RecordID Source # 
Generic RecordID Source # 

Associated Types

type Rep RecordID :: * -> * #

Methods

from :: RecordID -> Rep RecordID x #

to :: Rep RecordID x -> RecordID #

Hashable RecordID Source # 

Methods

hashWithSalt :: Int -> RecordID -> Int #

hash :: RecordID -> Int #

ToJSON RecordID Source # 
FromJSON RecordID Source # 
HasRecordId RecordID Source # 
type Rep RecordID Source # 
type Rep RecordID = D1 (MetaData "RecordID" "Airtable.Table" "airtable-api-0.3.2.4-1b5HaNvaRlv8BV4bY4128D" True) (C1 (MetaCons "RecordID" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

HasRecordId class

class HasRecordId a where Source #

A convenience typeclass for selecting records using RecordID-like keys.

Minimal complete definition

toRecId

Methods

toRecId :: a -> RecordID Source #

Table

data Table a Source #

An airtable table.

Constructors

Table 

Fields

Instances

Functor Table Source # 

Methods

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

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

Eq a => Eq (Table a) Source # 

Methods

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

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

Read a => Read (Table a) Source # 
Show a => Show (Table a) Source # 

Methods

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

show :: Table a -> String #

showList :: [Table a] -> ShowS #

Generic (Table a) Source # 

Associated Types

type Rep (Table a) :: * -> * #

Methods

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

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

Monoid (Table a) Source # 

Methods

mempty :: Table a #

mappend :: Table a -> Table a -> Table a #

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

ToJSON a => ToJSON (Table a) Source # 
FromJSON a => FromJSON (Table a) Source # 
type Rep (Table a) Source # 
type Rep (Table a) = D1 (MetaData "Table" "Airtable.Table" "airtable-api-0.3.2.4-1b5HaNvaRlv8BV4bY4128D" False) (C1 (MetaCons "Table" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "tableRecords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap RecordID (Record a)))) (S1 (MetaSel (Just Symbol "tableOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))

type TableName = String Source #

Synonym used in querying tables from the API.

Table methods

fromRecords :: [Record a] -> Table a Source #

Create a Table from a list of Records.

fromList :: [(RecordID, Record a)] -> Table a Source #

Create a table from a list of key-record pairs.

toList :: Table a -> [(RecordID, Record a)] Source #

Convert a Table to a list of key-record pairs.

exists :: HasRecordId r => Table a -> r -> Bool Source #

Check if a record exists at the given key in a table.

select :: (HasCallStack, HasRecordId r, Show a) => Table a -> r -> Record a Source #

Unsafely lookup a record using its RecordID. Will throw a pretty-printed error if record does not exist.

vSelect :: (HasCallStack, HasRecordId r, Show a) => Table a -> r -> a Source #

Same as select, but returns the record object.

selectMaybe :: HasRecordId r => Table a -> r -> Maybe (Record a) Source #

Safely lookup a record using its RecordID.

vSelectMaybe :: HasRecordId r => Table a -> r -> Maybe a Source #

Same as selectMaybe, but returns the record object.

selectAll :: Table a -> [Record a] Source #

Read all records.

vSelectAll :: Table a -> [a] Source #

Same as selectAll, but returns the record object.

selectAllKeys :: Table a -> [RecordID] Source #

Read all RecordID's.

selectWhere :: Table a -> (Record a -> Bool) -> [Record a] Source #

Select all records satisfying a condition.

vSelectWhere :: Table a -> (a -> Bool) -> [a] Source #

Same as selectWhere, but returns the record object.

selectKeyWhere :: Table a -> (Record a -> Bool) -> [RecordID] Source #

Select all records satisfying a condition.

vSelectKeyWhere :: Table a -> (a -> Bool) -> [RecordID] Source #

Same as selectKeyWhere, but returns the record object.

deleteWhere :: Table a -> (Record a -> Bool) -> Table a Source #

Delete all Records satisfying a condition.

vDeleteWhere :: Table a -> (a -> Bool) -> Table a Source #

Same as deleteWhere, but returns the record object.