Merge pull request #846 from phadej/pull-809-foreign-data
Pull 809 foreign data
This commit is contained in:
commit
d04bd290c5
4 changed files with 28 additions and 29 deletions
|
@ -8,6 +8,8 @@
|
|||
|
||||
* Add instances for `Description` and `Summary` combinators
|
||||
([#767](https://github.com/haskell-servant/servant/pull/767))
|
||||
* Derive Data for all types
|
||||
([#809](https://github.com/haskell-servant/servant/pull/809))
|
||||
|
||||
0.10.1
|
||||
------
|
||||
|
|
|
@ -47,21 +47,21 @@ library
|
|||
if impl(ghc >= 8.0)
|
||||
ghc-options: -Wno-redundant-constraints
|
||||
include-dirs: include
|
||||
default-extensions: CPP
|
||||
, ConstraintKinds
|
||||
default-extensions: ConstraintKinds
|
||||
, CPP
|
||||
, DataKinds
|
||||
, DeriveDataTypeable
|
||||
, FlexibleContexts
|
||||
, FlexibleInstances
|
||||
, GeneralizedNewtypeDeriving
|
||||
, MultiParamTypeClasses
|
||||
, OverloadedStrings
|
||||
, PolyKinds
|
||||
, ScopedTypeVariables
|
||||
, StandaloneDeriving
|
||||
, TemplateHaskell
|
||||
, TypeFamilies
|
||||
, TypeOperators
|
||||
, UndecidableInstances
|
||||
, OverloadedStrings
|
||||
, PolyKinds
|
||||
|
||||
|
||||
test-suite spec
|
||||
|
|
|
@ -9,12 +9,14 @@ module Servant.Foreign.Internal where
|
|||
|
||||
import Control.Lens (makePrisms, makeLenses, Getter, (&), (<>~), (%~),
|
||||
(.~))
|
||||
import Data.Data (Data)
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Data.Monoid
|
||||
#endif
|
||||
import Data.Proxy
|
||||
import Data.String
|
||||
import Data.Text
|
||||
import Data.Typeable (Typeable)
|
||||
import Data.Text.Encoding (decodeUtf8)
|
||||
import GHC.TypeLits
|
||||
import qualified Network.HTTP.Types as HTTP
|
||||
|
@ -24,21 +26,19 @@ import Servant.API.TypeLevel
|
|||
|
||||
|
||||
newtype FunctionName = FunctionName { unFunctionName :: [Text] }
|
||||
deriving (Show, Eq, Monoid)
|
||||
deriving (Data, Show, Eq, Monoid, Typeable)
|
||||
|
||||
makePrisms ''FunctionName
|
||||
|
||||
newtype PathSegment = PathSegment { unPathSegment :: Text }
|
||||
deriving (Show, Eq, IsString, Monoid)
|
||||
deriving (Data, Show, Eq, IsString, Monoid, Typeable)
|
||||
|
||||
makePrisms ''PathSegment
|
||||
|
||||
data Arg f = Arg
|
||||
{ _argName :: PathSegment
|
||||
, _argType :: f }
|
||||
|
||||
deriving instance Eq f => Eq (Arg f)
|
||||
deriving instance Show f => Show (Arg f)
|
||||
deriving (Data, Eq, Show, Typeable)
|
||||
|
||||
makeLenses ''Arg
|
||||
|
||||
|
@ -50,16 +50,12 @@ data SegmentType f
|
|||
-- ^ a static path segment. like "/foo"
|
||||
| Cap (Arg f)
|
||||
-- ^ a capture. like "/:userid"
|
||||
|
||||
deriving instance Eq f => Eq (SegmentType f)
|
||||
deriving instance Show f => Show (SegmentType f)
|
||||
deriving (Data, Eq, Show, Typeable)
|
||||
|
||||
makePrisms ''SegmentType
|
||||
|
||||
newtype Segment f = Segment { unSegment :: SegmentType f }
|
||||
|
||||
deriving instance Eq f => Eq (Segment f)
|
||||
deriving instance Show f => Show (Segment f)
|
||||
deriving (Data, Eq, Show, Typeable)
|
||||
|
||||
makePrisms ''Segment
|
||||
|
||||
|
@ -77,7 +73,7 @@ data ArgType
|
|||
= Normal
|
||||
| Flag
|
||||
| List
|
||||
deriving (Eq, Show)
|
||||
deriving (Data, Eq, Show, Typeable)
|
||||
|
||||
makePrisms ''ArgType
|
||||
|
||||
|
@ -85,9 +81,7 @@ data QueryArg f = QueryArg
|
|||
{ _queryArgName :: Arg f
|
||||
, _queryArgType :: ArgType
|
||||
}
|
||||
|
||||
deriving instance Eq f => Eq (QueryArg f)
|
||||
deriving instance Show f => Show (QueryArg f)
|
||||
deriving (Data, Eq, Show, Typeable)
|
||||
|
||||
makeLenses ''QueryArg
|
||||
|
||||
|
@ -97,9 +91,7 @@ data HeaderArg f = HeaderArg
|
|||
{ _headerArg :: Arg f
|
||||
, _headerPattern :: Text
|
||||
}
|
||||
|
||||
deriving instance Eq f => Eq (HeaderArg f)
|
||||
deriving instance Show f => Show (HeaderArg f)
|
||||
deriving (Data, Eq, Show, Typeable)
|
||||
|
||||
makeLenses ''HeaderArg
|
||||
|
||||
|
@ -109,9 +101,7 @@ data Url f = Url
|
|||
{ _path :: Path f
|
||||
, _queryStr :: [QueryArg f]
|
||||
}
|
||||
|
||||
deriving instance Eq f => Eq (Url f)
|
||||
deriving instance Show f => Show (Url f)
|
||||
deriving (Data, Eq, Show, Typeable)
|
||||
|
||||
defUrl :: Url f
|
||||
defUrl = Url [] []
|
||||
|
@ -126,9 +116,7 @@ data Req f = Req
|
|||
, _reqReturnType :: Maybe f
|
||||
, _reqFuncName :: FunctionName
|
||||
}
|
||||
|
||||
deriving instance Eq f => Eq (Req f)
|
||||
deriving instance Show f => Show (Req f)
|
||||
deriving (Data, Eq, Show, Typeable)
|
||||
|
||||
makeLenses ''Req
|
||||
|
||||
|
|
|
@ -21,6 +21,15 @@
|
|||
|
||||
### Other changes
|
||||
|
||||
- *servant-foreign* Derive `Data` for all types
|
||||
([#809](https://github.com/haskell-servant/servant/pull/809))
|
||||
- *servant-docs* Add authentication lenses
|
||||
([#787](https://github.com/haskell-servant/servant/pull/787))
|
||||
- *servant-docs* Generated markdown improvements
|
||||
([#813](https://github.com/haskell-servant/servant/pull/787)
|
||||
[#767](https://github.com/haskell-servant/servant/pull/767)
|
||||
[#790](https://github.com/haskell-servant/servant/pull/790)
|
||||
[#788](https://github.com/haskell-servant/servant/pull/788))
|
||||
- Allow newest dependencies
|
||||
([#772](https://github.com/haskell-servant/servant/pull/772)
|
||||
[#842](https://github.com/haskell-servant/servant/pull/842))
|
||||
|
|
Loading…
Reference in a new issue