~alcinnz/rhapsode

49f5059152b74d220f8673d9c7ae35a3ab484c44 — Adrian Cochrane 3 years ago 2b90b1d
Bundle readStrict implementation.
4 files changed, 8 insertions(+), 7 deletions(-)

M src/Input.hs
M src/Links.hs
M src/Render.hs
M src/Types.hs
M src/Input.hs => src/Input.hs +1 -1
@@ 1,7 1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE PatternSynonyms, ViewPatterns #-}
module Input(fetchDocument, pageForText, applyCSScharset) where
module Input(fetchDocument, pageForText, applyCSScharset, readStrict) where

import           Data.Text.Lazy (fromStrict)
import qualified Data.Text as Txt

M src/Links.hs => src/Links.hs +1 -1
@@ 166,7 166,7 @@ updateSuggestions page = do
    let path = dir </> "suggestions.gmni"
    exists <- doesFileExist path
    suggestions <- if not exists then return [] else do
        file <- Prelude.readFile path
        file <- readStrict path
        return [line' | line <- lines file, line'@(_:uri':_) <- [words line], not (pack uri' `Set.member` visitedURLs page)]

    let suggestions' = suggestions ++ nub [["=>", uri', domain] | link <- links,

M src/Render.hs => src/Render.hs +0 -1
@@ 12,7 12,6 @@ import Data.FileEmbed

import Data.Maybe (fromMaybe, maybeToList)
import Text.Read (readMaybe)
import Debug.Trace (trace)

--- External Rhapsode subcomponents
import qualified Data.CSS.Syntax.StyleSheet as CSS

M src/Types.hs => src/Types.hs +6 -4
@@ 1,5 1,5 @@
{-# LANGUAGE OverloadedStrings #-}
module Types(CArray, Page(..), Application(..), buildDirFile) where
module Types(CArray, Page(..), Application(..), buildDirFile, readStrict) where

import System.Directory (getCurrentDirectory) -- default referer URI
import SpeechStyle (SpeechStyle)


@@ 49,11 49,13 @@ loadVisited = do
    exists <- doesFileExist path

    if exists then do
        file <- Prelude.readFile path -- Can't leave this file locked when I'll shortly append to it!
        let hist = length file `seq` Set.fromList [Txt.pack uri | _:uri:_ <- map words $ lines file]
        hist `par` return hist
        file <- readStrict path
        let hist = Set.fromList [Txt.pack uri | _:uri:_ <- map words $ lines file]
        return hist
    else return Set.empty

readStrict path = do s <- Prelude.readFile path; length s `seq` return s

c_initialReferer = do
    cwd <- getCurrentDirectory
    hist <- loadVisited