Skip to content

Commit

Permalink
Select assertions out of DB in controller
Browse files Browse the repository at this point in the history
  • Loading branch information
singpolyma committed Mar 20, 2013
1 parent a372318 commit 699f97f
Show file tree
Hide file tree
Showing 3 changed files with 15 additions and 3 deletions.
11 changes: 10 additions & 1 deletion Application.hs
@@ -1,11 +1,15 @@
module Application where

import Data.String (fromString)
import Network.Wai (Request(..), Response(..), Application)
import Network.HTTP.Types (ok200, notFound404, seeOther303, badRequest400, notAcceptable406, Status, ResponseHeaders)
import Network.Wai.Util (string, stringHeaders)
import Web.PathPieces (PathPiece(..))
import Data.Base58Address (RippleAddress)
import Control.Error (readMay)
import Control.Monad.Trans (liftIO)
import Database.SQLite.Simple (query, field, FromRow(..), Connection, open, close)
import Database.SQLite.Simple.ToField (ToField(..))
import qualified Blaze.ByteString.Builder.Char.Utf8 as Blaze
import qualified Data.Text as T
import qualified Data.Text.Lazy.Builder as TL
Expand All @@ -19,6 +23,9 @@ instance PathPiece RippleAddress where
fromPathPiece = readMay . T.unpack
toPathPiece = T.pack . show

instance ToField RippleAddress where
toField adr = toField (show adr)

htmlEscape :: String -> String
htmlEscape = concatMap escChar
where
Expand All @@ -35,6 +42,8 @@ on404 :: Application
on404 _ = string notFound404 [] "Not Found"

reportFor :: Connection -> RippleAddress -> Application
reportFor db adr req = return $ responseTextBuilder ok200 headers (viewReport htmlEscape $ Report adr)
reportFor db adr req = do
assertions <- liftIO $ query db (fromString "SELECT `to`, `from`, `type`, `time`, `signed` FROM assertions WHERE `to` = ?") [adr]
return $ responseTextBuilder ok200 headers (viewReport htmlEscape $ Report adr assertions)
where
Just headers = stringHeaders [("Content-Type", "text/html; charset=utf8")]
5 changes: 4 additions & 1 deletion Records.hs
Expand Up @@ -4,9 +4,12 @@ import Data.Base58Address (RippleAddress)
import qualified Data.Text.Buildable as TL
import qualified Data.Text.Format.Types as TL

import Sqlite3

instance TL.Buildable RippleAddress where
build adr = TL.build (TL.Shown adr)

data Report = Report {
address :: RippleAddress
address :: RippleAddress,
assertions :: [AssertionRow]
}
2 changes: 1 addition & 1 deletion TODO
Expand Up @@ -7,7 +7,7 @@ thread B that gets signaled by thread A on new message and also takes requests t
If it's a response we're waiting for, send it back
Else, ignore it

AssertionRow probably also needs ToRow. We store normalized data from the blob in the DB for aggregation and sorting, and so might as well use it for display. INVESTIGATE HOW UTCTIME IS STORED IN DB!
NEEDS TO BE A REC IN Records.hs YOU FOOL! AssertionRow probably also needs ToRow. We store normalized data from the blob in the DB for aggregation and sorting, and so might as well use it for display. INVESTIGATE HOW UTCTIME IS STORED IN DB!

Need JSON outputs also, just derive ToJSON for the record I expect. Include blobs in the JSON?

Expand Down

0 comments on commit 699f97f

Please sign in to comment.