{-# LANGUAGE OverloadedStrings #-}
module Handlers.DataHandler where
import qualified Data.ByteString.Lazy as BL
import Manager
userTmpJSON :: FilePath
userTmpJSON :: FilePath
userTmpJSON = FilePath
"data/userTemp.json"
userJSON :: FilePath
userJSON :: FilePath
userJSON = FilePath
"data/userData.json"
fileExists :: FilePath -> IO Bool
fileExists :: FilePath -> IO Bool
fileExists FilePath
path = do FilePath -> IO Bool
doesFileExist FilePath
path
instance FromJSON User where
instance ToJSON User where
instance FromJSON UserFull where
instance ToJSON UserFull where
noUsersYet :: IO Bool
noUsersYet :: IO Bool
noUsersYet = do
(Just [UserFull]
existingUsers) <- ByteString -> Maybe [UserFull]
forall a. FromJSON a => ByteString -> Maybe a
decode (ByteString -> Maybe [UserFull])
-> IO ByteString -> IO (Maybe [UserFull])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO ByteString
BL.readFile FilePath
userJSON :: IO (Maybe [UserFull])
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return ([UserFull] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UserFull]
existingUsers)
saveUser :: UserFull -> IO Bool
saveUser :: UserFull -> IO Bool
saveUser UserFull
newUser = do
(Just [UserFull]
allUsers) <- ByteString -> Maybe [UserFull]
forall a. FromJSON a => ByteString -> Maybe a
decode (ByteString -> Maybe [UserFull])
-> IO ByteString -> IO (Maybe [UserFull])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO ByteString
BL.readFile FilePath
userJSON :: IO (Maybe [UserFull])
let correspondingUsers :: [UserFull]
correspondingUsers = (UserFull -> Bool) -> [UserFull] -> [UserFull]
forall a. (a -> Bool) -> [a] -> [a]
filter (\UserFull
user -> UserFull -> FilePath
email UserFull
user FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== UserFull -> FilePath
email UserFull
newUser) [UserFull]
allUsers
if [UserFull] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UserFull]
correspondingUsers
then do {FilePath -> ByteString -> IO ()
BL.writeFile FilePath
userJSON (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ [UserFull] -> ByteString
forall a. ToJSON a => a -> ByteString
encode ([UserFull]
allUsers [UserFull] -> [UserFull] -> [UserFull]
forall a. [a] -> [a] -> [a]
++ [UserFull
newUser]); Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True}
else Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
deleteUser :: String -> IO Bool
deleteUser :: FilePath -> IO Bool
deleteUser FilePath
emailStr = do
(Just [UserFull]
allUsers) <- ByteString -> Maybe [UserFull]
forall a. FromJSON a => ByteString -> Maybe a
decode (ByteString -> Maybe [UserFull])
-> IO ByteString -> IO (Maybe [UserFull])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO ByteString
BL.readFile FilePath
userJSON :: IO (Maybe [UserFull])
let allButOne :: [UserFull]
allButOne = (UserFull -> Bool) -> [UserFull] -> [UserFull]
forall a. (a -> Bool) -> [a] -> [a]
filter (\UserFull
user -> UserFull -> FilePath
email UserFull
user FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
emailStr) [UserFull]
allUsers
FilePath -> ByteString -> IO ()
BL.writeFile FilePath
userJSON (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ [UserFull] -> ByteString
forall a. ToJSON a => a -> ByteString
encode [UserFull]
allButOne
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ [UserFull]
allUsers [UserFull] -> [UserFull] -> Bool
forall a. Eq a => a -> a -> Bool
/= [UserFull]
allButOne
getUser :: String -> IO (Maybe UserFull)
getUser :: FilePath -> IO (Maybe UserFull)
getUser FilePath
emailStr = do
(Just [UserFull]
allUsers) <- ByteString -> Maybe [UserFull]
forall a. FromJSON a => ByteString -> Maybe a
decode (ByteString -> Maybe [UserFull])
-> IO ByteString -> IO (Maybe [UserFull])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO ByteString
BL.readFile FilePath
userJSON :: IO (Maybe [UserFull])
let correspondingUsers :: [UserFull]
correspondingUsers = (UserFull -> Bool) -> [UserFull] -> [UserFull]
forall a. (a -> Bool) -> [a] -> [a]
filter (\UserFull
user -> UserFull -> FilePath
email UserFull
user FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
emailStr) [UserFull]
allUsers
if [UserFull] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UserFull]
correspondingUsers
then Maybe UserFull -> IO (Maybe UserFull)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe UserFull
forall a. Maybe a
Nothing
else Maybe UserFull -> IO (Maybe UserFull)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe UserFull -> IO (Maybe UserFull))
-> Maybe UserFull -> IO (Maybe UserFull)
forall a b. (a -> b) -> a -> b
$ UserFull -> Maybe UserFull
forall a. a -> Maybe a
Just ([UserFull] -> UserFull
forall a. [a] -> a
head [UserFull]
correspondingUsers)
signUser :: String -> IO ()
signUser :: FilePath -> IO ()
signUser FilePath
emailStr = do
(Just UserFull
userfull) <- FilePath -> IO (Maybe UserFull)
getUser FilePath
emailStr
let user :: User
user = FilePath -> FilePath -> Bool -> User
User (UserFull -> FilePath
name UserFull
userfull) (UserFull -> FilePath
email UserFull
userfull) (UserFull -> Bool
isAdmin UserFull
userfull)
FilePath -> ByteString -> IO ()
BL.writeFile FilePath
userTmpJSON (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ User -> ByteString
forall a. ToJSON a => a -> ByteString
encode User
user
hasLoggedUser :: IO Bool
hasLoggedUser :: IO Bool
hasLoggedUser = do FilePath -> IO Bool
fileExists FilePath
userTmpJSON
getLoggedUser :: IO User
getLoggedUser :: IO User
getLoggedUser = do
Maybe User
tmpUser <- ByteString -> Maybe User
forall a. FromJSON a => ByteString -> Maybe a
decode (ByteString -> Maybe User) -> IO ByteString -> IO (Maybe User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO ByteString
BL.readFile FilePath
userTmpJSON
IO User -> (User -> IO User) -> Maybe User -> IO User
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO User
getLoggedUser User -> IO User
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe User
tmpUser
signOutUser :: IO ()
signOutUser :: IO ()
signOutUser = do
Bool
existsTmp <- IO Bool
hasLoggedUser
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
existsTmp (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
removeFile FilePath
userTmpJSON
roomsJSON :: FilePath
roomsJSON :: FilePath
roomsJSON = FilePath
"data/roomsData.json"
instance FromJSON ResourceKind where
instance ToJSON ResourceKind where
instance FromJSON Resource where
instance ToJSON Resource where
instance FromJSON RoomCategory where
instance ToJSON RoomCategory where
instance FromJSON Reservation where
instance ToJSON Reservation where
instance FromJSON Room where
instance ToJSON Room where
fetchRooms :: IO [Room]
fetchRooms :: IO [Room]
fetchRooms = do
(Just [Room]
allRooms) <- ByteString -> Maybe [Room]
forall a. FromJSON a => ByteString -> Maybe a
decode (ByteString -> Maybe [Room]) -> IO ByteString -> IO (Maybe [Room])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO ByteString
BL.readFile FilePath
roomsJSON :: IO (Maybe [Room])
[Room] -> IO [Room]
forall (m :: * -> *) a. Monad m => a -> m a
return [Room]
allRooms
noRoomsYet :: IO Bool
noRoomsYet :: IO Bool
noRoomsYet = [Room] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Room] -> Bool) -> IO [Room] -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [Room]
fetchRooms
saveRoom :: Room -> IO Bool
saveRoom :: Room -> IO Bool
saveRoom Room
newRoom = do
[Room]
allRooms <- IO [Room]
fetchRooms
let correspondingRooms :: [Room]
correspondingRooms = (Room -> Bool) -> [Room] -> [Room]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Room
room -> Room -> FilePath
code Room
room FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== Room -> FilePath
code Room
newRoom) [Room]
allRooms
if [Room] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Room]
correspondingRooms
then do {FilePath -> ByteString -> IO ()
BL.writeFile FilePath
roomsJSON (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ [Room] -> ByteString
forall a. ToJSON a => a -> ByteString
encode ([Room]
allRooms [Room] -> [Room] -> [Room]
forall a. [a] -> [a] -> [a]
++ [Room
newRoom]); Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True}
else Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
updateRoom :: String -> Room -> IO Bool
updateRoom :: FilePath -> Room -> IO Bool
updateRoom FilePath
codeRoom Room
newRoom = do
Bool
operate <- FilePath -> IO Bool
deleteRoom FilePath
codeRoom
Room -> IO Bool
saveRoom Room
newRoom
updateAllRooms :: (Room -> Room) -> IO Bool
updateAllRooms :: (Room -> Room) -> IO Bool
updateAllRooms Room -> Room
function = do
[Room]
allRooms <- IO [Room]
fetchRooms
let updated :: [Room]
updated = (Room -> Room) -> [Room] -> [Room]
forall a b. (a -> b) -> [a] -> [b]
map Room -> Room
function [Room]
allRooms
FilePath -> ByteString -> IO ()
BL.writeFile FilePath
roomsJSON (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ [Room] -> ByteString
forall a. ToJSON a => a -> ByteString
encode [Room]
updated
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
deleteRoom :: String -> IO Bool
deleteRoom :: FilePath -> IO Bool
deleteRoom FilePath
codeStr = do
[Room]
allRooms <- IO [Room]
fetchRooms
let removed :: [Room]
removed = (Room -> Bool) -> [Room] -> [Room]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Room
room -> Room -> FilePath
code Room
room FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
codeStr) [Room]
allRooms
if [Room]
allRooms [Room] -> [Room] -> Bool
forall a. Eq a => a -> a -> Bool
/= [Room]
removed
then do {FilePath -> ByteString -> IO ()
BL.writeFile FilePath
roomsJSON (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ [Room] -> ByteString
forall a. ToJSON a => a -> ByteString
encode [Room]
removed; Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True}
else Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
getRoom :: String -> IO (Maybe Room)
getRoom :: FilePath -> IO (Maybe Room)
getRoom FilePath
codeStr = do
[Room]
allRooms <- IO [Room]
fetchRooms
let corresponding :: [Room]
corresponding = (Room -> Bool) -> [Room] -> [Room]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Room
room -> Room -> FilePath
code Room
room FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
codeStr) [Room]
allRooms
if [Room] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Room]
corresponding
then Maybe Room -> IO (Maybe Room)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Room
forall a. Maybe a
Nothing
else Maybe Room -> IO (Maybe Room)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Room -> IO (Maybe Room)) -> Maybe Room -> IO (Maybe Room)
forall a b. (a -> b) -> a -> b
$ Room -> Maybe Room
forall a. a -> Maybe a
Just ([Room] -> Room
forall a. [a] -> a
head [Room]
corresponding)