Compare commits
3 Commits
fb29a6e694
...
sandbox/Ma
Author | SHA1 | Date | |
---|---|---|---|
dc32120ca8 | |||
a580138e0d | |||
786927ccbd |
4
.gitignore
vendored
4
.gitignore
vendored
@ -1,6 +1,2 @@
|
||||
dist/
|
||||
config/config.dhall
|
||||
/ctags
|
||||
/TAGS
|
||||
/result*
|
||||
/backend/config
|
||||
|
@ -18,27 +18,25 @@ cabal-version: >=1.10
|
||||
executable backend
|
||||
main-is: Main.hs
|
||||
other-modules: Devel.Main
|
||||
, API
|
||||
, API.Books
|
||||
, API.Catalogue
|
||||
, API.Channels
|
||||
, API.Users
|
||||
, Database
|
||||
, Database.Book
|
||||
, Database.Channel
|
||||
, Database.Tag
|
||||
, Database.Schema
|
||||
, Database.Tag
|
||||
, Database.User
|
||||
, Datastore
|
||||
, Servant.XML
|
||||
, Server
|
||||
, Server.API
|
||||
, Server.API.Books
|
||||
, Server.API.Catalogue
|
||||
, Server.API.Channels
|
||||
, Server.API.Users
|
||||
, Server.Auth
|
||||
, Types
|
||||
, View
|
||||
-- other-extensions:
|
||||
build-depends: base >=4.10
|
||||
, exceptions
|
||||
, monad-control
|
||||
build-depends: base >=4.10 && <4.11
|
||||
, common
|
||||
, aeson
|
||||
, asn1-data
|
||||
@ -86,20 +84,3 @@ executable backend
|
||||
, NoImplicitPrelude
|
||||
, OverloadedStrings
|
||||
, RecordWildCards
|
||||
|
||||
test-suite spec
|
||||
type: exitcode-stdio-1.0
|
||||
main-is: Spec.hs
|
||||
hs-source-dirs: src
|
||||
build-depends: base >=4.10
|
||||
, classy-prelude
|
||||
, http-api-data
|
||||
, selda
|
||||
, selda-postgresql
|
||||
, aeson
|
||||
, text
|
||||
, validity
|
||||
, genvalidity-hspec
|
||||
, genvalidity-property
|
||||
, genvalidity-text
|
||||
, hspec
|
||||
|
@ -15,17 +15,15 @@ module Database
|
||||
, SeldaT )
|
||||
where
|
||||
|
||||
import ClassyPrelude
|
||||
import Control.Lens (view)
|
||||
import Control.Monad.Catch (MonadMask)
|
||||
import Control.Monad.Trans.Control (MonadBaseControl)
|
||||
import Data.Generics.Product
|
||||
import Control.Lens (view)
|
||||
import Data.Pool (Pool, withResource)
|
||||
import Database.Selda (query, select, transaction)
|
||||
import Database.Selda.Backend (SeldaConnection, runSeldaT, SeldaT)
|
||||
import Database.Selda (query, select, transaction)
|
||||
import Database.Selda.Generic (gen, fromRel, fromRels, toRel)
|
||||
import ClassyPrelude
|
||||
|
||||
type DBLike r m = (MonadBaseControl IO m, MonadIO m, MonadReader r m, HasField "database" r r (Pool SeldaConnection) (Pool SeldaConnection), MonadMask m)
|
||||
type DBLike r m = (MonadIO m, MonadReader r m, MonadBaseControl IO m, MonadMask m, HasField' "database" r (Pool SeldaConnection))
|
||||
|
||||
runDB :: DBLike r m => SeldaT m a -> m a
|
||||
runDB q = do
|
||||
|
@ -18,17 +18,18 @@ module Database.Book
|
||||
, BookID) where
|
||||
|
||||
import ClassyPrelude
|
||||
import Control.Lens (view)
|
||||
import Control.Monad.Catch (MonadCatch)
|
||||
import Data.Generics.Product
|
||||
import Database
|
||||
import Database.Channel (booksChannels, attachChannel, clearChannels)
|
||||
import Database.Schema (books, users, Username, Book(..), BookID(..), UserID, HashDigest(..))
|
||||
import Database
|
||||
import Database.Selda
|
||||
import Database.Selda.Generic
|
||||
import Database.Tag (booksTags, attachTag, clearTags)
|
||||
|
||||
usersBooks :: (MonadSelda m, MonadIO m) => Username -> m [Book]
|
||||
import Control.Lens (view)
|
||||
import Data.Generics.Product
|
||||
|
||||
import Database.Tag (booksTags, attachTag, clearTags)
|
||||
import Database.Channel (booksChannels, attachChannel, clearChannels)
|
||||
|
||||
usersBooks :: (MonadSelda m, MonadMask m, MonadIO m) => Username -> m [Book]
|
||||
usersBooks username = fromRels <$> query q
|
||||
where
|
||||
q = do
|
||||
@ -40,7 +41,7 @@ usersBooks username = fromRels <$> query q
|
||||
return book
|
||||
|
||||
|
||||
getBook :: (MonadSelda m, MonadIO m) => BookID -> Username -> m (Maybe Book)
|
||||
getBook :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> Username -> m (Maybe Book)
|
||||
getBook identifier owner = listToMaybe . fromRels <$> query q
|
||||
where
|
||||
q = do
|
||||
@ -55,7 +56,7 @@ data InsertBook = InsertBook { contentType :: Text
|
||||
, owner :: Username }
|
||||
|
||||
-- Always inserts
|
||||
insertBook :: (MonadSelda m, MonadIO m) => InsertBook -> m (Maybe BookID)
|
||||
insertBook :: (MonadSelda m, MonadMask m, MonadIO m) => InsertBook -> m (Maybe BookID)
|
||||
insertBook InsertBook{..} = do
|
||||
mUserId <- query $ do
|
||||
userId :*: _ :*: username' :*: _ <- select (gen users)
|
||||
@ -74,7 +75,7 @@ data UpdateBook = UpdateBook { identifier :: BookID
|
||||
, channels :: [Text] }
|
||||
deriving (Show, Generic)
|
||||
|
||||
bookExists :: (MonadSelda m, MonadIO m) => BookID -> m Bool
|
||||
bookExists :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> m Bool
|
||||
bookExists identifier = not . null <$> query q
|
||||
where
|
||||
q = do
|
||||
@ -82,7 +83,7 @@ bookExists identifier = not . null <$> query q
|
||||
restrict (bookId .== literal identifier)
|
||||
return bookId
|
||||
|
||||
isBookOwner :: (MonadSelda m, MonadIO m) => BookID -> Username -> m Bool
|
||||
isBookOwner :: (MonadSelda m, MonadIO m, MonadThrow m) => BookID -> Username -> m Bool
|
||||
isBookOwner identifier username = not . null <$> query (bookOwner' identifier username)
|
||||
|
||||
bookOwner' :: BookID -> Username -> Query s (Col s UserID :*: Col s BookID)
|
||||
@ -94,7 +95,7 @@ bookOwner' identifier username = do
|
||||
restrict (bookId .== literal identifier)
|
||||
return (userId :*: bookId)
|
||||
|
||||
updateBook :: (MonadCatch m, MonadSelda m, MonadIO m) => UpdateBook -> m (Maybe UpdateBook)
|
||||
updateBook :: (MonadSelda m, MonadMask m, MonadIO m) => UpdateBook -> m (Maybe UpdateBook)
|
||||
updateBook UpdateBook{..} = do
|
||||
clearTags identifier >> connectTags
|
||||
clearChannels identifier >> connectChannels
|
||||
@ -113,7 +114,7 @@ updateBook UpdateBook{..} = do
|
||||
predicate (bookId :*: _) = bookId .== literal identifier
|
||||
|
||||
|
||||
getUpdateBook :: (MonadIO m, MonadSelda m) => BookID -> Username -> m (Maybe UpdateBook)
|
||||
getUpdateBook :: (MonadMask m, MonadIO m, MonadSelda m) => BookID -> Username -> m (Maybe UpdateBook)
|
||||
getUpdateBook bookId username = do
|
||||
mBook <- getBook bookId username
|
||||
forM mBook $ \Book{..} -> do
|
||||
@ -121,7 +122,7 @@ getUpdateBook bookId username = do
|
||||
tags <- map (view (field @"tag")) <$> booksTags bookId
|
||||
return UpdateBook{owner=username,..}
|
||||
|
||||
setContent :: (MonadSelda m, MonadIO m) => BookID -> Username -> HashDigest -> m ()
|
||||
setContent :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> Username -> HashDigest -> m ()
|
||||
setContent identifier owner digest = do
|
||||
mOwner <- query (bookOwner' identifier owner)
|
||||
void $ forM (listToMaybe mOwner) $ \_ ->
|
||||
|
@ -17,15 +17,14 @@ module Database.Channel
|
||||
where
|
||||
|
||||
import ClassyPrelude
|
||||
import Control.Monad.Catch (MonadMask)
|
||||
import Database
|
||||
import Database.Schema
|
||||
import Database
|
||||
import Database.Selda
|
||||
import Database.Selda.Generic
|
||||
|
||||
import Control.Monad.Trans.Maybe
|
||||
|
||||
getChannel :: (MonadSelda m, MonadIO m) => ChannelID -> m (Maybe Channel)
|
||||
getChannel :: (MonadSelda m, MonadMask m, MonadIO m) => ChannelID -> m (Maybe Channel)
|
||||
getChannel identifier = listToMaybe . fromRels <$> query q
|
||||
where
|
||||
q = do
|
||||
@ -33,10 +32,10 @@ getChannel identifier = listToMaybe . fromRels <$> query q
|
||||
restrict (channelId .== literal identifier)
|
||||
return ch
|
||||
|
||||
channelExists :: (MonadSelda m, MonadIO m) => ChannelID -> m Bool
|
||||
channelExists :: (MonadSelda m, MonadMask m, MonadIO m) => ChannelID -> m Bool
|
||||
channelExists identifier = not . null <$> getChannel identifier
|
||||
|
||||
isChannelOwner :: (MonadSelda m, MonadIO m) => ChannelID -> Username -> m Bool
|
||||
isChannelOwner :: (MonadSelda m, MonadIO m, MonadMask m) => ChannelID -> Username -> m Bool
|
||||
isChannelOwner identifier username = not . null <$> query q
|
||||
where
|
||||
q = do
|
||||
@ -57,7 +56,7 @@ userChannels username = fromRels <$> query q
|
||||
restrict (username' .== literal username)
|
||||
return channel
|
||||
|
||||
updateChannelPrivacy :: (MonadIO m, MonadSelda m) => ChannelID -> Visibility -> m (Maybe Channel)
|
||||
updateChannelPrivacy :: (MonadMask m, MonadIO m, MonadSelda m) => ChannelID -> Visibility -> m (Maybe Channel)
|
||||
updateChannelPrivacy channelId visibility = do
|
||||
void $ update (gen channels) predicate (\channel -> channel `with` [pVis := literal visibility])
|
||||
getChannel channelId
|
||||
@ -82,7 +81,7 @@ insertChannel username channel visibility = runMaybeT $ do
|
||||
restrict (user .== literal username)
|
||||
return userId
|
||||
|
||||
channelBooks :: (MonadSelda m, MonadIO m) => Username -> ChannelID -> m [Book]
|
||||
channelBooks :: (MonadSelda m, MonadMask m, MonadIO m) => Username -> ChannelID -> m [Book]
|
||||
channelBooks username identifier = fromRels <$> query q
|
||||
where
|
||||
q = do
|
||||
@ -95,7 +94,7 @@ channelBooks username identifier = fromRels <$> query q
|
||||
restrict (bookId .== bookId')
|
||||
return book
|
||||
|
||||
booksChannels :: (MonadSelda m, MonadIO m) => BookID -> m [Channel]
|
||||
booksChannels :: (MonadSelda m, MonadMask m, MonadIO m) => BookID -> m [Channel]
|
||||
booksChannels bookId = fromRels <$> query q
|
||||
where
|
||||
q = do
|
||||
@ -105,7 +104,7 @@ booksChannels bookId = fromRels <$> query q
|
||||
restrict (bookId' .== literal bookId)
|
||||
return ch
|
||||
|
||||
attachChannel :: (MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m ()
|
||||
attachChannel :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m ()
|
||||
attachChannel username bookId channel = do
|
||||
mCh <- fromRels <$> query channelQ
|
||||
forM_ mCh $ \Channel{identifier} ->
|
||||
@ -124,5 +123,5 @@ attachChannel username bookId channel = do
|
||||
restrict (channel' .== literal channel)
|
||||
return ch
|
||||
|
||||
clearChannels :: (MonadIO m, MonadSelda m) => BookID -> m Int
|
||||
clearChannels :: (MonadMask m, MonadIO m, MonadSelda m) => BookID -> m Int
|
||||
clearChannels bookId = deleteFrom (gen bookChannels) (\(_ :*: bookId') -> bookId' .== literal bookId)
|
||||
|
@ -14,13 +14,10 @@ import Data.Aeson
|
||||
import Web.HttpApiData
|
||||
|
||||
-- | User type
|
||||
newtype PlainPassword = PlainPassword Text deriving (Show, ToJSON, FromJSON, ToHttpApiData, FromHttpApiData, Eq, Generic)
|
||||
newtype PlainPassword = PlainPassword Text deriving (Show, ToJSON, FromJSON, ToHttpApiData, FromHttpApiData, Eq)
|
||||
newtype HashedPassword = HashedPassword {unHashed :: ByteString}
|
||||
data NoPassword = NoPassword
|
||||
|
||||
newtype Email = Email { unEmail :: Text } deriving (Show, ToJSON, FromJSON, ToHttpApiData, FromHttpApiData, Generic, Eq)
|
||||
|
||||
newtype Username = Username { unUsername :: Text } deriving (Show, ToJSON, FromJSON, ToHttpApiData, FromHttpApiData, Eq, Generic)
|
||||
|
||||
instance SqlType HashedPassword where
|
||||
mkLit = LCustom . LBlob . unHashed
|
||||
@ -42,9 +39,9 @@ instance SqlType Username where
|
||||
|
||||
newtype UserID = UserID {unUserID :: Int} deriving (Show)
|
||||
|
||||
newtype BookID = BookID {unBookID :: Int} deriving (Show, ToJSON, FromJSON, FromHttpApiData, Eq, Ord, ToHttpApiData, Generic)
|
||||
newtype BookID = BookID {unBookID :: Int} deriving (Show, ToJSON, FromJSON, FromHttpApiData, Eq, Ord, ToHttpApiData)
|
||||
|
||||
newtype ChannelID = ChannelID {unChannelID :: Int} deriving (Show, ToHttpApiData, FromHttpApiData, ToJSON, FromJSON, Eq, Generic)
|
||||
newtype ChannelID = ChannelID {unChannelID :: Int} deriving (Show, ToHttpApiData, FromHttpApiData, ToJSON, FromJSON)
|
||||
|
||||
newtype TagID = TagID {unTagID :: Int} deriving (Show)
|
||||
|
||||
@ -77,7 +74,7 @@ data User pass = User { identifier :: UserID
|
||||
, password :: pass }
|
||||
deriving (Show, Generic)
|
||||
|
||||
data Role = UserRole | AdminRole deriving (Show, Read, Enum, Bounded, Typeable, Generic, Eq)
|
||||
data Role = UserRole | AdminRole deriving (Show, Read, Enum, Bounded, Typeable, Generic)
|
||||
|
||||
instance ToJSON Role
|
||||
instance FromJSON Role
|
||||
@ -125,7 +122,7 @@ data Tag = Tag { identifier :: TagID
|
||||
deriving (Show, Generic)
|
||||
|
||||
data Visibility = Public | Private | Followers
|
||||
deriving (Show, Read, Generic, Eq)
|
||||
deriving (Show, Read, Generic)
|
||||
|
||||
instance ToJSON Visibility
|
||||
instance FromJSON Visibility
|
||||
|
@ -12,14 +12,13 @@ module Database.Tag
|
||||
, Tag(..) ) where
|
||||
|
||||
import ClassyPrelude
|
||||
import Control.Monad.Catch (MonadCatch)
|
||||
import Control.Monad.Trans.Maybe
|
||||
import Database
|
||||
import Database.Schema
|
||||
import Database
|
||||
import Database.Selda
|
||||
import Database.Selda.Generic
|
||||
import Control.Monad.Trans.Maybe
|
||||
|
||||
upsertTag :: (MonadCatch m, MonadIO m, MonadSelda m) => Username -> Text -> m (Maybe Tag)
|
||||
upsertTag :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> Text -> m (Maybe Tag)
|
||||
upsertTag username tag = runMaybeT $ do
|
||||
userId <- MaybeT (listToMaybe <$> query userQ)
|
||||
void $ lift $ upsert (gen tags) (predicate userId) id [toRel (Tag def tag userId)]
|
||||
@ -35,7 +34,7 @@ upsertTag username tag = runMaybeT $ do
|
||||
restrict (username' .== literal username)
|
||||
return userId
|
||||
|
||||
booksTags :: (MonadIO m, MonadSelda m) => BookID -> m [Tag]
|
||||
booksTags :: (MonadMask m, MonadIO m, MonadSelda m) => BookID -> m [Tag]
|
||||
booksTags bookId = fromRels <$> query q
|
||||
where
|
||||
q = do
|
||||
@ -45,7 +44,7 @@ booksTags bookId = fromRels <$> query q
|
||||
restrict (bookId' .== literal bookId)
|
||||
return tag
|
||||
|
||||
attachTag :: (MonadCatch m, MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m ()
|
||||
attachTag :: (MonadMask m, MonadIO m, MonadSelda m) => Username -> BookID -> Text -> m ()
|
||||
attachTag username bookId tag = do
|
||||
maybeT <- upsertTag username tag
|
||||
forM_ maybeT $ \Tag{identifier} -> do
|
||||
@ -57,6 +56,6 @@ attachTag username bookId tag = do
|
||||
restrict (tagId' .== literal tagId .&& bookId' .== literal bookId)
|
||||
return tagId'
|
||||
|
||||
clearTags :: (MonadIO m, MonadSelda m) => BookID -> m Int
|
||||
clearTags :: (MonadMask m, MonadIO m, MonadSelda m) => BookID -> m Int
|
||||
clearTags bookId = deleteFrom (gen bookTags) (\(_ :*: bookId') -> bookId' .== literal bookId)
|
||||
|
||||
|
@ -5,21 +5,20 @@
|
||||
module Database.User where
|
||||
|
||||
import ClassyPrelude
|
||||
import Control.Lens (view, over, _Just)
|
||||
import Control.Monad (mfilter)
|
||||
import Control.Monad.Catch (MonadMask)
|
||||
import Control.Monad.Logger
|
||||
import Crypto.KDF.BCrypt
|
||||
import Crypto.Random.Types (MonadRandom)
|
||||
import Data.Generics.Product
|
||||
import Database
|
||||
import Database.Schema
|
||||
import Database.Selda
|
||||
import Control.Lens (view, over, _Just)
|
||||
import Data.Generics.Product
|
||||
import Crypto.KDF.BCrypt
|
||||
import Crypto.Random.Types (MonadRandom)
|
||||
import Control.Monad.Logger
|
||||
import Control.Monad (mfilter)
|
||||
|
||||
data UserExistsError = UserExistsError
|
||||
|
||||
|
||||
insertUser :: (MonadMask m, MonadLogger m, MonadIO m, MonadRandom m) => Username -> Email -> PlainPassword -> SeldaT m (Either UserExistsError (User NoPassword))
|
||||
insertUser :: (MonadLogger m, MonadIO m, MonadMask m, MonadRandom m) => Username -> Email -> PlainPassword -> SeldaT m (Either UserExistsError (User NoPassword))
|
||||
insertUser username email (PlainPassword password) =
|
||||
getUser' username >>= maybe insert' (const (return $ Left UserExistsError))
|
||||
where
|
||||
|
@ -5,7 +5,6 @@
|
||||
{-# Language FlexibleContexts #-}
|
||||
{-# Language TypeSynonymInstances #-}
|
||||
{-# Language FlexibleInstances #-}
|
||||
{-# Language ScopedTypeVariables #-}
|
||||
module Datastore where
|
||||
|
||||
import ClassyPrelude
|
||||
@ -29,26 +28,26 @@ instance MonadDS AppM where
|
||||
get = getLocal
|
||||
|
||||
putLocal :: ( MonadIO m
|
||||
, HasField "config" r r config config
|
||||
, HasField "store" config config store store
|
||||
, HasType Text store
|
||||
, HasField' "config" r config
|
||||
, HasField' "store" config store
|
||||
, HasField' "path" store Text
|
||||
, MonadReader r m)
|
||||
=> ByteString -> m (Digest SHA256)
|
||||
putLocal bs = do
|
||||
store :: FilePath <- unpack <$> view (field @"config" . field @"store" . typed @Text)
|
||||
store <- unpack <$> view (field @"config" . field @"store" . field @"path")
|
||||
liftIO $ createDirectoryIfMissing True store
|
||||
let key = hashWith SHA256 bs
|
||||
writeFile (store </> show key) bs
|
||||
return key
|
||||
|
||||
getLocal :: ( MonadIO m
|
||||
, HasField "config" r r config config
|
||||
, HasField "store" config config store store
|
||||
, HasType Text store
|
||||
, HasField' "config" r config
|
||||
, HasField' "store" config store
|
||||
, HasField' "path" store Text
|
||||
, MonadReader r m)
|
||||
=> Digest SHA256 -> m (Maybe ByteString)
|
||||
getLocal key = do
|
||||
store <- unpack <$> view (field @"config" . field @"store" . typed @Text)
|
||||
store <- unpack <$> view (field @"config" . field @"store" . field @"path")
|
||||
liftIO $ createDirectoryIfMissing True store
|
||||
let file = store </> show key
|
||||
exists <- liftIO $ doesFileExist file
|
||||
|
@ -3,18 +3,19 @@
|
||||
{-# Language FlexibleContexts #-}
|
||||
module Devel.Main where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.Trans.Reader (runReaderT)
|
||||
import Main (withApp, defaultMain)
|
||||
import Control.Concurrent
|
||||
import Control.Monad (void)
|
||||
import Control.Monad.Trans.Reader (runReaderT)
|
||||
import Data.IORef (IORef, newIORef, readIORef, writeIORef)
|
||||
import Database
|
||||
import Database.Schema
|
||||
import Database.Selda (tryCreateTable)
|
||||
import Dhall (input, auto)
|
||||
import Foreign.Store (Store(..), lookupStore, readStore, storeAction, withStore)
|
||||
import GHC.Word (Word32)
|
||||
import Main (withApp, defaultMain)
|
||||
import Prelude
|
||||
import Dhall (input, auto)
|
||||
|
||||
import Database.Schema
|
||||
import Database.Selda (tryCreateTable)
|
||||
import Database
|
||||
|
||||
update :: IO ()
|
||||
update = do
|
||||
|
@ -25,7 +25,6 @@ withApp :: Config -> (App -> IO ()) -> IO ()
|
||||
withApp config f = do
|
||||
let pgHost = view (field @"database" . field @"host") config
|
||||
pgPort = 5432
|
||||
pgSchema = Nothing
|
||||
pgDatabase = view (field @"database" . field @"database") config
|
||||
pgUsername = Just (view (field @"database" . field @"username") config)
|
||||
pgPassword = Just (view (field @"database" . field @"password") config)
|
||||
|
@ -10,10 +10,9 @@
|
||||
{-# Language DeriveGeneric #-}
|
||||
{-# Language FlexibleInstances #-}
|
||||
{-# Language TypeApplications #-}
|
||||
{-# Language ScopedTypeVariables #-}
|
||||
module Server where
|
||||
|
||||
import qualified API as API
|
||||
import qualified Server.API as API
|
||||
import Server.Auth (authCheck)
|
||||
import Servant
|
||||
import Types
|
||||
@ -23,21 +22,19 @@ import Control.Monad.Except
|
||||
import Servant.Auth.Server as SAS
|
||||
import Control.Lens
|
||||
import Data.Generics.Product
|
||||
import Server.Auth (SafeUser)
|
||||
|
||||
type API = API.API :<|> "static" :> Raw
|
||||
|
||||
type Ctx = '[BasicAuthData -> IO (AuthResult SafeUser), CookieSettings, JWTSettings]
|
||||
|
||||
server :: App -> Application
|
||||
server app = serveWithContext api cfg (hoistServerWithContext (Proxy @ API.API) (Proxy @ Ctx) server' API.handler :<|> serveDirectoryFileServer "static")
|
||||
server app = serveWithContext api cfg (enter server' API.handler :<|> serveDirectoryFileServer "static")
|
||||
where
|
||||
myKey = view (field @"jwk") app
|
||||
jwtCfg = defaultJWTSettings myKey
|
||||
authCfg = authCheck app
|
||||
cookieSettings = SAS.defaultCookieSettings{cookieIsSecure=SAS.NotSecure}
|
||||
cfg = jwtCfg :. cookieSettings :. authCfg :. EmptyContext
|
||||
server' :: AppM a -> Servant.Handler a
|
||||
server' = Handler . ExceptT . try . (`runReaderT` app) . (runFileLoggingT "logs/server.log")
|
||||
server' :: AppM :~> Servant.Handler
|
||||
server' = NT (Handler . ExceptT . try . (`runReaderT` app) . (runFileLoggingT "logs/server.log"))
|
||||
api :: Proxy API
|
||||
api = Proxy
|
||||
|
@ -9,7 +9,7 @@
|
||||
{-# Language RecordWildCards #-}
|
||||
{-# Language DeriveGeneric #-}
|
||||
{-# Language FlexibleInstances #-}
|
||||
module API (API, handler) where
|
||||
module Server.API (API, handler) where
|
||||
|
||||
|
||||
import Servant
|
||||
@ -18,10 +18,10 @@ import Types
|
||||
|
||||
import View
|
||||
|
||||
import qualified API.Users as Users
|
||||
import qualified API.Channels as Channels
|
||||
import qualified API.Books as Books
|
||||
import qualified API.Catalogue as Catalogue
|
||||
import qualified Server.API.Users as Users
|
||||
import qualified Server.API.Channels as Channels
|
||||
import qualified Server.API.Books as Books
|
||||
import qualified Server.API.Catalogue as Catalogue
|
||||
|
||||
data Index = Index
|
||||
|
@ -13,27 +13,26 @@
|
||||
{-# Language TypeApplications #-}
|
||||
{-# Language DataKinds #-}
|
||||
{-# Language NamedFieldPuns #-}
|
||||
module API.Books where
|
||||
module Server.API.Books where
|
||||
|
||||
import ClassyPrelude
|
||||
import Control.Lens
|
||||
import Control.Monad.Catch (throwM, MonadThrow)
|
||||
import Data.Aeson
|
||||
import Data.Generics.Product
|
||||
import Database
|
||||
import Database.Book
|
||||
import Database.Channel
|
||||
import Database.Tag
|
||||
import Servant hiding (contentType)
|
||||
import Servant.Auth as SA
|
||||
import Server.Auth
|
||||
import Types
|
||||
import Servant hiding (contentType)
|
||||
import Types
|
||||
import ClassyPrelude
|
||||
import Server.Auth
|
||||
import Servant.Auth as SA
|
||||
import Data.Aeson
|
||||
import Database.Book
|
||||
import Database.Channel
|
||||
import Database.Tag
|
||||
import Database
|
||||
import Control.Lens
|
||||
import Data.Generics.Product
|
||||
|
||||
import Control.Monad.Trans.Maybe
|
||||
import Control.Monad.Trans.Maybe
|
||||
|
||||
import qualified Datastore as DS
|
||||
import Data.ByteArray (convert)
|
||||
import Crypto.Hash (digestFromByteString)
|
||||
import Data.ByteArray (convert)
|
||||
import Crypto.Hash (digestFromByteString)
|
||||
|
||||
data JsonBook = JsonBook { identifier :: BookID
|
||||
, contentType :: Text
|
@ -14,19 +14,19 @@
|
||||
{-# Language TemplateHaskell #-}
|
||||
{-# Language MultiParamTypeClasses #-}
|
||||
{-# Language ScopedTypeVariables #-}
|
||||
module API.Catalogue (VersionedAPI, handler) where
|
||||
module Server.API.Catalogue (VersionedAPI, handler) where
|
||||
|
||||
import qualified API.Books
|
||||
import ClassyPrelude
|
||||
import Database
|
||||
import Database.Book (Book(..))
|
||||
import Types
|
||||
import Servant hiding (contentType)
|
||||
import ClassyPrelude
|
||||
import GHC.TypeLits
|
||||
import Server.Auth
|
||||
import Servant.Auth as SA
|
||||
import Servant.XML
|
||||
import qualified Database.Channel as Channel
|
||||
import GHC.TypeLits
|
||||
import Servant hiding (contentType)
|
||||
import Servant.Auth as SA
|
||||
import Servant.XML
|
||||
import Server.Auth
|
||||
import Types
|
||||
import Database.Book (Book(..))
|
||||
import Database
|
||||
import qualified Server.API.Books as API.Books
|
||||
|
||||
-- This is my first try on going to versioned apis, things might change
|
||||
-- I think my rule of thumb is that you can add new things as you want, but
|
@ -13,20 +13,19 @@
|
||||
{-# Language DataKinds #-}
|
||||
{-# Language DuplicateRecordFields #-}
|
||||
{-# Language NamedFieldPuns #-}
|
||||
module API.Channels (API, handler, JsonChannel(..)) where
|
||||
module Server.API.Channels (API, handler, JsonChannel(..)) where
|
||||
|
||||
import Servant
|
||||
import Types
|
||||
import ClassyPrelude
|
||||
import Control.Lens
|
||||
import Control.Monad.Catch (throwM, MonadThrow)
|
||||
import Server.Auth
|
||||
import Servant.Auth as SA
|
||||
import Control.Monad.Logger
|
||||
import Data.Aeson
|
||||
import Data.Generics.Product
|
||||
import Database
|
||||
import Database.Channel
|
||||
import Servant
|
||||
import Servant.Auth as SA
|
||||
import Server.Auth
|
||||
import Types
|
||||
import Data.Aeson
|
||||
import Control.Lens
|
||||
import Data.Generics.Product
|
||||
|
||||
data JsonChannel = JsonChannel { channel :: Text
|
||||
, visibility :: Visibility }
|
@ -5,20 +5,19 @@
|
||||
{-# Language TypeOperators #-}
|
||||
{-# Language DuplicateRecordFields #-}
|
||||
{-# Language TypeApplications #-}
|
||||
module API.Users where
|
||||
module Server.API.Users where
|
||||
|
||||
import ClassyPrelude
|
||||
import Control.Monad.Catch (throwM, MonadThrow)
|
||||
import Data.Aeson
|
||||
import Database (runDB)
|
||||
import Database.Schema
|
||||
import Database.User
|
||||
import Servant
|
||||
import Servant.Auth as SA
|
||||
import Servant.Auth.Server as SAS
|
||||
import Server.Auth
|
||||
import ClassyPrelude
|
||||
import Types
|
||||
import Data.Aeson
|
||||
import Web.FormUrlEncoded
|
||||
import Database (runDB)
|
||||
import Database.User
|
||||
import Database.Schema
|
||||
import Server.Auth
|
||||
import Servant.Auth.Server as SAS
|
||||
import Servant.Auth as SA
|
||||
|
||||
|
||||
data RegisterForm = RegisterForm { username :: Username
|
@ -14,32 +14,18 @@ module Server.Auth
|
||||
where
|
||||
|
||||
import ClassyPrelude
|
||||
import Control.Lens (view)
|
||||
import Control.Monad.Logger
|
||||
import Control.Monad.Catch (throwM, MonadThrow)
|
||||
import Servant.Auth.Server as SAS
|
||||
import Data.Aeson
|
||||
import Data.Generics.Product
|
||||
import Database
|
||||
import Database.Schema
|
||||
import Database.User
|
||||
import Servant (err401)
|
||||
import Servant.Auth.Server as SAS
|
||||
import Database
|
||||
import Types
|
||||
import Control.Lens (view)
|
||||
import Data.Generics.Product
|
||||
import Servant (err401)
|
||||
import Control.Monad.Logger
|
||||
import Auth (SafeUser(..))
|
||||
|
||||
-- generic-lens can convert similar types to this
|
||||
-- I'm trying out servant-auth-server which uses a jwt style login. IIRC anyone
|
||||
-- can open the jwt token and view what's inside, you just can't modify it.
|
||||
--
|
||||
-- Is it a problem that a human readable username and email are visible?
|
||||
data SafeUser = SafeUser { email :: Email
|
||||
, username :: Username
|
||||
, role :: Role }
|
||||
deriving (Show, Generic)
|
||||
|
||||
instance ToJSON SafeUser where
|
||||
instance FromJSON SafeUser where
|
||||
instance ToJWT SafeUser where
|
||||
instance FromJWT SafeUser where
|
||||
|
||||
type instance BasicAuthCfg = BasicAuthData -> IO (AuthResult SafeUser)
|
||||
|
||||
@ -54,6 +40,6 @@ authCheck app (BasicAuthData username password) = flip runReaderT app $
|
||||
password' = PlainPassword $ decodeUtf8 password
|
||||
authenticated = SAS.Authenticated . view (super @SafeUser)
|
||||
|
||||
requireLoggedIn :: (MonadThrow m, MonadLogger m, Monad m) => (SafeUser -> m a) -> AuthResult SafeUser -> m a
|
||||
requireLoggedIn :: (MonadLogger m, MonadThrow m, Monad m) => (SafeUser -> m a) -> AuthResult SafeUser -> m a
|
||||
requireLoggedIn f (Authenticated user) = f user
|
||||
requireLoggedIn _ u = $logError (pack (show u)) >> throwM err401
|
||||
|
@ -1,53 +0,0 @@
|
||||
{-# Language TypeApplications #-}
|
||||
module Main where
|
||||
|
||||
import qualified Data.Aeson as A
|
||||
import Data.Char (isPrint)
|
||||
import Data.GenValidity.Text ()
|
||||
import qualified Data.Text as T
|
||||
import Database.Schema
|
||||
import Test.Hspec
|
||||
import Test.Validity
|
||||
|
||||
instance GenUnchecked PlainPassword
|
||||
instance GenValid PlainPassword
|
||||
instance GenInvalid PlainPassword
|
||||
instance Validity PlainPassword
|
||||
instance GenUnchecked Email
|
||||
instance GenValid Email
|
||||
instance GenInvalid Email
|
||||
instance Validity Email
|
||||
instance GenUnchecked Username
|
||||
instance GenValid Username
|
||||
instance GenInvalid Username
|
||||
instance Validity Username
|
||||
instance GenUnchecked BookID
|
||||
instance GenValid BookID
|
||||
instance GenInvalid BookID
|
||||
instance Validity BookID
|
||||
instance GenUnchecked ChannelID
|
||||
instance GenValid ChannelID
|
||||
instance GenInvalid ChannelID
|
||||
instance Validity ChannelID
|
||||
instance GenUnchecked Role
|
||||
instance GenValid Role
|
||||
instance GenInvalid Role
|
||||
instance Validity Role
|
||||
instance GenUnchecked Visibility
|
||||
instance GenValid Visibility
|
||||
instance GenInvalid Visibility
|
||||
instance Validity Visibility
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
describe "JSON encoding" $ do
|
||||
it "Works for PlainPassword" $ inverseFunctionsIfSecondSucceedsOnValid (A.encode @PlainPassword) A.decode
|
||||
it "Works for Email" $ inverseFunctionsIfSecondSucceedsOnValid (A.encode @Email) A.decode
|
||||
it "Username" $ inverseFunctionsIfSecondSucceedsOnValid (A.encode @Username) A.decode
|
||||
it "Works for BookID" $ inverseFunctionsIfSecondSucceedsOnValid (A.encode @BookID) A.decode
|
||||
it "Works for ChannelID" $ inverseFunctionsIfSecondSucceedsOnValid (A.encode @ChannelID) A.decode
|
||||
it "Works for Role" $ inverseFunctionsIfSecondSucceedsOnValid (A.encode @Role) A.decode
|
||||
it "Works for Visibility" $ inverseFunctionsIfSecondSucceedsOnValid (A.encode @Visibility) A.decode
|
||||
|
||||
main :: IO ()
|
||||
main = hspec spec
|
@ -15,14 +15,27 @@ cabal-version: >=1.10
|
||||
library
|
||||
exposed-modules: Configuration
|
||||
, Data.Versioned
|
||||
, API
|
||||
, API.Books
|
||||
, API.Catalogue
|
||||
, API.Channels
|
||||
, API.Users
|
||||
, Auth
|
||||
-- other-extensions:
|
||||
build-depends: base >=4.10
|
||||
build-depends: base >=4.10 && <4.11
|
||||
, aeson
|
||||
, classy-prelude
|
||||
, dhall
|
||||
, foreign-store
|
||||
, generic-lens
|
||||
, lens
|
||||
, mtl
|
||||
, servant
|
||||
, servant-auth
|
||||
, servant-auth-server
|
||||
, servant-docs
|
||||
, servant-lucid
|
||||
, servant-multipart
|
||||
, text
|
||||
, transformers
|
||||
hs-source-dirs: src
|
||||
@ -30,22 +43,6 @@ library
|
||||
, NoImplicitPrelude
|
||||
, OverloadedStrings
|
||||
, RecordWildCards
|
||||
, TypeOperators
|
||||
, DataKinds
|
||||
default-language: Haskell2010
|
||||
|
||||
test-suite spec
|
||||
type: exitcode-stdio-1.0
|
||||
main-is: Spec.hs
|
||||
hs-source-dirs: src
|
||||
build-depends: base >=4.10
|
||||
, classy-prelude
|
||||
, dhall
|
||||
, foreign-store
|
||||
, generic-lens
|
||||
, lens
|
||||
, mtl
|
||||
, text
|
||||
, transformers
|
||||
, validity
|
||||
, genvalidity-hspec
|
||||
, genvalidity-property
|
||||
, hspec
|
1
common/src/API.hs
Normal file
1
common/src/API.hs
Normal file
@ -0,0 +1 @@
|
||||
module API where
|
1
common/src/API/Books.hs
Normal file
1
common/src/API/Books.hs
Normal file
@ -0,0 +1 @@
|
||||
module API.Books where
|
1
common/src/API/Catalogue.hs
Normal file
1
common/src/API/Catalogue.hs
Normal file
@ -0,0 +1 @@
|
||||
module API.Catalogue where
|
27
common/src/API/Channels.hs
Normal file
27
common/src/API/Channels.hs
Normal file
@ -0,0 +1,27 @@
|
||||
{-# Language DuplicateRecordFields #-}
|
||||
module API.Channels (API) where
|
||||
|
||||
import Auth
|
||||
import ClassyPrelude
|
||||
import Data.Aeson
|
||||
import Servant.API
|
||||
import Servant.Auth as SA
|
||||
|
||||
data JsonChannel = JsonChannel { channel :: Text
|
||||
, visibility :: Visibility }
|
||||
deriving (Show, Generic)
|
||||
data UpdateChannel = UpdateChannel { identifier :: ChannelID
|
||||
, channel :: Text
|
||||
, visibility :: Visibility }
|
||||
deriving (Show, Generic)
|
||||
|
||||
instance ToJSON JsonChannel
|
||||
instance FromJSON JsonChannel
|
||||
instance ToJSON UpdateChannel
|
||||
instance FromJSON UpdateChannel
|
||||
|
||||
type API = Auth '[SA.BasicAuth, SA.Cookie, SA.JWT] SafeUser :> BaseAPI
|
||||
|
||||
type BaseAPI = "channels" :> ReqBody '[JSON] JsonChannel :> Post '[JSON] UpdateChannel
|
||||
:<|> "channels" :> Capture "channel_id" ChannelID :> ReqBody '[JSON] UpdateChannel :> Put '[JSON] UpdateChannel
|
||||
:<|> "channels" :> Get '[JSON] [JsonChannel]
|
1
common/src/API/Users.hs
Normal file
1
common/src/API/Users.hs
Normal file
@ -0,0 +1 @@
|
||||
module API.Users where
|
26
common/src/Auth.hs
Normal file
26
common/src/Auth.hs
Normal file
@ -0,0 +1,26 @@
|
||||
{-# Language GeneralizedNewtypeDeriving #-}
|
||||
module Auth where
|
||||
|
||||
import ClassyPrelude
|
||||
import Data.Aeson
|
||||
import Servant.Auth.Server (ToJWT, FromJWT)
|
||||
import Servant.API
|
||||
|
||||
-- generic-lens can convert similar types to this
|
||||
-- I'm trying out servant-auth-server which uses a jwt style login. IIRC anyone
|
||||
-- can open the jwt token and view what's inside, you just can't modify it.
|
||||
--
|
||||
-- Is it a problem that a human readable username and email are visible?
|
||||
newtype Email = Email { unEmail :: Text } deriving (Show, ToJSON, FromJSON, ToHttpApiData, FromHttpApiData)
|
||||
|
||||
newtype Username = Username { unUsername :: Text } deriving (Show, ToJSON, FromJSON, ToHttpApiData, FromHttpApiData)
|
||||
|
||||
data SafeUser = SafeUser { email :: Email
|
||||
, username :: Username
|
||||
}
|
||||
deriving (Show, Generic)
|
||||
|
||||
instance ToJSON SafeUser where
|
||||
instance FromJSON SafeUser where
|
||||
instance ToJWT SafeUser where
|
||||
instance FromJWT SafeUser where
|
@ -12,9 +12,7 @@ data Pg = Pg { username :: Text
|
||||
, database :: Text }
|
||||
deriving (Show, Generic)
|
||||
|
||||
data Store = Filestore { path :: Text }
|
||||
| IPFS { common :: Text }
|
||||
deriving (Show, Generic)
|
||||
newtype Store = Store { path :: Text } deriving (Show, Generic)
|
||||
|
||||
data Config = Config { database :: Pg
|
||||
, store :: Store }
|
||||
|
@ -1,9 +0,0 @@
|
||||
module Main where
|
||||
|
||||
import Test.Hspec
|
||||
|
||||
spec :: Spec
|
||||
spec = describe "test" $ it "verifies tests work" $ True == True
|
||||
|
||||
main :: IO ()
|
||||
main = hspec spec
|
@ -5,9 +5,6 @@
|
||||
common = ./common;
|
||||
backend = ./backend;
|
||||
};
|
||||
overrides = self: super: {
|
||||
generic-lens = nixpkgs.haskell.lib.dontCheck super.generic-lens;
|
||||
};
|
||||
tools = with haskellPackages; [
|
||||
ghcid
|
||||
hasktags
|
||||
|
@ -1,7 +1,7 @@
|
||||
{
|
||||
"url": "https://github.com/nixos/nixpkgs.git",
|
||||
"rev": "e0d250e5cf6d179e1ccc775472d89718f61fcfd1",
|
||||
"rev": "83a5765b1fea2472ec9cf9d179d3efd18b45c77e",
|
||||
"date": "2018-01-08T11:52:28+01:00",
|
||||
"sha256": "1iqpjz4czcpghbv924a5h4jvfmj6c8q6sl3b1z7blz3mi740aivs",
|
||||
"sha256": "01rb61dkbzjbwnb3p8lgs03a94f4584199dlr0cwdmqzaxnp506h",
|
||||
"fetchSubmodules": true
|
||||
}
|
||||
|
@ -15,20 +15,19 @@ let
|
||||
|
||||
overrides' = nixpkgs.lib.foldr nixpkgs.lib.composeExtensions (_: _: {}) [
|
||||
(self: super: mapAttrs (name: path: self.callCabal2nix name path {}) packages)
|
||||
overrides
|
||||
];
|
||||
haskellPackages = nixpkgs.haskellPackages.override { overrides = overrides'; };
|
||||
packages' = mapAttrs (name: _: haskellPackages."${name}") packages;
|
||||
mkShell = name: pkg:
|
||||
let
|
||||
n = "${name}-shell";
|
||||
deps = haskellPackages.ghcWithHoogle (pkgs: pkg.buildInputs ++ pkg.propagatedBuildInputs);
|
||||
deps = haskellPackages.ghcWithPackages (pkgs: pkg.buildInputs);
|
||||
in
|
||||
{
|
||||
name = "${n}";
|
||||
value = nixpkgs.buildEnv {
|
||||
name = "${n}";
|
||||
paths = tools;
|
||||
paths = tools ++ [deps];
|
||||
buildInputs = tools ++ [deps];
|
||||
};
|
||||
};
|
||||
|
Reference in New Issue
Block a user