Skip to content

Commit

Permalink
Rename module names
Browse files Browse the repository at this point in the history
Problem: module names are prefixed with `Crv` which does not suit the
new project naming.

Solution: following the new `xrefcheck` name, rename modules so that
they start from `Xrefcheck`.
  • Loading branch information
Martoon-00 committed Jan 14, 2020
1 parent fd949bc commit 0c1d453
Show file tree
Hide file tree
Showing 14 changed files with 45 additions and 45 deletions.
12 changes: 6 additions & 6 deletions exec/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,12 +10,12 @@ import Data.Yaml (decodeFileEither, prettyPrintParseException)
import Fmt (blockListF', build, fmt, fmtLn, indentF)
import System.Directory (doesFileExist)

import Crv.CLI
import Crv.Config
import Crv.Progress
import Crv.Scan
import Crv.Scanners
import Crv.Verify
import Xrefcheck.CLI
import Xrefcheck.Config
import Xrefcheck.Progress
import Xrefcheck.Scan
import Xrefcheck.Scanners
import Xrefcheck.Verify

formats :: FormatsSupport
formats = specificFormatsSupport
Expand Down
6 changes: 3 additions & 3 deletions src/Crv/CLI.hs → src/Xrefcheck/CLI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@

{-# LANGUAGE ApplicativeDo #-}

module Crv.CLI
module Xrefcheck.CLI
( VerifyMode (..)
, shouldCheckLocal
, shouldCheckExternal
Expand All @@ -21,7 +21,7 @@ import Options.Applicative (Parser, ReadM, command, eitherReader, execParser, fu
short, strOption, switch, value)
import Paths_xrefcheck (version)

import Crv.Core
import Xrefcheck.Core

modeReadM :: ReadM VerifyMode
modeReadM = eitherReader $ \s ->
Expand Down Expand Up @@ -109,7 +109,7 @@ totalParser = asum
]

versionOption :: Parser (a -> a)
versionOption = infoOption ("xrefcheck-" <> (showVersion version)) $
versionOption = infoOption ("xrefcheck-" <> showVersion version) $
long "version" <>
help "Show version."

Expand Down
4 changes: 2 additions & 2 deletions src/Crv/Config.hs → src/Xrefcheck/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@

{-# OPTIONS_GHC -fno-warn-orphans #-}

module Crv.Config where
module Xrefcheck.Config where

import Data.Aeson.Options (defaultOptions)
import Data.Aeson.TH (deriveFromJSON)
Expand All @@ -16,7 +16,7 @@ import System.FilePath.Posix ((</>))
import TH.RelativePaths (qReadFileBS)
import Time (KnownRatName, Second, Time, unitsP)

import Crv.System (CanonicalizedGlobPattern)
import Xrefcheck.System (CanonicalizedGlobPattern)

-- | Overall config.
data Config = Config
Expand Down
6 changes: 3 additions & 3 deletions src/Crv/Core.hs → src/Xrefcheck/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@

-- | Various primitives.

module Crv.Core where
module Xrefcheck.Core where

import Control.DeepSeq (NFData)
import Control.Lens (makeLenses, (%=))
Expand All @@ -22,8 +22,8 @@ import System.Console.Pretty (Color (..), Style (..), color, style)
import System.FilePath.Posix (isPathSeparator, pathSeparator)
import Text.Numeral.Roman (toRoman)

import Crv.Progress
import Crv.Util
import Xrefcheck.Progress
import Xrefcheck.Util

-----------------------------------------------------------
-- Types
Expand Down
6 changes: 3 additions & 3 deletions src/Crv/Progress.hs → src/Xrefcheck/Progress.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
-}

-- | Printing progress bars.
module Crv.Progress
module Xrefcheck.Progress
( -- * Progress
Progress (..)
, initProgress
Expand All @@ -30,9 +30,9 @@ import Time (ms, threadDelay)
data Progress a = Progress
{ pCurrent :: a
-- ^ How much has been completed.
, pTotal :: a
, pTotal :: a
-- ^ Overall amount of work.
, pErrors :: !a
, pErrors :: !a
-- ^ How many of the completed work finished with an error.
} deriving (Show)

Expand Down
10 changes: 5 additions & 5 deletions src/Crv/Scan.hs → src/Xrefcheck/Scan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@

-- | Generalised repo scanner and analyser.

module Crv.Scan
module Xrefcheck.Scan
( Extension
, ScanAction
, FormatsSupport
Expand All @@ -21,10 +21,10 @@ import GHC.Err (errorWithoutStackTrace)
import qualified System.Directory.Tree as Tree
import System.FilePath.Posix (takeDirectory, takeExtension, (</>))

import Crv.Config
import Crv.Core
import Crv.Progress
import Crv.Util ()
import Xrefcheck.Config
import Xrefcheck.Core
import Xrefcheck.Progress
import Xrefcheck.Util ()

-- | File extension, dot included.
type Extension = String
Expand Down
File renamed without changes.
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@

-- | Markdown documents markdownScanner.

module Crv.Scanners.Markdown
module Xrefcheck.Scanners.Markdown
( markdownScanner
, markdownSupport
) where
Expand All @@ -21,8 +21,8 @@ import qualified Data.Text.Lazy as LT
import Fmt (Buildable (..), blockListF, nameF, (+|), (|+))
import GHC.Conc (par)

import Crv.Core
import Crv.Scan
import Xrefcheck.Core
import Xrefcheck.Scan

instance Buildable Node where
build (Node _mpos ty subs) = nameF (show ty) $ blockListF subs
Expand Down
2 changes: 1 addition & 1 deletion src/Crv/System.hs → src/Xrefcheck/System.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
- SPDX-License-Identifier: MPL-2.0
-}

module Crv.System
module Xrefcheck.System
( readingSystem
, CanonicalizedGlobPattern (..)
) where
Expand Down
2 changes: 1 addition & 1 deletion src/Crv/Util.hs → src/Xrefcheck/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@

{-# OPTIONS_GHC -fno-warn-orphans #-}

module Crv.Util
module Xrefcheck.Util
( nameF'
, paren
) where
Expand Down
24 changes: 12 additions & 12 deletions src/Crv/Verify.hs → src/Xrefcheck/Verify.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@
{-# LANGUAGE PartialTypeSignatures #-}
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}

module Crv.Verify
module Xrefcheck.Verify
( -- * General verification
VerifyResult (..)
, verifyOk
Expand All @@ -17,7 +17,7 @@ module Crv.Verify
, WithReferenceLoc (..)

-- * Cross-references validation
, CrvVerifyError (..)
, VerifyError (..)
, verifyRepo
, checkExternalResource
) where
Expand All @@ -39,10 +39,10 @@ import qualified System.FilePath.Glob as Glob
import System.FilePath.Posix (takeDirectory, (</>))
import Time (RatioNat, Second, Time (..), ms, threadDelay, timeout)

import Crv.Config
import Crv.Core
import Crv.Progress
import Crv.System
import Xrefcheck.Config
import Xrefcheck.Core
import Xrefcheck.Progress
import Xrefcheck.System

{-# ANN module ("HLint: ignore Use uncurry" :: Text) #-}
{-# ANN module ("HLint: ignore Use 'runExceptT' from Universum" :: Text) #-}
Expand Down Expand Up @@ -89,7 +89,7 @@ instance Buildable a => Buildable (WithReferenceLoc a) where
"In file " +| style Faint (style Bold wrlFile) |+ "\nbad " +| wrlReference |+ "\n"
+| wrlItem |+ "\n\n"

data CrvVerifyError
data VerifyError
= FileDoesNotExist FilePath
| AnchorDoesNotExist Text [Anchor]
| AmbiguousAnchorRef FilePath Text (NonEmpty Anchor)
Expand All @@ -98,7 +98,7 @@ data CrvVerifyError
| ExternalResourceSomeError Text
deriving (Show)

instance Buildable CrvVerifyError where
instance Buildable VerifyError where
build = \case
FileDoesNotExist file ->
"⛀ File does not exist:\n " +| file |+ "\n"
Expand Down Expand Up @@ -131,7 +131,7 @@ verifyRepo
-> VerifyMode
-> FilePath
-> RepoInfo
-> IO (VerifyResult $ WithReferenceLoc CrvVerifyError)
-> IO (VerifyResult $ WithReferenceLoc VerifyError)
verifyRepo rw config@VerifyConfig{..} mode root repoInfo'@(RepoInfo repoInfo) = do
let toScan = do
(file, fileInfo) <- M.toList repoInfo
Expand Down Expand Up @@ -163,7 +163,7 @@ verifyReference
-> FilePath
-> FilePath
-> Reference
-> IO (VerifyResult $ WithReferenceLoc CrvVerifyError)
-> IO (VerifyResult $ WithReferenceLoc VerifyError)
verifyReference config@VerifyConfig{..} mode progressRef (RepoInfo repoInfo)
root fileWithReference ref@Reference{..} = do

Expand Down Expand Up @@ -244,7 +244,7 @@ verifyReference config@VerifyConfig{..} mode progressRef (RepoInfo repoInfo)

checkExternalResource :: VerifyConfig
-> Text
-> IO (VerifyResult CrvVerifyError)
-> IO (VerifyResult VerifyError)
checkExternalResource VerifyConfig{..} link
| doesReferLocalhost = return mempty
| otherwise = fmap toVerifyRes $ do
Expand All @@ -254,7 +254,7 @@ checkExternalResource VerifyConfig{..} link
where
doesReferLocalhost = any (`T.isInfixOf` link) ["://localhost", "://127.0.0.1"]

makeRequest :: _ => method -> RatioNat -> IO (Either CrvVerifyError ())
makeRequest :: _ => method -> RatioNat -> IO (Either VerifyError ())
makeRequest method timeoutFrac = runExceptT $ do
parsedUrl <- parseUrl (encodeUtf8 link)
& maybe (throwError ExternalResourceInvalidUri) pure
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,12 @@
- SPDX-License-Identifier: MPL-2.0
-}

module Test.Crv.AnchorsSpec where
module Test.Xrefcheck.AnchorsSpec where

import Test.Hspec (Spec, describe, it)
import Test.QuickCheck ((===))

import Crv.Core (headerToAnchor)
import Xrefcheck.Core (headerToAnchor)

spec :: Spec
spec = do
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,12 @@
- SPDX-License-Identifier: MPL-2.0
-}

module Test.Crv.ConfigSpec where
module Test.Xrefcheck.ConfigSpec where

import Test.Hspec (Spec, it)
import Test.QuickCheck (ioProperty, once)

import Crv.Config
import Xrefcheck.Config

spec :: Spec
spec =
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,12 @@
- SPDX-License-Identifier: MPL-2.0
-}

module Test.Crv.LocalSpec where
module Test.Xrefcheck.LocalSpec where

import Test.Hspec (Spec, describe, it)
import Test.QuickCheck ((===))

import Crv.Core (canonizeLocalRef)
import Xrefcheck.Core (canonizeLocalRef)

spec :: Spec
spec = do
Expand Down

0 comments on commit 0c1d453

Please sign in to comment.