server-generic-1.0.0: Auto-generate a server for your datatype

Safe HaskellNone

Server.Generic

Contents

Description

This library auto-generates API services for data types using Haskell's built-in support for generic programming. The best way to understand how this library works is to walk through a few examples.

For example, suppose that you define the following type:

 -- Example.hs

 {-# LANGUAGE DeriveGeneric #-}

 import Server.Generic

 data Example = Example { foo :: Int, bar :: Double }
     deriving (Generic)

 instance ParseRecord Example
 instance ToJSON      Example

 handler :: Example -> IO Example
 handler = return

 main :: IO ()
 main = serveJSON 8080 handler

Named fields translate to query parameters which you can provide in any order:

 $ stack build server-generic
 $ stack runghc Example.hs
 ...
 {in another terminal}
 $ curl 'localhost:8080/example?bar=2.5&foo=1'
 {"foo":1,"bar":2.5}

serveJSON performs the following steps:

  • automatically marshals the route into the Example data type * supplies the Example data type to the handler * converts the return value of the handler to JSON served back to the client

Let's write a more interesting handler that creates files:

 -- Create.hs
 
 {-# LANGUAGE DeriveGeneric #-}
 
 import Server.Generic
 
 data Create = Create { filepath :: FilePath, contents :: String }
     deriving (Generic)
 
 instance ParseRecord Create
 
 handler :: Create -> IO ()
 handler create = writeFile (filepath create) (contents create)
 
 main :: IO ()
 main = serveJSON 8080 handler

If we run that then it will create a file any time we hit the /create endpoint with the appropriate query parameters:

 $ curl 'localhost:8080/create?filepath=test.txt&contents=ABC'
 []
 $ cat test.txt
 ABC

The [] in the response is just how the aeson library encodes the empty () return value of the handler.

Unlabeled fields translate to path tokens in the route. For example, this type:

 -- Example.hs
 
 {-# LANGUAGE DeriveGeneric #-}
 
 import Server.Generic
 
 data Example = Example Int Double Text
     deriving (Generic)
 
 instance ParseRecord Example
 instance ToJSON      Example
 
 handler :: Example -> IO Example
 handler = return
 
 main :: IO ()
 main = serveJSON 8080 handler

... translates to a /example/:int/:double/:text route that captures the last three tokens as the fields of the Example type:

 $ curl 'localhost:8080/example/1/2.5/foo'
 [1,2.5,"foo"]

Also, unlabeled data types get converted to an array when rendered as JSON.

Certain types of fields are given special treatment, such as in this example:

 data Example = Example
     { list     :: [Int]
     , optional :: Maybe   Int
     , first    :: First   Int
     , last     :: Last    Int
     } deriving (Generic)

This gives the following behavior:

 $ curl 'localhost:8080/example?optional=1&list=1&list=2&first=1&first=2&last=1&last=2'
 {"list":[1,2],"first":1,"last":2,"optional":1}
 
 $ curl 'localhost:8080/example'
 {"list":[],"first":null,"last":null,"optional":null}

If a datatype has multiple constructors:

 data Example
     = Create { name :: Text, duration :: Maybe Int }
     | Kill   { name :: Text }
     deriving (Generic)

... then they will translate into multiple API endpoints:

 $ curl 'localhost:8080/create?name=foo&duration=60'
 {"tag":"Create","name":"foo","duration":60}
 $ curl 'localhost:8080/kill?name=foo'
 {"tag":"Kill","name":"foo"}

This library also provides out-of-the-box support for many existing types, like tuples and Either:

 {-# LANGUAGE DeriveGeneric #-}
 
 import Server.Generic
 
 handler :: Either Int Double -> IO (Either Int Double)
 handler = return
 
 main :: IO ()
 main = serveJSON 8080 handler
 $ curl 'localhost:8080/left/1'
 {"Left":1}
 $ curl 'localhost:8080/right/2.5'
 {"Right":2.5}
 handler :: (Int, Double) -> IO (Int, Double)
 handler = return
 $ curl 'localhost:8080/1/2.5'
 [1,2.5]

... and you can also just parse a single value:

 handler :: Int -> IO Int
 handler = return
 $ curl 'localhost:8080/1'
 1

However, there are some types that this library cannot generate sensible routes for, such as:

  • recursive types:
 data Example = Example { foo :: Example }
  • records whose fields are other records
 data Outer = Outer { foo :: Inner } deriving (Show, Generic)
 data Inner = Inner { bar :: Int   } deriving (Show, Generic)
  • record fields with nested Maybes or nested lists
 data Example = Example { foo :: Maybe (Maybe Int) }
 data Example = Example { foo :: [[Int]]           }

If you try to auto-generate a parser for these types you will get an error at compile time that will look something like this:

     No instance for (ParseFields TheTypeOfYourField)
       arising from a use of ‘Server.Generic.$gdmparseRecord’
     In the expression: Server.Generic.$gdmparseRecord
     In an equation for ‘parseRecord’:
         parseRecord = Server.Generic.$gdmparseRecord
     In the instance declaration for ‘ParseRecord TheTypeOfYourRecord’

Synopsis

Server

serveSource

Arguments

:: ParseRecord a 
=> Port

Port to listen on

-> (a -> IO Response)

Handler for parsed value

-> IO ()

Run the server

Simple server that listens on the given Port and runs the handler for each incoming connection

The value supplied to the handler is automatically parsed from the route

The request method is ignored

Failure to parse a value from the route results in a response with a 404 status code

serveJSON :: (ParseRecord a, ToJSON b) => Port -> (a -> IO b) -> IO ()Source

Like serve except the handler result is automatically encoded as JSON and served as the Response

serveOK :: ParseRecord a => Port -> (a -> IO ()) -> IO ()Source

Like serve except the Response is always "200 OK"

Parser

data Route Source

A list of path tokens which were originally separated by /s

Constructors

Route 

Fields

path :: [Text]
 
query :: [(ByteString, ByteString)]
 

newtype Parser a Source

A backtracking Route parser

Constructors

Parser 

Fields

unParser :: StateT Route [] a
 

class ParseRecord a whereSource

A class for types that can be parsed from path tokens or query parameters

This class has a default implementation for any type that implements Generic and you can derive Generic for many types by enabling the DeriveGeneric language extension

You can also use getOnly to create a ParseRecord instance from a ParseFields instance:

 instance ParseRecord MyType where
     parseRecord = fmap getOnly parseRecord

class ParseRecord a => ParseFields a whereSource

A class for all types that can be parsed from zero or more path tokens or query parameters

parseFields has a default implementation for any type that implements ParseField

Methods

parseFieldsSource

Arguments

:: Maybe Text

Field label (Nothing for path token, and Just for query param)

-> Parser a 

class ParseField a whereSource

A class for all record fields that can be parsed from exactly one path token or query parameter

parseField has a default implementation for any type that implements Read

Methods

parseFieldSource

Arguments

:: Maybe Text

Field label (Nothing for path token, and Just for query param)

-> Parser a 

parseListOfFieldSource

Arguments

:: Maybe Text

Field label

-> Parser [a] 

newtype Only a Source

A 1-tuple, used solely to translate ParseFields instances into ParseRecord instances

Constructors

Only a 

Instances

Show a => Show (Only a) 
Generic (Only a) 
ParseFields a => ParseRecord (Only a) 

getOnly :: Only a -> aSource

This is a convenience function that you can use if you want to create a ParseRecord instance that just defers to the ParseFields instance for the same type:

 instance ParseRecord MyType where
     parseRecord = fmap getOnly parseRecord

Re-exports

class Generic a

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Instances

Generic Bool 
Generic Char 
Generic Double 
Generic Float 
Generic Int 
Generic Ordering 
Generic () 
Generic IPRange 
Generic IP 
Generic IPv4 
Generic IPv6 
Generic Void 
Generic [a] 
Generic (Maybe a) 
Generic (AddrRange a) 
Generic (Min a) 
Generic (Max a) 
Generic (First a) 
Generic (Last a) 
Generic (WrappedMonoid m) 
Generic (Option a) 
Generic (NonEmpty a) 
Generic (Only a) 
Generic (Either a b) 
Generic (a, b) 
Generic (Arg a b) 
Generic (Proxy k s) 
Generic (a, b, c) 
Generic (Tagged k s b) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g) 

class ToJSON a

A type that can be converted to JSON.

An example type and instance:

{-# LANGUAGE OverloadedStrings #-}

data Coord = Coord { x :: Double, y :: Double }

instance ToJSON Coord where
   toJSON (Coord x y) = object ["x" .= x, "y" .= y]

Note the use of the OverloadedStrings language extension which enables Text values to be written as string literals.

Instead of manually writing your ToJSON instance, there are three options to do it automatically:

  • Data.Aeson.TH provides template-haskell functions which will derive an instance at compile-time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
  • Data.Aeson.Generic provides a generic toJSON function that accepts any type which is an instance of Data.
  • If your compiler has support for the DeriveGeneric and DefaultSignatures language extensions (GHC 7.2 and newer), toJSON will have a default generic implementation.

To use the latter option, simply add a deriving Generic clause to your datatype and declare a ToJSON instance for your datatype without giving a definition for toJSON.

For example the previous example can be simplified to just:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Coord = Coord { x :: Double, y :: Double } deriving Generic

instance ToJSON Coord

Note that, instead of using DefaultSignatures, it's also possible to parameterize the generic encoding using genericToJSON applied to your encoding/decoding Options:

 instance ToJSON Coord where
     toJSON = genericToJSON defaultOptions

Instances

ToJSON Bool 
ToJSON Char 
ToJSON Double 
ToJSON Float 
ToJSON Int 
ToJSON Int8 
ToJSON Int16 
ToJSON Int32 
ToJSON Int64 
ToJSON Integer 
ToJSON Word 
ToJSON Word8 
ToJSON Word16 
ToJSON Word32 
ToJSON Word64 
ToJSON () 
ToJSON Scientific 
ToJSON Number 
ToJSON Text 
ToJSON UTCTime 
ToJSON Value 
ToJSON DotNetTime 
ToJSON Text 
ToJSON IntSet 
ToJSON ZonedTime 
ToJSON [Char] 
ToJSON a => ToJSON [a] 
ToJSON (Ratio Integer) 
ToJSON a => ToJSON (Maybe a) 
HasResolution a => ToJSON (Fixed a) 
ToJSON a => ToJSON (Dual a) 
ToJSON a => ToJSON (First a) 
ToJSON a => ToJSON (Last a) 
ToJSON v => ToJSON (Tree v) 
ToJSON a => ToJSON (IntMap a) 
ToJSON a => ToJSON (Set a) 
ToJSON a => ToJSON (HashSet a) 
ToJSON a => ToJSON (Vector a) 
(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
(Storable a, ToJSON a) => ToJSON (Vector a) 
(Prim a, ToJSON a) => ToJSON (Vector a) 
(ToJSON a, ToJSON b) => ToJSON (Either a b) 
(ToJSON a, ToJSON b) => ToJSON (a, b) 
ToJSON v => ToJSON (HashMap String v) 
ToJSON v => ToJSON (HashMap Text v) 
ToJSON v => ToJSON (HashMap Text v) 
ToJSON v => ToJSON (Map String v) 
ToJSON v => ToJSON (Map Text v) 
ToJSON v => ToJSON (Map Text v) 
(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) 

newtype All

Boolean monoid under conjunction.

Constructors

All 

Fields

getAll :: Bool
 

newtype Any

Boolean monoid under disjunction.

Constructors

Any 

Fields

getAny :: Bool
 

newtype First a

Maybe monoid returning the leftmost non-Nothing value.

Constructors

First 

Fields

getFirst :: Maybe a
 

Instances

Eq a => Eq (First a) 
Ord a => Ord (First a) 
Read a => Read (First a) 
Show a => Show (First a) 
ToJSON a => ToJSON (First a) 
FromJSON a => FromJSON (First a) 
Monoid (First a) 
Semigroup (First a) 
ParseField a => ParseFields (First a) 
ParseField a => ParseRecord (First a) 

newtype Last a

Maybe monoid returning the rightmost non-Nothing value.

Constructors

Last 

Fields

getLast :: Maybe a
 

Instances

Eq a => Eq (Last a) 
Ord a => Ord (Last a) 
Read a => Read (Last a) 
Show a => Show (Last a) 
ToJSON a => ToJSON (Last a) 
FromJSON a => FromJSON (Last a) 
Monoid (Last a) 
Semigroup (Last a) 
ParseField a => ParseFields (Last a) 
ParseField a => ParseRecord (Last a) 

newtype Sum a

Monoid under addition.

Constructors

Sum 

Fields

getSum :: a
 

Instances

Bounded a => Bounded (Sum a) 
Eq a => Eq (Sum a) 
Ord a => Ord (Sum a) 
Read a => Read (Sum a) 
Show a => Show (Sum a) 
Num a => Monoid (Sum a) 
Num a => Semigroup (Sum a) 
(Num a, ParseField a) => ParseFields (Sum a) 
(Num a, ParseField a) => ParseRecord (Sum a) 

newtype Product a

Monoid under multiplication.

Constructors

Product 

Fields

getProduct :: a
 

Instances

Bounded a => Bounded (Product a) 
Eq a => Eq (Product a) 
Ord a => Ord (Product a) 
Read a => Read (Product a) 
Show a => Show (Product a) 
Num a => Monoid (Product a) 
Num a => Semigroup (Product a) 
(Num a, ParseField a) => ParseFields (Product a) 
(Num a, ParseField a) => ParseRecord (Product a)