Skip to content

Commit

Permalink
Merge pull request #26 from GetShopTV/docs-#20
Browse files Browse the repository at this point in the history
Documentation
  • Loading branch information
fizruk committed Dec 20, 2015
2 parents a6ac15f + fef1895 commit 5da3f8e
Show file tree
Hide file tree
Showing 7 changed files with 267 additions and 14 deletions.
29 changes: 29 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -4,3 +4,32 @@
[![Build Status](https://travis-ci.org/GetShopTV/swagger2.svg?branch=master)](https://travis-ci.org/GetShopTV/swagger2)

Swagger 2.0 data model.

The original Swagger 2.0 specification is available at http://swagger.io/specification/.

## Usage

This library is inteded to be used for decoding and encoding Swagger 2.0 API specifications as well as manipulating them.

Please refer to [haddock documentation](http://hackage.haskell.org/package/swagger2).

Some examples can be found in [`examples/` directory](/examples).

## Trying out

All generated swagger specifications can be interactively viewed on [Swagger Editor](http://editor.swagger.io/).

Ready-to-use specification can be served as JSON and interactive API documentation
can be displayed using [Swagger UI](https://github.com/swagger-api/swagger-ui).

Many Swagger tools, including server and client code generation for many languages, can be found on
[Swagger's Tools and Integrations page](http://swagger.io/open-source-integrations/).

## Contributing

We are happy to receive bug reports, fixes, documentation enhancements, and other improvements.

Please report bugs via the [github issue tracker](https://github.com/GetShopTV/swagger2/issues).

*GetShopTV Team*

70 changes: 70 additions & 0 deletions examples/hackage.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,70 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where

import Control.Lens
import Data.Aeson
import Data.Proxy
import Data.Text (Text)
import GHC.Generics

import Data.Swagger
import Data.Swagger.Declare
import Data.Swagger.Lens

type Username = Text

data UserSummary = UserSummary
{ summaryUsername :: Username
, summaryUserid :: Int
} deriving (Generic, ToSchema)

type Group = Text

data UserDetailed = UserDetailed
{ username :: Username
, userid :: Int
, groups :: [Group]
} deriving (Generic, ToSchema)

newtype Package = Package { packageName :: Text }
deriving (Generic, ToSchema)

hackageSwagger :: Swagger
hackageSwagger = spec & definitions .~ defs
where
(defs, spec) = runDeclare declareHackageSwagger mempty

declareHackageSwagger :: Declare Definitions Swagger
declareHackageSwagger = do
let usernameParamSchema = toParamSchema (Proxy :: Proxy Username)
userSummarySchemaRef <- declareSchemaRef (Proxy :: Proxy UserSummary)
userDetailedSchemaRef <- declareSchemaRef (Proxy :: Proxy UserDetailed)
packagesSchemaRef <- declareSchemaRef (Proxy :: Proxy [Package])
return $ mempty
& paths.pathsMap .~
[ ("/users", mempty & pathItemGet ?~ (mempty
& operationProduces ?~ MimeList ["application/json"]
& operationResponses .~ (mempty
& responsesResponses . at 200 ?~ Inline (mempty & responseSchema ?~ userSummarySchemaRef))))
, ("/user/{username}", mempty & pathItemGet ?~ (mempty
& operationProduces ?~ MimeList ["application/json"]
& operationParameters .~ [ Inline $ mempty
& paramName .~ "username"
& paramRequired ?~ True
& paramSchema .~ ParamOther (mempty
& paramOtherSchemaIn .~ ParamPath
& paramOtherSchemaParamSchema .~ usernameParamSchema) ]
& operationResponses .~ (mempty
& responsesResponses . at 200 ?~ Inline (mempty & responseSchema ?~ userDetailedSchemaRef))))
, ("/packages", mempty & pathItemGet ?~ (mempty
& operationProduces ?~ MimeList ["application/json"]
& operationResponses .~ (mempty
& responsesResponses . at 200 ?~ Inline (mempty & responseSchema ?~ packagesSchemaRef))))
]

main :: IO ()
main = putStrLn . read . show . encode $ hackageSwagger

154 changes: 141 additions & 13 deletions src/Data/Swagger.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,20 @@
-- and Swagger-Codegen to generate clients in various languages.
-- Additional utilities can also take advantage of the resulting files, such as testing tools.
module Data.Swagger (
-- * How to use this library
-- $howto

-- ** @'Monoid'@ instances
-- $monoids

-- ** Lenses and prisms
-- $lens

-- ** Schema specification
-- $schema

-- * Re-exports
module Data.Swagger.Lens,
module Data.Swagger.ParamSchema,
module Data.Swagger.Schema,

Expand All @@ -14,25 +28,25 @@ module Data.Swagger (
Host(..),
Scheme(..),

-- * Info types
-- ** Info types
Info(..),
Contact(..),
License(..),

-- * Paths
-- ** Paths
Paths(..),
PathItem(..),

-- * Operations
-- ** Operations
Tag(..),
Operation(..),

-- * Types and formats
-- ** Types and formats
SwaggerType(..),
Format,
CollectionFormat(..),

-- * Parameters
-- ** Parameters
Param(..),
ParamAnySchema(..),
ParamOtherSchema(..),
Expand All @@ -42,45 +56,159 @@ module Data.Swagger (
Header(..),
Example(..),

-- * Schemas
-- ** Schemas
ParamSchema(..),
Schema(..),
SwaggerItems(..),
Xml(..),

-- * Responses
-- ** Responses
Responses(..),
Response(..),

-- * Security
-- ** Security
SecurityScheme(..),
SecuritySchemeType(..),
SecurityRequirement(..),

-- ** API key
-- *** API key
ApiKeyParams(..),
ApiKeyLocation(..),

-- ** OAuth2
-- *** OAuth2
OAuth2Params(..),
OAuth2Flow(..),
AuthorizationURL,
TokenURL,

-- * External documentation
-- ** External documentation
ExternalDocs(..),

-- * References
-- ** References
Reference(..),
Referenced(..),

-- * Miscellaneous
-- ** Miscellaneous
MimeList(..),
URL(..),
) where

import Data.Swagger.Lens
import Data.Swagger.ParamSchema
import Data.Swagger.Schema

import Data.Swagger.Internal

-- $setup
-- >>> import Control.Lens
-- >>> import Data.Aeson
-- >>> import Data.Monoid
-- >>> import Data.Proxy
-- >>> import GHC.Generics
-- >>> :set -XDeriveGeneric
-- >>> :set -XOverloadedStrings
-- >>> :set -XOverloadedLists
-- >>> :set -fno-warn-missing-methods

-- $howto
--
-- This section explains how to use this library to work with Swagger specification.

-- $monoids
--
-- Virtually all types representing Swagger specification have @'Monoid'@ instances.
-- The @'Monoid'@ type class provides two methods — @'mempty'@ and @'mappend'@.
--
-- In this library you can use @'mempty'@ for a default/empty value. For instance:
--
-- >>> encode (mempty :: Swagger)
-- "{\"swagger\":\"2.0\",\"info\":{\"version\":\"\",\"title\":\"\"}}"
--
-- As you can see some spec properties (e.g. @"version"@) are there even when the spec is empty.
-- That is because these properties are actually required ones.
--
-- You /should/ always override the default (empty) value for these properties,
-- although it is not strictly necessary:
--
-- >>> encode mempty { _infoTitle = "Todo API", _infoVersion = "1.0" }
-- "{\"version\":\"1.0\",\"title\":\"Todo API\"}"
--
-- You can merge two values using @'mappend'@ or its infix version @('<>')@:
--
-- >>> encode $ mempty { _infoTitle = "Todo API" } <> mempty { _infoVersion = "1.0" }
-- "{\"version\":\"1.0\",\"title\":\"Todo API\"}"
--
-- This can be useful for combining specifications of endpoints into a whole API specification:
--
-- @
-- \-\- /account subAPI specification
-- accountAPI :: Swagger
--
-- \-\- /task subAPI specification
-- taskAPI :: Swagger
--
-- \-\- while API specification is just a combination
-- \-\- of subAPIs' specifications
-- api :: Swagger
-- api = accountAPI <> taskAPI
-- @

-- $lens
--
-- Since @'Swagger'@ has a fairly complex structure, lenses and prisms are used
-- to modify this structure. In combination with @'Monoid'@ instances, lenses
-- also make it fairly simple to construct/modify any part of the specification:
--
-- >>> :{
-- encode $ mempty & pathsMap .~
-- [ ("/user", mempty & pathItemGet ?~ (mempty
-- & operationProduces ?~ MimeList ["application/json"]
-- & operationResponses .~ (mempty
-- & responsesResponses . at 200 ?~ Inline (mempty & responseSchema ?~ Ref (Reference "#/definitions/User")))))]
-- :}
-- "{\"/user\":{\"get\":{\"responses\":{\"200\":{\"schema\":{\"$ref\":\"#/definitions/#/definitions/User\"},\"description\":\"\"}},\"produces\":[\"application/json\"]}}}"
--
-- Since @'ParamSchema'@ is basically the /base schema specification/, a special
-- @'HasParamSchema'@ class has been introduced to generalize @'ParamSchema'@ lenses
-- and allow them to be used by any type that has a @'ParamSchema'@:
--
-- >>> :{
-- encode $ mempty
-- & schemaTitle ?~ "Email"
-- & schemaType .~ SwaggerString
-- & schemaFormat ?~ "email"
-- :}
-- "{\"format\":\"email\",\"title\":\"Email\",\"type\":\"string\"}"

-- $schema
--
-- This library provides two classes for schema encoding.
-- Both these classes provide means to encode _types_ as Swagger _schemas_.
--
-- @'ToParamSchema'@ is intended to be used for primitive API endpoint parameters,
-- such as query parameters, headers and URL path pieces.
-- Its corresponding value-encoding class is @'ToHttpApiData'@ (from @http-api-data@ package).
--
-- @'ToSchema'@ is used for request and response bodies and mostly differ from
-- primitive parameters by allowing objects/mappings in addition to primitive types and arrays.
-- Its corresponding value-encoding class is @'ToJSON'@ (from @aeson@ package).
--
-- While lenses and prisms make it easy to define schemas, it might be that you don't need to:
-- @'ToSchema'@ and @'ToParamSchema'@ classes both have default @'Generic'@-based implementations!
--
-- @'ToSchema'@ default implementation is also aligned with @'ToJSON'@ default implementation with
-- the only difference being for sum encoding. @'ToJSON'@ defaults sum encoding to @'defaultTaggedObject'@,
-- while @'ToSchema'@ defaults to something which corresponds to @'ObjectWithSingleField'@. This is due to
-- @'defaultTaggedObject'@ behavior being hard to specify in Swagger.
--
-- Here's an example showing @'ToJSON'@–@'ToSchema'@ correspondance:
--
-- >>> data Person = Person { name :: String, age :: Integer } deriving Generic
-- >>> instance ToJSON Person
-- >>> instance ToSchema Person
-- >>> encode (Person "David" 28)
-- "{\"age\":28,\"name\":\"David\"}"
-- >>> encode $ toSchema (Proxy :: Proxy Person)
-- "{\"required\":[\"name\",\"age\"],\"type\":\"object\",\"properties\":{\"age\":{\"type\":\"integer\"},\"name\":{\"type\":\"string\"}}}"
--

13 changes: 13 additions & 0 deletions src/Data/Swagger/Declare.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,12 +72,18 @@ instance (Monad m, Monoid d) => MonadDeclare d (DeclareT d m) where
looks :: MonadDeclare d m => (d -> a) -> m a
looks f = f <$> look

-- | Evaluate @'DeclareT' d m a@ computation,
-- ignoring new output @d@.
evalDeclareT :: Monad m => DeclareT d m a -> d -> m a
evalDeclareT (DeclareT f) d = snd `liftM` f d

-- | Execute @'DeclateT' d m a@ computation,
-- ignoring result and only producing new output @d@.
execDeclareT :: Monad m => DeclareT d m a -> d -> m d
execDeclareT (DeclareT f) d = fst `liftM` f d

-- | Evaluate @'DeclareT' d m a@ computation,
-- starting with empty output history.
undeclareT :: (Monad m, Monoid d) => DeclareT d m a -> m a
undeclareT = flip evalDeclareT mempty

Expand All @@ -91,15 +97,22 @@ undeclareT = flip evalDeclareT mempty
-- * a writer monad with the extra ability to read all previous output.
type Declare d = DeclareT d Identity

-- | Run @'Declare' d a@ computation with output history @d@,
-- producing result @a@ and new output @d@.
runDeclare :: Declare d a -> d -> (d, a)
runDeclare m = runIdentity . runDeclareT m

-- | Evaluate @'Declare' d a@ computation, ignoring output @d@.
evalDeclare :: Declare d a -> d -> a
evalDeclare m = runIdentity . evalDeclareT m

-- | Execute @'Declate' d a@ computation, ignoring result and only
-- producing output @d@.
execDeclare :: Declare d a -> d -> d
execDeclare m = runIdentity . execDeclareT m

-- | Evaluate @'DeclareT' d m a@ computation,
-- starting with empty output history.
undeclare :: Monoid d => Declare d a -> a
undeclare = runIdentity . undeclareT

11 changes: 11 additions & 0 deletions src/Data/Swagger/Internal/ParamSchema.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,9 @@ import Data.Swagger.SchemaOptions
-- @
class ToParamSchema a where
-- | Convert a type into a plain parameter schema.
--
-- >>> encode $ toParamSchema (Proxy :: Proxy Integer)
-- "{\"type\":\"integer\"}"
toParamSchema :: proxy a -> ParamSchema t
default toParamSchema :: (Generic a, GToParamSchema (Rep a)) => proxy a -> ParamSchema t
toParamSchema = genericToParamSchema defaultSchemaOptions
Expand All @@ -89,6 +92,9 @@ instance ToParamSchema Word32 where toParamSchema = toParamSchemaBoundedIntegral
instance ToParamSchema Word64 where toParamSchema = toParamSchemaBoundedIntegral

-- | Default plain schema for @'Bounded'@, @'Integral'@ types.
--
-- >>> encode $ toParamSchemaBoundedIntegral (Proxy :: Proxy Int8)
-- "{\"maximum\":127,\"minimum\":-128,\"type\":\"integer\"}"
toParamSchemaBoundedIntegral :: forall proxy a t. (Bounded a, Integral a) => proxy a -> ParamSchema t
toParamSchemaBoundedIntegral _ = mempty
& schemaType .~ SwaggerInteger
Expand Down Expand Up @@ -166,6 +172,11 @@ instance ToParamSchema () where
& schemaEnum ?~ ["_"]

-- | A configurable generic @'ParamSchema'@ creator.
--
-- >>> :set -XDeriveGeneric
-- >>> data Color = Red | Blue deriving Generic
-- >>> encode $ genericToParamSchema defaultSchemaOptions (Proxy :: Proxy Color)
-- "{\"type\":\"string\",\"enum\":[\"Red\",\"Blue\"]}"
genericToParamSchema :: forall proxy a t. (Generic a, GToParamSchema (Rep a)) => SchemaOptions -> proxy a -> ParamSchema t
genericToParamSchema opts _ = gtoParamSchema opts (Proxy :: Proxy (Rep a)) mempty

Expand Down
Loading

0 comments on commit 5da3f8e

Please sign in to comment.