module Rest.Dictionary.Combinators
(
stringI
, xmlTextI
, fileI
, readI
, xmlI
, rawXmlI
, jsonI
, rawJsonI
, rawJsonAndXmlI
, stringO
, fileO
, xmlO
, rawXmlO
, jsonO
, rawJsonO
, rawJsonAndXmlO
, multipartO
, jsonE
, xmlE
, xmlJsonI
, xmlJsonO
, xmlJsonE
, xmlJson
, mkHeader
, addHeader
, mkPar
, addPar
, someI
, someO
, someE
) where
import Prelude hiding (id, (.))
import Control.Category
import Data.Aeson
import Data.ByteString.Lazy (ByteString)
import Data.JSON.Schema
import Data.Text.Lazy (Text)
import Data.Typeable
import Network.Multipart (BodyPart)
import Text.XML.HXT.Arrow.Pickle
import qualified Data.Label.Total as L
import Rest.Dictionary.Types
import Rest.Info
import Rest.Types.Error
mkHeader :: Header h -> Dict x p i o e -> Dict h p i o e
mkHeader = L.set headers
addHeader :: Header h -> Dict h' p i o e -> Dict (h, h') p i o e
addHeader = L.modify headers . TwoHeaders
mkPar :: Param p -> Dict h x i o e -> Dict h p i o e
mkPar = L.set params
addPar :: Param p -> Dict h p' i o e -> Dict h (p, p') i o e
addPar = L.modify params . TwoParams
someI :: Dict h p i o e -> Dict h p i o e
someI = id
stringI :: Dict h p 'Nothing o e -> Dict h p ('Just String) o e
stringI = L.set inputs (Dicts [StringI])
xmlTextI :: Dict h p 'Nothing o e -> Dict h p ('Just Text) o e
xmlTextI = L.set inputs (Dicts [XmlTextI])
fileI :: Dict h p 'Nothing o e -> Dict h p ('Just ByteString) o e
fileI = L.set inputs (Dicts [FileI])
readI :: (Info i, Read i, Show i, FromMaybe i i' ~ i) => Dict h p i' o e -> Dict h p ('Just i) o e
readI = L.modify inputs (modDicts (ReadI:))
xmlI :: (Typeable i, XmlPickler i, FromMaybe i i' ~ i) => Dict h p i' o e -> Dict h p ('Just i) o e
xmlI = L.modify inputs (modDicts (XmlI:))
rawXmlI :: Dict h p 'Nothing o e -> Dict h p ('Just ByteString) o e
rawXmlI = L.set inputs (Dicts [RawXmlI])
rawJsonI :: Dict h p 'Nothing o e -> Dict h p ('Just ByteString) o e
rawJsonI = L.set inputs (Dicts [RawJsonI])
jsonI :: (Typeable i, FromJSON i, JSONSchema i, FromMaybe i i' ~ i) => Dict h p i' o e -> Dict h p ('Just i) o e
jsonI = L.modify inputs (modDicts (JsonI:))
rawJsonAndXmlI :: Dict h p 'Nothing o e -> Dict h p ('Just (Either Json Xml)) o e
rawJsonAndXmlI = L.set inputs (Dicts [RawJsonAndXmlI])
someO :: Dict h p i o e -> Dict h p i o e
someO = id
stringO :: Dict h p i 'Nothing e -> Dict h p i ('Just String) e
stringO = L.set outputs (Dicts [StringO])
fileO :: Dict h p i 'Nothing e -> Dict h p i ('Just (ByteString, String, Bool)) e
fileO = L.set outputs (Dicts [FileO])
xmlO :: (Typeable o, XmlPickler o, FromMaybe o o' ~ o) => Dict h p i o' e -> Dict h p i ('Just o) e
xmlO = L.modify outputs (modDicts (XmlO:))
rawXmlO :: Dict h p i 'Nothing e -> Dict h p i ('Just ByteString) e
rawXmlO = L.set outputs (Dicts [RawXmlO])
rawJsonO :: Dict h p i 'Nothing e -> Dict h p i ('Just ByteString) e
rawJsonO = L.set outputs (Dicts [RawJsonO])
jsonO :: (Typeable o, ToJSON o, JSONSchema o, FromMaybe o o' ~ o) => Dict h p i o' e -> Dict h p i ('Just o) e
jsonO = L.modify outputs (modDicts (JsonO:))
rawJsonAndXmlO :: Dict h p i 'Nothing e -> Dict h p i ('Just ByteString) e
rawJsonAndXmlO = L.set outputs (Dicts [RawJsonAndXmlO])
multipartO :: Dict h p i 'Nothing e -> Dict h p i ('Just [BodyPart]) e
multipartO = L.set outputs (Dicts [MultipartO])
someE :: Dict h p i o e -> Dict h p i o e
someE = id
jsonE :: (ToResponseCode e, Typeable e, ToJSON e, JSONSchema e, FromMaybe e e' ~ e) => Dict h p i o e' -> Dict h p i o ('Just e)
jsonE = L.modify errors (modDicts (JsonE:))
xmlE :: (ToResponseCode e, Typeable e, XmlPickler e, FromMaybe e e' ~ e) => Dict h p i o e' -> Dict h p i o ('Just e)
xmlE = L.modify errors (modDicts (XmlE:))
xmlJsonI :: (Typeable i, FromJSON i, JSONSchema i, XmlPickler i, FromMaybe i i' ~ i) => Dict h p i' o e -> Dict h p ('Just i) o e
xmlJsonI = xmlI . jsonI
xmlJsonO :: (Typeable o, ToJSON o, JSONSchema o, XmlPickler o, FromMaybe o o' ~ o) => Dict h p i o' e -> Dict h p i ('Just o) e
xmlJsonO = xmlO . jsonO
xmlJsonE :: (ToResponseCode e, Typeable e, ToJSON e, JSONSchema e, XmlPickler e, FromMaybe e e' ~ e) => Dict h p i o e' -> Dict h p i o ('Just e)
xmlJsonE = xmlE . jsonE
xmlJson :: ( Typeable i, FromJSON i, JSONSchema i, XmlPickler i
, Typeable o, ToJSON o, JSONSchema o, XmlPickler o
, FromMaybe i i' ~ i, FromMaybe o o' ~ o
)
=> Dict h p i' o' e -> Dict h p ('Just i) ('Just o) e
xmlJson = xmlJsonI . xmlJsonO