servant-foreign: Derive Data for all types
This commit is contained in:
parent
b7b6ce7f40
commit
335e30be74
2 changed files with 12 additions and 25 deletions
|
@ -55,7 +55,6 @@ library
|
||||||
, GeneralizedNewtypeDeriving
|
, GeneralizedNewtypeDeriving
|
||||||
, MultiParamTypeClasses
|
, MultiParamTypeClasses
|
||||||
, ScopedTypeVariables
|
, ScopedTypeVariables
|
||||||
, StandaloneDeriving
|
|
||||||
, TemplateHaskell
|
, TemplateHaskell
|
||||||
, TypeFamilies
|
, TypeFamilies
|
||||||
, TypeOperators
|
, TypeOperators
|
||||||
|
|
|
@ -1,4 +1,5 @@
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
{-# LANGUAGE DeriveDataTypeable #-}
|
||||||
#if !MIN_VERSION_base(4,8,0)
|
#if !MIN_VERSION_base(4,8,0)
|
||||||
{-# LANGUAGE NullaryTypeClasses #-}
|
{-# LANGUAGE NullaryTypeClasses #-}
|
||||||
#endif
|
#endif
|
||||||
|
@ -9,6 +10,7 @@ module Servant.Foreign.Internal where
|
||||||
|
|
||||||
import Control.Lens (makePrisms, makeLenses, Getter, (&), (<>~), (%~),
|
import Control.Lens (makePrisms, makeLenses, Getter, (&), (<>~), (%~),
|
||||||
(.~))
|
(.~))
|
||||||
|
import Data.Data
|
||||||
#if !MIN_VERSION_base(4,8,0)
|
#if !MIN_VERSION_base(4,8,0)
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
#endif
|
#endif
|
||||||
|
@ -24,21 +26,19 @@ import Servant.API.TypeLevel
|
||||||
|
|
||||||
|
|
||||||
newtype FunctionName = FunctionName { unFunctionName :: [Text] }
|
newtype FunctionName = FunctionName { unFunctionName :: [Text] }
|
||||||
deriving (Show, Eq, Monoid)
|
deriving (Data, Show, Eq, Monoid)
|
||||||
|
|
||||||
makePrisms ''FunctionName
|
makePrisms ''FunctionName
|
||||||
|
|
||||||
newtype PathSegment = PathSegment { unPathSegment :: Text }
|
newtype PathSegment = PathSegment { unPathSegment :: Text }
|
||||||
deriving (Show, Eq, IsString, Monoid)
|
deriving (Data, Show, Eq, IsString, Monoid)
|
||||||
|
|
||||||
makePrisms ''PathSegment
|
makePrisms ''PathSegment
|
||||||
|
|
||||||
data Arg f = Arg
|
data Arg f = Arg
|
||||||
{ _argName :: PathSegment
|
{ _argName :: PathSegment
|
||||||
, _argType :: f }
|
, _argType :: f }
|
||||||
|
deriving (Data, Eq, Show)
|
||||||
deriving instance Eq f => Eq (Arg f)
|
|
||||||
deriving instance Show f => Show (Arg f)
|
|
||||||
|
|
||||||
makeLenses ''Arg
|
makeLenses ''Arg
|
||||||
|
|
||||||
|
@ -50,16 +50,12 @@ data SegmentType f
|
||||||
-- ^ a static path segment. like "/foo"
|
-- ^ a static path segment. like "/foo"
|
||||||
| Cap (Arg f)
|
| Cap (Arg f)
|
||||||
-- ^ a capture. like "/:userid"
|
-- ^ a capture. like "/:userid"
|
||||||
|
deriving (Data, Eq, Show)
|
||||||
deriving instance Eq f => Eq (SegmentType f)
|
|
||||||
deriving instance Show f => Show (SegmentType f)
|
|
||||||
|
|
||||||
makePrisms ''SegmentType
|
makePrisms ''SegmentType
|
||||||
|
|
||||||
newtype Segment f = Segment { unSegment :: SegmentType f }
|
newtype Segment f = Segment { unSegment :: SegmentType f }
|
||||||
|
deriving (Data, Eq, Show)
|
||||||
deriving instance Eq f => Eq (Segment f)
|
|
||||||
deriving instance Show f => Show (Segment f)
|
|
||||||
|
|
||||||
makePrisms ''Segment
|
makePrisms ''Segment
|
||||||
|
|
||||||
|
@ -77,7 +73,7 @@ data ArgType
|
||||||
= Normal
|
= Normal
|
||||||
| Flag
|
| Flag
|
||||||
| List
|
| List
|
||||||
deriving (Eq, Show)
|
deriving (Data, Eq, Show)
|
||||||
|
|
||||||
makePrisms ''ArgType
|
makePrisms ''ArgType
|
||||||
|
|
||||||
|
@ -85,9 +81,7 @@ data QueryArg f = QueryArg
|
||||||
{ _queryArgName :: Arg f
|
{ _queryArgName :: Arg f
|
||||||
, _queryArgType :: ArgType
|
, _queryArgType :: ArgType
|
||||||
}
|
}
|
||||||
|
deriving (Data, Eq, Show)
|
||||||
deriving instance Eq f => Eq (QueryArg f)
|
|
||||||
deriving instance Show f => Show (QueryArg f)
|
|
||||||
|
|
||||||
makeLenses ''QueryArg
|
makeLenses ''QueryArg
|
||||||
|
|
||||||
|
@ -97,9 +91,7 @@ data HeaderArg f = HeaderArg
|
||||||
{ _headerArg :: Arg f
|
{ _headerArg :: Arg f
|
||||||
, _headerPattern :: Text
|
, _headerPattern :: Text
|
||||||
}
|
}
|
||||||
|
deriving (Data, Eq, Show)
|
||||||
deriving instance Eq f => Eq (HeaderArg f)
|
|
||||||
deriving instance Show f => Show (HeaderArg f)
|
|
||||||
|
|
||||||
makeLenses ''HeaderArg
|
makeLenses ''HeaderArg
|
||||||
|
|
||||||
|
@ -109,9 +101,7 @@ data Url f = Url
|
||||||
{ _path :: Path f
|
{ _path :: Path f
|
||||||
, _queryStr :: [QueryArg f]
|
, _queryStr :: [QueryArg f]
|
||||||
}
|
}
|
||||||
|
deriving (Data, Eq, Show)
|
||||||
deriving instance Eq f => Eq (Url f)
|
|
||||||
deriving instance Show f => Show (Url f)
|
|
||||||
|
|
||||||
defUrl :: Url f
|
defUrl :: Url f
|
||||||
defUrl = Url [] []
|
defUrl = Url [] []
|
||||||
|
@ -126,9 +116,7 @@ data Req f = Req
|
||||||
, _reqReturnType :: Maybe f
|
, _reqReturnType :: Maybe f
|
||||||
, _reqFuncName :: FunctionName
|
, _reqFuncName :: FunctionName
|
||||||
}
|
}
|
||||||
|
deriving (Data, Eq, Show)
|
||||||
deriving instance Eq f => Eq (Req f)
|
|
||||||
deriving instance Show f => Show (Req f)
|
|
||||||
|
|
||||||
makeLenses ''Req
|
makeLenses ''Req
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue