Skip to content

Instantly share code, notes, and snippets.

@beala
Last active February 22, 2017 00:07
Show Gist options
  • Save beala/acd616c3b6d765801dd4 to your computer and use it in GitHub Desktop.
Save beala/acd616c3b6d765801dd4 to your computer and use it in GitHub Desktop.
An HTTP endpoint that accepts sensor readings as JSON and writes them to a database. Written with servant: http://haskell-servant.github.io/tutorial/
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Data.Aeson
import GHC.Generics
import Network.Wai
import Network.Wai.Handler.Warp
import Servant
import qualified Data.Text as T
import Control.Monad.Trans.Either
import qualified Database.MySQL.Simple as DB
import Control.Monad.IO.Class
import Data.Int
-- Endpoint: POST /record
-- Accepts JSON in the request body that must parse to SensorEntry.
-- Returns plaintext.
-- Notice that this is a *type* which encodes all this information.
type SensorAPI = "record" :> ReqBody '[JSON] SensorEntry :> Post '[PlainText] T.Text
-- One reading from the sensors. This is what the POST body must decode to.
data SensorEntry = SensorEntry { temp :: Double -- temperature reading.
, unit :: Integer -- number of sensor unit.
, light :: Integer -- light intensity reading.
} deriving (Show, Eq, Generic)
-- Declare SensorEntry as instances of ToJSON and FromJSON
-- and we get JSON de/serialization for free.
instance ToJSON SensorEntry
instance FromJSON SensorEntry
-- The application serves the `sensorAPI` given the `record` handler.
app :: Application
app = serve sensorAPI record
-- Handler for "/record" endpoint.
record :: SensorEntry -> EitherT ServantErr IO T.Text
record entry = do
conn <- liftIO $ DB.connect connectionInfo
_ <- recordSensorEntry conn entry
liftIO $ DB.close conn
return "OK"
-- Write the sensor data to the DB.
recordSensorEntry :: MonadIO m => DB.Connection -> SensorEntry -> m Int64
recordSensorEntry conn entry = liftIO $ DB.execute conn rowInsertQuery (u ,l, t)
where rowInsertQuery = "INSERT INTO log (unit, light, temp) VALUES (?, ?, ?)"
t = temp entry
u = unit entry
l = light entry
sensorAPI :: Proxy SensorAPI
sensorAPI = Proxy
connectionInfo :: DB.ConnectInfo
connectionInfo = DB.ConnectInfo { DB.connectHost = "localhost"
, DB.connectPort = 34789
, DB.connectPassword = ""
, DB.connectDatabase = "sensor-log"
, DB.connectOptions = []
, DB.connectPath = ""
, DB.connectSSL = Nothing
, DB.connectUser = "root" }
-- Start the server on port 1337.
main :: IO ()
main = run 1337 app
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment