Switch from To/FromRawObjec to To/FromObject

This commit is contained in:
Michael Snoyman 2009-10-15 08:58:41 +02:00
parent 564d1431df
commit 32ae0439f7
3 changed files with 18 additions and 9 deletions

View File

@ -20,6 +20,7 @@ module Data.Object.Instances
) where
import Data.Object
import Data.Object.Raw
import qualified Data.ByteString.Lazy as B
import Data.ByteString.Class
import Web.Encodings (encodeJson)
@ -32,7 +33,7 @@ newtype Json = Json { unJson :: B.ByteString }
instance SafeFromObject Json where
safeFromObject = Json . helper where
helper :: RawObject -> B.ByteString
helper (Scalar s) = B.concat
helper (Scalar (Raw s)) = B.concat
[ toLazyByteString "\""
, encodeJson $ fromLazyByteString s
, toLazyByteString "\""
@ -47,8 +48,8 @@ instance SafeFromObject Json where
, B.intercalate (toLazyByteString ",") $ map helper2 m
, toLazyByteString "}"
]
helper2 :: (B.ByteString, RawObject) -> B.ByteString
helper2 (k, v) = B.concat
helper2 :: (Raw, RawObject) -> B.ByteString
helper2 (Raw k, v) = B.concat
[ toLazyByteString "\""
, encodeJson $ fromLazyByteString k
, toLazyByteString "\":"
@ -73,7 +74,7 @@ instance SafeFromObject Html where
, toLazyByteString "</body></html>"
] where
helper :: RawObject -> B.ByteString
helper (Scalar s) = B.concat
helper (Scalar (Raw s)) = B.concat
[ toLazyByteString "<p>"
, toLazyByteString s
, toLazyByteString "</p>"
@ -88,8 +89,8 @@ instance SafeFromObject Html where
toLazyByteString "<dl>" :
map helper2 m ++
[ toLazyByteString "</dl>" ]
helper2 :: (B.ByteString, RawObject) -> B.ByteString
helper2 (k, v) = B.concat
helper2 :: (Raw, RawObject) -> B.ByteString
helper2 (Raw k, v) = B.concat
[ toLazyByteString "<dt>"
, toLazyByteString k
, toLazyByteString "</dt><dd>"

View File

@ -2,6 +2,7 @@
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
---------------------------------------------------------
--
-- Module : Web.Restful.Application
@ -24,6 +25,7 @@ module Web.Restful.Application
import Web.Encodings
import qualified Data.ByteString.Lazy as B
import Data.Object
import Data.Object.Raw
import Data.Enumerable
import Control.Monad (when)
@ -42,6 +44,10 @@ import Web.Restful.Definitions
import Web.Restful.Constants
import Web.Restful.Resource
-- FIXME move to Data.Object.Raw
toRawObject :: ToObject o Raw Raw => o -> RawObject
toRawObject = toObject
-- | A data type that can be turned into a Hack application.
class ResourceName a => RestfulApp a where
-- | The encryption key to be used for encrypting client sessions.

View File

@ -1,4 +1,5 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeSynonymInstances #-}
---------------------------------------------------------
--
@ -38,7 +39,8 @@ module Web.Restful.Response
) where
import Data.Time.Clock
import Data.Object hiding (testSuite)
import Data.Object
import Data.Object.Raw
import Data.Object.Instances
import Web.Encodings (formatW3)
@ -115,8 +117,8 @@ htmlResponse :: (Monad m, NoI18N lbs) => lbs -> m Reps
htmlResponse = genResponse "text/html"
-- | Return a response from an Object.
objectResponse :: (Monad m, ToRawObject o) => o -> m Reps
objectResponse = return . reps . toRawObject
objectResponse :: (Monad m, ToObject o Raw Raw) => o -> m Reps
objectResponse o = return $ reps $ (toObject o :: RawObject)
-- HasReps instances
instance HasReps () where