Skip to content

Commit

Permalink
WIP
Browse files Browse the repository at this point in the history
  • Loading branch information
memowe committed Feb 16, 2024
1 parent f0bd51c commit a8e024c
Show file tree
Hide file tree
Showing 6 changed files with 58 additions and 22 deletions.
29 changes: 29 additions & 0 deletions lib/LiBro/WebService.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
module LiBro.WebService where

import Data.Aeson
import Data.Proxy
import Servant
import GHC.Generics

newtype PersonIDs = PersonIDs {personIDs :: [Int]} deriving Generic
instance ToJSON PersonIDs

type LiBroAPI = "hello" :> Get '[JSON] PersonIDs
:<|> "yay" :> Get '[PlainText] String

libroServer :: Server LiBroAPI
libroServer = handleHello
:<|> handleYay
where
handleHello :: Handler PersonIDs
handleHello = return $ PersonIDs [17, 42]

handleYay :: Handler String
handleYay = return "Yay!"

libroApi :: Proxy LiBroAPI
libroApi = Proxy

libro :: Application
libro = serve libroApi libroServer

9 changes: 0 additions & 9 deletions lib/LiBro/WebService/API.hs

This file was deleted.

10 changes: 0 additions & 10 deletions lib/LiBro/WebService/Server.hs

This file was deleted.

25 changes: 25 additions & 0 deletions lib/LiBro/WebService/State.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
module LiBro.WebService.State where

import LiBro.Config
import LiBro.Data
import LiBro.Control
import Control.Concurrent

data LiBroState = LiBroState
{ config :: Config
, mvBlocking :: MVar Blocking
, mvData :: MVar LiBroData
}

lsConfig :: LiBroState -> IO Config
lsConfig = return . config

lsData :: LiBroState -> IO LiBroData
lsData = readMVar . mvData

lsInit :: Config -> IO LiBroState
lsInit config = do
mvb <- newEmptyMVar
mvd <- newEmptyMVar
initData config mvb mvd
return $ LiBroState config mvb mvd
5 changes: 3 additions & 2 deletions libro-backend.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -41,8 +41,8 @@ library
, LiBro.Data.Storage
, LiBro.Data.SafeText
, LiBro.Control
, LiBro.WebService.API
, LiBro.WebService.Server
, LiBro.WebService
, LiBro.WebService.State
, LiBro.Util
build-depends: aeson
, attoparsec
Expand Down Expand Up @@ -108,3 +108,4 @@ test-suite libro-backend-test
, text
, transformers
, vector
, wai
2 changes: 1 addition & 1 deletion server/Main.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Main where

import LiBro.Config as Conf
import LiBro.WebService.Server
import LiBro.WebService
import Network.Wai.Handler.Warp

configuredMain :: Config -> IO ()
Expand Down

0 comments on commit a8e024c

Please sign in to comment.