servant-foreign: Derive Data for all types

This commit is contained in:
Ollie Charles 2017-09-20 13:34:08 +01:00 committed by Oleg Grenrus
parent b7b6ce7f40
commit 335e30be74
2 changed files with 12 additions and 25 deletions

View File

@ -55,7 +55,6 @@ library
, GeneralizedNewtypeDeriving
, MultiParamTypeClasses
, ScopedTypeVariables
, StandaloneDeriving
, TemplateHaskell
, TypeFamilies
, TypeOperators

View File

@ -1,4 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
#if !MIN_VERSION_base(4,8,0)
{-# LANGUAGE NullaryTypeClasses #-}
#endif
@ -9,6 +10,7 @@ module Servant.Foreign.Internal where
import Control.Lens (makePrisms, makeLenses, Getter, (&), (<>~), (%~),
(.~))
import Data.Data
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid
#endif
@ -24,21 +26,19 @@ import Servant.API.TypeLevel
newtype FunctionName = FunctionName { unFunctionName :: [Text] }
deriving (Show, Eq, Monoid)
deriving (Data, Show, Eq, Monoid)
makePrisms ''FunctionName
newtype PathSegment = PathSegment { unPathSegment :: Text }
deriving (Show, Eq, IsString, Monoid)
deriving (Data, Show, Eq, IsString, Monoid)
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)
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)
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)
makePrisms ''Segment
@ -77,7 +73,7 @@ data ArgType
= Normal
| Flag
| List
deriving (Eq, Show)
deriving (Data, Eq, Show)
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)
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)
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)
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)
makeLenses ''Req