summaryrefslogtreecommitdiff
path: root/Biz/Ibb
diff options
context:
space:
mode:
Diffstat (limited to 'Biz/Ibb')
-rw-r--r--Biz/Ibb/Client.hs1
-rw-r--r--Biz/Ibb/Core.hs6
-rw-r--r--Biz/Ibb/Influencers.hs2
-rw-r--r--Biz/Ibb/Keep.hs6
-rw-r--r--Biz/Ibb/Look.hs4
-rw-r--r--Biz/Ibb/Server.hs18
6 files changed, 14 insertions, 23 deletions
diff --git a/Biz/Ibb/Client.hs b/Biz/Ibb/Client.hs
index 89e0ffc..c3dae4b 100644
--- a/Biz/Ibb/Client.hs
+++ b/Biz/Ibb/Client.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NoImplicitPrelude #-}
diff --git a/Biz/Ibb/Core.hs b/Biz/Ibb/Core.hs
index 2c1fbae..007d835 100644
--- a/Biz/Ibb/Core.hs
+++ b/Biz/Ibb/Core.hs
@@ -83,7 +83,7 @@ data Action
deriving (Show, Eq)
home :: Model -> View Action
-home m = see m
+home = see
handlers :: Model -> View Action
handlers = home
@@ -134,7 +134,7 @@ seePerson person =
[]
[ a_
[ class_ "fab fa-twitter",
- href_ $ "https://twitter.com/" <> (ms $ _twitter person)
+ href_ $ "https://twitter.com/" <> ms (_twitter person)
]
[],
a_ [class_ "fas fa-globe", href_ $ ms $ _website person] []
@@ -151,7 +151,7 @@ seeBook book =
[]
[ a_
[ class_ "text-dark",
- href_ $ "https://www.amazon.com/dp/" <> (ms $ _amznref book)
+ href_ $ "https://www.amazon.com/dp/" <> ms (_amznref book)
]
[text $ ms $ _title book]
]
diff --git a/Biz/Ibb/Influencers.hs b/Biz/Ibb/Influencers.hs
index cf53cc0..08ce3e8 100644
--- a/Biz/Ibb/Influencers.hs
+++ b/Biz/Ibb/Influencers.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Biz.Ibb.Influencers where
diff --git a/Biz/Ibb/Keep.hs b/Biz/Ibb/Keep.hs
index d546aae..8ee1228 100644
--- a/Biz/Ibb/Keep.hs
+++ b/Biz/Ibb/Keep.hs
@@ -27,7 +27,7 @@ import qualified Data.Text as Text
-- * Keep
-- | Main database. Need to think of a better name for this.
-data IbbKeep
+newtype IbbKeep
= IbbKeep
{ _people :: IxSet Person
}
@@ -79,9 +79,7 @@ newPerson name blurb = do
}
getPeople :: Int -> Acid.Query IbbKeep [Person]
-getPeople n = do
- keep <- ask
- return $ take n $ IxSet.toList $ _people keep
+getPeople n = take n $ IxSet.toList $ _people keep </ ask
-- * Index @Book@
diff --git a/Biz/Ibb/Look.hs b/Biz/Ibb/Look.hs
index 1ab12c1..50cda9e 100644
--- a/Biz/Ibb/Look.hs
+++ b/Biz/Ibb/Look.hs
@@ -26,8 +26,8 @@ main = do
justifyContent center
flexDirection column
fontFamily ["GillSans", "Calibri", "Trebuchet"] [sansSerif]
- headings ? do
- fontFamily
+ headings
+ ? fontFamily
[ "Palatino",
"Palatino Linotype",
"Hoefler Text",
diff --git a/Biz/Ibb/Server.hs b/Biz/Ibb/Server.hs
index b5a7464..e87c55a 100644
--- a/Biz/Ibb/Server.hs
+++ b/Biz/Ibb/Server.hs
@@ -1,8 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE QuasiQuotes #-}
-{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE NoImplicitPrelude #-}
@@ -57,11 +55,11 @@ import System.Environment (lookupEnv)
main :: IO ()
main = do
say "rise: ibb"
- staticDir <- fromMaybe "static" <$> lookupEnv "STATIC_DIR" :: IO [Char]
- port <- read <$> fromMaybe "3000" <$> lookupEnv "PORT" :: IO Int
+ staticDir <- fromMaybe "static" <$> lookupEnv "STATIC_DIR" :: IO String
+ port <- (read . fromMaybe "3000" <$> lookupEnv "PORT") :: IO Int
keep <- Keep.openLocal "_keep/"
say "port: 3000"
- run port $ logStdout $ compress $ app staticDir $ keep
+ run port $ logStdout $ compress $ app staticDir keep
where
compress = gzip def {gzipFiles = GzipCompress}
@@ -75,8 +73,7 @@ instance L.ToHtml a => L.ToHtml (HtmlPage a) where
L.meta_ [L.charset_ "utf-8"]
jsRef "/static/ibb.js"
cssRef "/css/main.css"
- L.body_ $ do
- page
+ L.body_ page
where
page = L.toHtml x
jsRef href =
@@ -100,8 +97,7 @@ handle404 _ respond =
$ responseLBS status404 [("Content-Type", "text/html")]
$ renderBS
$ toHtml
- $ HtmlPage
- $ notfound
+ $ HtmlPage notfound
newtype CSS
= CSS
@@ -128,7 +124,7 @@ type Routes =
cssHandlers :: Server CssRoute
cssHandlers = return . Lazy.toStrict . Clay.render $ Look.main
-app :: [Char] -> AcidState Keep.IbbKeep -> Application
+app :: String -> AcidState Keep.IbbKeep -> Application
app staticDir keep =
serve (Proxy @Routes) $
static
@@ -137,7 +133,7 @@ app staticDir keep =
:<|> apiHandlers keep
:<|> Tagged handle404
where
- static = serveDirectoryWith (defaultWebAppSettings $ staticDir)
+ static = serveDirectoryWith (defaultWebAppSettings staticDir)
type ApiRoutes = "people" :> Get '[JSON] [Person]