11{-# LANGUAGE ViewPatterns, TupleSections, RecordWildCards, ScopedTypeVariables, PatternGuards #-}
22{-# LANGUAGE OverloadedStrings #-}
33{-# LANGUAGE MultiWayIf #-}
4- {-# OPTIONS_GHC -Wall #-}
4+ {-# OPTIONS_GHC -Wall -Wno-incomplete-patterns -Wno-name-shadowing #-}
55{-# LANGUAGE NamedFieldPuns #-}
66
77module Action.Server (actionServer , actionReplay , action_server_test_ , action_server_test ) where
@@ -33,7 +33,7 @@ import System.Time.Extra
3333import Data.Time.Clock
3434import Data.Time.Calendar
3535import System.IO.Unsafe
36- import Numeric.Extra hiding ( log )
36+ import Numeric.Extra
3737import System.Info.Extra
3838
3939import Output.Tags
@@ -48,7 +48,7 @@ import Action.Search
4848import Action.CmdLine
4949import Control.Applicative
5050import Data.Monoid
51- import Prelude hiding ( log )
51+ import Prelude
5252
5353import qualified Data.Aeson as JSON
5454
@@ -65,9 +65,9 @@ actionServer cmd@Server{..} = do
6565 putStrLn . showDuration =<< time
6666 _ <- evaluate spawned
6767 dataDir <- maybe getDataDir pure datadir
68- haddock' <- maybe (pure Nothing ) (fmap Just . canonicalizePath) haddock
68+ haddock <- maybe (pure Nothing ) (fmap Just . canonicalizePath) haddock
6969 withSearch database $ \ store ->
70- server log cmd $ replyServer log local links haddock' store cdn home (dataDir </> " html" ) scope
70+ server log cmd $ replyServer log local links haddock store cdn home (dataDir </> " html" ) scope
7171actionServer _ = error " should not happen"
7272
7373actionReplay :: CmdLine -> IO ()
@@ -83,7 +83,6 @@ actionReplay Replay{..} = withBuffering stdout NoBuffering $ do
8383 evaluate $ rnf res
8484 putChar ' .'
8585 putStrLn $ " \n Took " ++ showDuration t ++ " (" ++ showDuration (t / intToDouble (repeat_ * length qs)) ++ " )"
86- actionReplay _ = error " should not happen"
8786
8887{-# NOINLINE spawned #-}
8988spawned :: UTCTime
@@ -111,9 +110,9 @@ replyServer log local links haddock store cdn home htmlDir scope Input{..} = cas
111110 let (q2, results) = search store q
112111
113112 let urlOpts = if
114- | Just _ <- haddock -> IsHaddockUrl
115- | local -> IsLocalUrl
116- | otherwise -> IsOtherUrl
113+ | Just _ <- haddock -> HaddockUrl
114+ | local -> LocalUrl
115+ | otherwise -> OtherUrl
117116 let body = showResults urlOpts links (filter ((/= " mode" ) . fst ) inputArgs) q2 $
118117 takeAndGroup 25 (\ t -> t{targetURL= " " ,targetPackage= Nothing , targetModule= Nothing }) results
119118 case lookup " mode" inputArgs of
@@ -154,8 +153,8 @@ replyServer log local links haddock store cdn home htmlDir scope Input{..} = cas
154153 [" log" ] -> do
155154 OutputHTML <$> templateRender templateLog []
156155 [" log.js" ] -> do
157- log' <- displayLog <$> logSummary log
158- OutputJavascript <$> templateRender templateLogJs [(" data" ,html $ H. preEscapedString log' )]
156+ log <- displayLog <$> logSummary log
157+ OutputJavascript <$> templateRender templateLogJs [(" data" ,html $ H. preEscapedString log )]
159158 [" stats" ] -> do
160159 stats <- getStatsDebug
161160 pure $ case stats of
@@ -210,7 +209,7 @@ takeAndGroup n key = f [] Map.empty
210209 | otherwise = f (k: keys) (Map. insert k [x] mp) xs
211210 where k = key x
212211
213- data UrlOpts = IsHaddockUrl | IsLocalUrl | IsOtherUrl
212+ data UrlOpts = HaddockUrl | LocalUrl | OtherUrl
214213
215214showResults :: UrlOpts -> Bool -> [(String , String )] -> [Query ] -> [[Target ]] -> Markup
216215showResults urlOpts links args query results = do
@@ -285,10 +284,10 @@ showFroms urlOpts targets = mconcat $ intersperse ", " $ flip map pkgs $ \pkg ->
285284 pkgs = nubOrd $ map targetPackage targets
286285
287286showURL :: UrlOpts -> URL -> String
288- showURL IsHaddockUrl x = " haddock/" ++ dropPrefix " file:///" x
289- showURL IsLocalUrl (stripPrefix " file:///" -> Just x) = " file/" ++ x
290- showURL IsLocalUrl x = x
291- showURL IsOtherUrl x = x
287+ showURL HaddockUrl x = " haddock/" ++ dropPrefix " file:///" x
288+ showURL LocalUrl (stripPrefix " file:///" -> Just x) = " file/" ++ x
289+ showURL LocalUrl x = x
290+ showURL OtherUrl x = x
292291
293292
294293-------------------------------------------------------------
0 commit comments