Split source file rendering into separate module

This commit is contained in:
fr33domlover 2016-04-13 06:55:39 +00:00
parent 2323ec3fc0
commit b42d9db432
4 changed files with 61 additions and 27 deletions

View file

@ -58,8 +58,6 @@ import Database.Esqueleto
import Data.Hourglass (timeConvert) import Data.Hourglass (timeConvert)
import System.Directory (createDirectoryIfMissing) import System.Directory (createDirectoryIfMissing)
import System.Hourglass (dateCurrent) import System.Hourglass (dateCurrent)
import Text.Highlighter (lexerFromFilename, runLexer, Lexer (lName))
import Text.Highlighter.Formatters.Html (format)
import qualified Data.DList as D import qualified Data.DList as D
import qualified Data.Set as S (member) import qualified Data.Set as S (member)
@ -71,6 +69,7 @@ import Vervis.Foundation
import Vervis.Git (timeAgo') import Vervis.Git (timeAgo')
import Vervis.Path import Vervis.Path
import Vervis.Model import Vervis.Model
import Vervis.Render
import Vervis.Settings import Vervis.Settings
import Vervis.Style import Vervis.Style
@ -169,26 +168,8 @@ getRepoSource repository user repo ref dir = do
, toText $ toBytes name , toText $ toBytes name
) )
display <- case view of display <- case view of
Left b -> Left b -> return $ Left $
let lbs = blobGetContent b renderSource (unpack $ last dir) (blobGetContent b)
bs = toStrict lbs
in Left <$>
case lexerFromFilename $ unpack $ last dir of
Nothing -> return $ Left $ toTextL lbs
Just lexer ->
case runLexer lexer bs of
Left err -> do
$logWarn $ mconcat
[ "Failed to highlight "
, ref
, " :: "
, intercalate "/" dir
, " with lexer "
, pack $ lName lexer
]
return $ Left $ toTextL lbs
Right tokens ->
return $ Right $ format True tokens
Right v -> return $ Right $ map mkrow v Right v -> return $ Right $ map mkrow v
let parent = if null dir then [] else init dir let parent = if null dir then [] else init dir
dirs = zip parent (tail $ inits parent) dirs = zip parent (tail $ inits parent)

54
src/Vervis/Render.hs Normal file
View file

@ -0,0 +1,54 @@
{- This file is part of Vervis.
-
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
-
- Copying is an act of love. Please copy, reuse and share.
-
- The author(s) have dedicated all copyright and related and neighboring
- rights to this software to the public domain worldwide. This software is
- distributed without any warranty.
-
- You should have received a copy of the CC0 Public Domain Dedication along
- with this software. If not, see
- <http://creativecommons.org/publicdomain/zero/1.0/>.
-}
-- | Tools for rendering repository file contents and other source files.
module Vervis.Render
( renderSource
)
where
import Prelude
import Control.Monad.Logger (logWarn)
import Data.ByteString.Lazy (ByteString, toStrict)
import Data.Text (pack)
import Data.Text.Encoding.Error (lenientDecode)
import Data.Text.Lazy.Encoding (decodeUtf8With)
import Text.Highlighter (lexerFromFilename, runLexer, Lexer (lName))
import Text.Highlighter.Formatters.Html (format)
import Yesod.Core.Widget (whamlet, toWidget)
import Vervis.Foundation (Widget)
renderSource :: FilePath -> ByteString -> Widget
renderSource name content =
let raw =
[whamlet|
<pre>
<code>#{decodeUtf8With lenientDecode content}
|]
in case lexerFromFilename name of
Nothing -> raw
Just lexer ->
case runLexer lexer $ toStrict content of
Left err -> do
$logWarn $ mconcat
[ "Failed to highlight "
, pack name
, " with lexer "
, pack $ lName lexer
]
raw
Right tokens -> toWidget $ format True tokens

View file

@ -39,11 +39,8 @@ $forall (piece, piecePath) <- dirs
<span>/ <span>/
<h2>#{title} <h2>#{title}
$case display $case display
$of Left (Left plain) $of Left source
<pre> ^{source}
<code>#{plain}
$of Left (Right highlighted)
#{highlighted}
$of Right rows $of Right rows
<table> <table>
<tr> <tr>

View file

@ -53,6 +53,8 @@ library
Vervis.Import Vervis.Import
Vervis.Import.NoFoundation Vervis.Import.NoFoundation
Vervis.Model Vervis.Model
Vervis.Readme
Vervis.Render
Vervis.Settings Vervis.Settings
Vervis.Settings.StaticFiles Vervis.Settings.StaticFiles
Vervis.Handler.Common Vervis.Handler.Common