1
1
{-# LANGUAGE ViewPatterns, TupleSections, RecordWildCards, ScopedTypeVariables, PatternGuards #-}
2
2
{-# LANGUAGE OverloadedStrings #-}
3
3
{-# LANGUAGE MultiWayIf #-}
4
- {-# OPTIONS_GHC -Wall #-}
4
+ {-# OPTIONS_GHC -Wall -Wno-incomplete-patterns -Wno-name-shadowing #-}
5
5
{-# LANGUAGE NamedFieldPuns #-}
6
6
7
7
module Action.Server (actionServer , actionReplay , action_server_test_ , action_server_test ) where
@@ -33,7 +33,7 @@ import System.Time.Extra
33
33
import Data.Time.Clock
34
34
import Data.Time.Calendar
35
35
import System.IO.Unsafe
36
- import Numeric.Extra hiding ( log )
36
+ import Numeric.Extra
37
37
import System.Info.Extra
38
38
39
39
import Output.Tags
@@ -48,7 +48,7 @@ import Action.Search
48
48
import Action.CmdLine
49
49
import Control.Applicative
50
50
import Data.Monoid
51
- import Prelude hiding ( log )
51
+ import Prelude
52
52
53
53
import qualified Data.Aeson as JSON
54
54
@@ -65,9 +65,9 @@ actionServer cmd@Server{..} = do
65
65
putStrLn . showDuration =<< time
66
66
_ <- evaluate spawned
67
67
dataDir <- maybe getDataDir pure datadir
68
- haddock' <- maybe (pure Nothing ) (fmap Just . canonicalizePath) haddock
68
+ haddock <- maybe (pure Nothing ) (fmap Just . canonicalizePath) haddock
69
69
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
71
71
actionServer _ = error " should not happen"
72
72
73
73
actionReplay :: CmdLine -> IO ()
@@ -83,7 +83,6 @@ actionReplay Replay{..} = withBuffering stdout NoBuffering $ do
83
83
evaluate $ rnf res
84
84
putChar ' .'
85
85
putStrLn $ " \n Took " ++ showDuration t ++ " (" ++ showDuration (t / intToDouble (repeat_ * length qs)) ++ " )"
86
- actionReplay _ = error " should not happen"
87
86
88
87
{-# NOINLINE spawned #-}
89
88
spawned :: UTCTime
@@ -111,9 +110,9 @@ replyServer log local links haddock store cdn home htmlDir scope Input{..} = cas
111
110
let (q2, results) = search store q
112
111
113
112
let urlOpts = if
114
- | Just _ <- haddock -> IsHaddockUrl
115
- | local -> IsLocalUrl
116
- | otherwise -> IsOtherUrl
113
+ | Just _ <- haddock -> HaddockUrl
114
+ | local -> LocalUrl
115
+ | otherwise -> OtherUrl
117
116
let body = showResults urlOpts links (filter ((/= " mode" ) . fst ) inputArgs) q2 $
118
117
takeAndGroup 25 (\ t -> t{targetURL= " " ,targetPackage= Nothing , targetModule= Nothing }) results
119
118
case lookup " mode" inputArgs of
@@ -154,8 +153,8 @@ replyServer log local links haddock store cdn home htmlDir scope Input{..} = cas
154
153
[" log" ] -> do
155
154
OutputHTML <$> templateRender templateLog []
156
155
[" 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 )]
159
158
[" stats" ] -> do
160
159
stats <- getStatsDebug
161
160
pure $ case stats of
@@ -210,7 +209,7 @@ takeAndGroup n key = f [] Map.empty
210
209
| otherwise = f (k: keys) (Map. insert k [x] mp) xs
211
210
where k = key x
212
211
213
- data UrlOpts = IsHaddockUrl | IsLocalUrl | IsOtherUrl
212
+ data UrlOpts = HaddockUrl | LocalUrl | OtherUrl
214
213
215
214
showResults :: UrlOpts -> Bool -> [(String , String )] -> [Query ] -> [[Target ]] -> Markup
216
215
showResults urlOpts links args query results = do
@@ -285,10 +284,10 @@ showFroms urlOpts targets = mconcat $ intersperse ", " $ flip map pkgs $ \pkg ->
285
284
pkgs = nubOrd $ map targetPackage targets
286
285
287
286
showURL :: 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
292
291
293
292
294
293
-------------------------------------------------------------
0 commit comments