servant-activeresource-0.1.0.0: Servant endpoints compatible with Rails's ActiveResources
Copyright(C) 2024 Bellroy Pty Ltd
LicenseBSD-3-Clause
MaintainerBellroy Tech Team <haskell@bellroy.com>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Servant.ActiveResource

Description

Types and helpers for defining Servant routes compatible with Rails' ActiveResource.

{-# LANGUAGE TemplateHaskell #-}

import qualified Servant.ActiveResource as AR

newtype MyResourceId = MyResourceId Int
-- Type for new values or updates to existing values. Usually
-- missing an id field.
data MyResource = MyResource {...}
-- Like MyResource, but returned from the database.
data MyStoredResource = MyStoredResource {...}

-- The exact monad used will depend on your program. Here, we just assume
-- Handler from package servant-server.
instance AR.Resource MyResourceId Handler where
  type ResourceData MyResourceId = MyResource
  type StoredResourceData MyResourceId = MyStoredResource

  -- These form the implementation of your API.
  listResources = ...
  createResource = ...
  readResource = ...
  upsertResource = ...
  deleteResource = ...

-- Record of routes, which can be spliced into a top-level handler
-- via NamedRoutes.
routes :: AR.ResourceRoutes MyResourceId (AsServerT Handler)
routes = $(AR.makeResourceServerT [t|MyResourceId|])
Synopsis

Documentation

class Monad m => Resource id m where Source #

A Resource instance says that the type id is the primary key for some abstract resource, and that the collection of such resources can be manipulated with CRUDL actions inside a Monad m.

Associated Types

type ResourceData id :: Type Source #

The type used to represent new records or updates to existing records. Typically, this is missing an id field.

type StoredResourceData id :: Type Source #

The type used to represent existing records.

data NotFoundError Source #

Constructors

NotFoundError 

Instances

Instances details
ToJSON NotFoundError Source # 
Instance details

Defined in Servant.ActiveResource

Bounded NotFoundError Source # 
Instance details

Defined in Servant.ActiveResource

Generic NotFoundError Source # 
Instance details

Defined in Servant.ActiveResource

Associated Types

type Rep NotFoundError :: Type -> Type #

Show NotFoundError Source # 
Instance details

Defined in Servant.ActiveResource

Eq NotFoundError Source # 
Instance details

Defined in Servant.ActiveResource

Ord NotFoundError Source # 
Instance details

Defined in Servant.ActiveResource

type Rep NotFoundError Source # 
Instance details

Defined in Servant.ActiveResource

type Rep NotFoundError = D1 ('MetaData "NotFoundError" "Servant.ActiveResource" "servant-activeresource-0.1.0.0-CUkqHZK6xQe9X5O430Iewn" 'False) (C1 ('MetaCons "NotFoundError" 'PrefixI 'False) (U1 :: Type -> Type))

newtype ValidationError Source #

ActiveResource errors are a map where the keys name fields from the payload, and the values are lists of errors at that field.

The ToJSON instance wraps the whole thing in an { "errors": ... } object, to match ActiveResource's expectations.

Constructors

ValidationError (Map Text [Text]) 

Instances

Instances details
ToJSON ValidationError Source # 
Instance details

Defined in Servant.ActiveResource

Generic ValidationError Source # 
Instance details

Defined in Servant.ActiveResource

Associated Types

type Rep ValidationError :: Type -> Type #

Show ValidationError Source # 
Instance details

Defined in Servant.ActiveResource

Eq ValidationError Source # 
Instance details

Defined in Servant.ActiveResource

type Rep ValidationError Source # 
Instance details

Defined in Servant.ActiveResource

type Rep ValidationError = D1 ('MetaData "ValidationError" "Servant.ActiveResource" "servant-activeresource-0.1.0.0-CUkqHZK6xQe9X5O430Iewn" 'True) (C1 ('MetaCons "ValidationError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text [Text]))))

data CreatedUpdated Source #

Constructors

Created 
Updated 

Instances

Instances details
Bounded CreatedUpdated Source # 
Instance details

Defined in Servant.ActiveResource

Generic CreatedUpdated Source # 
Instance details

Defined in Servant.ActiveResource

Associated Types

type Rep CreatedUpdated :: Type -> Type #

Show CreatedUpdated Source # 
Instance details

Defined in Servant.ActiveResource

Eq CreatedUpdated Source # 
Instance details

Defined in Servant.ActiveResource

Ord CreatedUpdated Source # 
Instance details

Defined in Servant.ActiveResource

type Rep CreatedUpdated Source # 
Instance details

Defined in Servant.ActiveResource

type Rep CreatedUpdated = D1 ('MetaData "CreatedUpdated" "Servant.ActiveResource" "servant-activeresource-0.1.0.0-CUkqHZK6xQe9X5O430Iewn" 'False) (C1 ('MetaCons "Created" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Updated" 'PrefixI 'False) (U1 :: Type -> Type))

data ResourceRoutes (id :: Type) mode Source #

The CRUDL routes required by an ActiveResource API, using Servant's generic record-based routing. Once you have a Resource instance, use makeResourceServerT to generate a server that fills out this structure.

NOTE: If the alternate syntax for :- gets merged, we intend to adopt it; it's easier to read.

Instances

Instances details
Generic (ResourceRoutes id mode) Source # 
Instance details

Defined in Servant.ActiveResource

Associated Types

type Rep (ResourceRoutes id mode) :: Type -> Type #

Methods

from :: ResourceRoutes id mode -> Rep (ResourceRoutes id mode) x #

to :: Rep (ResourceRoutes id mode) x -> ResourceRoutes id mode #

type Rep (ResourceRoutes id mode) Source # 
Instance details

Defined in Servant.ActiveResource

type Rep (ResourceRoutes id mode) = D1 ('MetaData "ResourceRoutes" "Servant.ActiveResource" "servant-activeresource-0.1.0.0-CUkqHZK6xQe9X5O430Iewn" 'False) (C1 ('MetaCons "ResourceRoutes" 'PrefixI 'True) ((S1 ('MetaSel ('Just "listRoute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mode :- UVerb 'GET '[JSON] '[WithStatus 200 [StoredResourceData id]])) :*: S1 ('MetaSel ('Just "createRoute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mode :- (ReqBody '[JSON] (ResourceData id) :> UVerb 'POST '[JSON] '[WithStatus 422 ValidationError, WithStatus 201 (StoredResourceData id)])))) :*: (S1 ('MetaSel ('Just "readRoute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mode :- (Capture "id" id :> UVerb 'GET '[JSON] '[WithStatus 404 NotFoundError, WithStatus 200 (StoredResourceData id)]))) :*: (S1 ('MetaSel ('Just "upsertRoute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mode :- (Capture "id" id :> (ReqBody '[JSON] (ResourceData id) :> UVerb 'PUT '[JSON] '[WithStatus 422 ValidationError, WithStatus 200 (StoredResourceData id), WithStatus 201 (StoredResourceData id)])))) :*: S1 ('MetaSel ('Just "deleteRoute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mode :- (Capture "id" id :> UVerb 'DELETE '[JSON] '[WithStatus 404 NotFoundError, WithStatus 204 NoContent])))))))

makeResourceServerT :: TypeQ -> ExpQ Source #

Given an instance of 'ResourceId ty', plumb through its operations to build a ResourceRoutes. GHC's type checker isn't smart enough to reason through the generated code if it's given a polymorphic type, so we have to use TH.

If m ~ ResourceMonad ty, then you can call it like this:

myResourceServer :: ResourceRoutes ty (AsServerT m)
myResourceServer = $(makeResourceServerT [t|ty|])

The generated code will need -XDataKinds, -XLambdaCase, and -XTypeApplications.

You can then serve it using the functions in Servant.Server.Generic.

errorFormatters :: ErrorFormatters Source #

This is a custom error formatter for parse errors, which runs when Servant fails to deserialise a request parameter (i.e., before endpoint code runs).

Technically, such a parse failure should return HTTP 400 Bad Request, but ActiveResource shows no useful information in such cases. This formatter therefore gives up technical purity in favour of reasonable error messages.

You can use it with servant-server's various ...WithContext functions:

-- Supposing our ResourceMonad is servant-server's Handler type, so we
-- can pass id as the natural transformation parameter:
genericServeTWithContext id myResourceServer (errorFormatters :. EmptyContext)