firestore-0.1.0.0: Wrapper for Google Firestore/Datastore API
Safe HaskellNone
LanguageHaskell2010

Database.Firestore

Description

This is an arguably convenient wrapper around gogol's FireStore. This is likely not the idiomatic or best API for Google Firestore/Datastore/Firebase. I don't even understand the difference between all of those trademarks. Bug reports and suggestions are welcome.

Synopsis

The types

data Document Source #

Constructors

Document 

Fields

Instances

Instances details
Eq Document Source # 
Instance details

Defined in Database.Firestore.Types

Show Document Source # 
Instance details

Defined in Database.Firestore.Types

Generic Document Source # 
Instance details

Defined in Database.Firestore.Types

Associated Types

type Rep Document :: Type -> Type #

Methods

from :: Document -> Rep Document x #

to :: Rep Document x -> Document #

ToJSON Document Source # 
Instance details

Defined in Database.Firestore.Types

type Rep Document Source # 
Instance details

Defined in Database.Firestore.Types

type Rep Document = D1 ('MetaData "Document" "Database.Firestore.Types" "firestore-0.1.0.0-GrbsSLYeGb4AmfYCFA8tEe" 'False) (C1 ('MetaCons "Document" 'PrefixI 'True) ((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "createTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe UTCTime))) :*: (S1 ('MetaSel ('Just "updateTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe UTCTime)) :*: S1 ('MetaSel ('Just "fields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Text Value)))))

data Value Source #

Instances

Instances details
Eq Value Source # 
Instance details

Defined in Database.Firestore.Types

Methods

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

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

Show Value Source # 
Instance details

Defined in Database.Firestore.Types

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 
Instance details

Defined in Database.Firestore.Types

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

ToJSON Value Source # 
Instance details

Defined in Database.Firestore.Types

type Rep Value Source # 
Instance details

Defined in Database.Firestore.Types

type Rep Value = D1 ('MetaData "Value" "Database.Firestore.Types" "firestore-0.1.0.0-GrbsSLYeGb4AmfYCFA8tEe" 'False) (((C1 ('MetaCons "GeoPoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "Bytes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) :+: (C1 ('MetaCons "Int" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: (C1 ('MetaCons "Timestamp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime)) :+: C1 ('MetaCons "Double" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))))) :+: ((C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "Bool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "Map" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Text Value))))) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Value])) :+: (C1 ('MetaCons "Reference" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type)))))

data FireStore a Source #

This is just a convenience monad that allows one to avoid all the gogol machinery.

Instances

Instances details
Monad FireStore Source # 
Instance details

Defined in Database.Firestore.Types

Methods

(>>=) :: FireStore a -> (a -> FireStore b) -> FireStore b #

(>>) :: FireStore a -> FireStore b -> FireStore b #

return :: a -> FireStore a #

Functor FireStore Source # 
Instance details

Defined in Database.Firestore.Types

Methods

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

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

Applicative FireStore Source # 
Instance details

Defined in Database.Firestore.Types

Methods

pure :: a -> FireStore a #

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

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

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

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

MonadIO FireStore Source # 
Instance details

Defined in Database.Firestore.Types

Methods

liftIO :: IO a -> FireStore a #

Running FireStore

runFireStore :: (MonadUnliftIO m, HasEnv s env, AllowScopes s, HasScope' s FireStoreScope ~ 'True) => env -> Text -> FireStore a -> m a Source #

Runs the FireStore monad. It needs the env and the project name.

runFireStore env "myproject" someFireStoreAction

defaultEnvironment :: IO (Env FireStoreScope) Source #

This initializes the the google environment with stderr logging, tls manager, and "application default" credentials. (gcloud auth login on your local machine, or maybe gcloud auth application-default login, and it will also probably "just work" with the relevant service account (e.g. "compute") in the cloud). It will only have the scopes needed for FireStore (FireStoreScope).

This is just pure convenience.

do
  env <- defaultEnvironment
  result <- runFireStore env "myproject" someFireStoreAction

CRUD

listAllDocuments :: Text -> FireStore [Document] Source #

It only wants the collection name itself. In the language of the Google's resource identifiers, this will get into ("projects/" <> projectName <> "/databases/(default)/documents/" <> collectionName). Apparently, (default) is the actual real name of the only database you can have.

Other stuff

You can check out the docs for the additional types, as well as the lenses in the Types module: