import Control.Monad ((<=<))
 import CssContentType
+import Data.ByteString.Lazy (ByteString(..))
 import GHC.Generics (Generic(..))
+import ImageContentType
 import Lucid
 import Servant
 import Servant.HTML.Lucid (HTML(..))
 import qualified Data.Text as T
 
 type Api = Styling :<|> Page
-type Page = ChangeTheme :<|> MainPage :<|> BlogPost
+type Page = ChangeTheme :<|> ImageLink :<|> MainPage :<|> BlogPost
 type MainPage = ThemeParam :> Get '[HTML] (Html ())
 type BlogPost = ThemeParam :> Capture "id" BlogId :> Get '[HTML] (Html ())
+type ImageLink = "image" :> Capture "id" ImageId :> Get '[PNG] ByteString
 type Styling = "style" :> ThemeParam :> Get '[CSS] C.Css
 type ChangeTheme = ReqBody '[FormUrlEncoded] Theme :> Capture "id" BlogId :> Post '[HTML] (Html ())
 type ThemeParam = QueryParam "theme" Theme
 
 type BlogId = FilePath
+type ImageId = FilePath
 
 data LightDark = Light | Dark deriving (Eq)
 
 
 import Control.Exception.Safe (SomeException)
 import Control.Monad (void)
 import Control.Monad.IO.Class (MonadIO(..), liftIO)
+import Data.ByteString.Lazy (ByteString(..))
 import Data.List (sort)
 import Data.Maybe (fromMaybe)
 import Lucid
 blogLink :: T.Text -> Maybe T.Text
 blogLink = T.stripSuffix markdownExtension
 
+imageNotFound :: (MonadIO m) => SomeException -> m ByteString
+imageNotFound _ = pure mempty
+
 blogNotFound :: (MonadIO m) => Maybe Theme -> BlogId -> SomeException -> m (Html ())
 blogNotFound theme blogId _ = htmlContainer theme Nothing $ do
   div_ [class_ "not-found"] $ do
 staticPath :: FilePath
 staticPath = "static/"
 
+imagePath :: FilePath
+imagePath = staticPath <> "img/"
+
 markdownExtension :: T.Text
 markdownExtension = ".md"
 
--- /dev/null
+module ImageContentType where
+
+import Data.ByteString.Lazy (ByteString(..))
+import Network.HTTP.Media ((//), (/:))
+import Servant
+
+data PNG
+
+instance Accept PNG where
+  contentType _ = "image" // "png"
+
+instance MimeRender PNG ByteString where
+  mimeRender _ val = val
 
 
 import ApiTypes
 import Control.Exception.Safe (handleAny)
-import Control.Monad ((<=<))
 import Control.Monad.IO.Class (liftIO)
 import Data.Maybe (fromMaybe)
 import Html
 import Servant
 import StyleSheet
 import qualified Clay as C
+import qualified Data.ByteString.Lazy as B
 import qualified Data.Text as T
 import qualified Data.Text.IO as T
 
 api = styling :<|> page
 
 page :: Server Page
-page = changeTheme :<|> mainPage :<|> blogPost
+page = changeTheme :<|> imageLink :<|> mainPage :<|> blogPost
 
 mainPage :: Maybe Theme -> Handler (Html ())
 mainPage = flip blogPost defaultBlogId
 changeTheme :: Theme -> BlogId -> Handler (Html ())
 changeTheme theme = blogPost (Just theme)
 
+imageLink :: ImageId -> Handler B.ByteString
+imageLink imageId = handleAny imageNotFound $ liftIO $ B.readFile $ imagePath <> imageId
+
 styling :: Maybe Theme -> Handler C.Css
 styling (fromMaybe defaultTheme -> theme) = pure $ getStyleFromTheme (themeType theme) $ C.rgba (themeRed theme) (themeGreen theme) (themeBlue theme) 1
 
 
 makeStyle colorAction themeColor = do
   html ? maxWidth (pct 100)
   bodyStyle colorAction themeColor
+  imageStyle
   paragraphStyle
   codeStyle
   headerStyle
   padding (rem 0.25) (rem 0.25) (rem 0.25) (rem 0.25)
   fontSize $ px 16
 
+imageStyle :: Css
+imageStyle = img ? do
+  display block
+  marginLeft auto
+  marginRight auto
+  width $ pct 100
+
 paragraphStyle :: Css
 paragraphStyle = p ? do
   fontSize $ rem 1