Skip to content

Commit

Permalink
Merge pull request #63 from jrp2014/master
Browse files Browse the repository at this point in the history
Some hlint cleanups
  • Loading branch information
robstewart57 authored Jan 23, 2019
2 parents 14e1b35 + 287b017 commit 4fd2edf
Show file tree
Hide file tree
Showing 18 changed files with 122 additions and 59 deletions.
65 changes: 65 additions & 0 deletions .hlint.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,65 @@
# HLint configuration file
# https://github.com/ndmitchell/hlint
##########################

# This file contains a template configuration file, which is typically
# placed as .hlint.yaml in the root of your project


# Specify additional command line arguments
#
# - arguments: [--color, --cpp-simple, -XQuasiQuotes]


# Control which extensions/flags/modules/functions can be used
#
# - extensions:
# - default: false # all extension are banned by default
# - name: [PatternGuards, ViewPatterns] # only these listed extensions can be used
# - {name: CPP, within: CrossPlatform} # CPP can only be used in a given module
#
# - flags:
# - {name: -w, within: []} # -w is allowed nowhere
#
# - modules:
# - {name: [Data.Set, Data.HashSet], as: Set} # if you import Data.Set qualified, it must be as 'Set'
# - {name: Control.Arrow, within: []} # Certain modules are banned entirely
#
# - functions:
# - {name: unsafePerformIO, within: []} # unsafePerformIO can only appear in no modules


# Add custom hints for this project
#
# Will suggest replacing "wibbleMany [myvar]" with "wibbleOne myvar"
# - error: {lhs: "wibbleMany [x]", rhs: wibbleOne x}


# Turn on hints that are off by default
#
# Ban "module X(module X) where", to require a real export list
# - warn: {name: Use explicit module export list}
#
# Replace a $ b $ c with a . b $ c
# - group: {name: dollar, enabled: true}
#
# Generalise map to fmap, ++ to <>
# - group: {name: generalise, enabled: true}


# Ignore some builtin hints
# - ignore: {name: Use let}
# - ignore: {name: Use const, within: SpecialModule} # Only within certain modules


# Define some custom infix operators
# - fixity: infixr 3 ~^#^~


# To generate a suitable file for HLint do:
# $ hlint --default > .hlint.yaml

- ignore: {name: Eta reduce}
- ignore: {name: Redundant bracket}
- ignore: {name: Reduce duplication}
- ignore: {name: Use camelCase}
4 changes: 2 additions & 2 deletions bench/MainCriterion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -150,8 +150,8 @@ addRemoveTriples lbl triples emptyGr populatedGr =

addTriples :: Rdf a => (Triples,RDF a) -> RDF a
addTriples (triples,emptyGr) =
foldr (\t g -> addTriple g t) emptyGr triples
foldr (flip addTriple) emptyGr triples

removeTriples :: Rdf a => (Triples,RDF a) -> RDF a
removeTriples (triples,populatedGr) =
foldr (\t g -> removeTriple g t) populatedGr triples
foldr (flip removeTriple) populatedGr triples
2 changes: 1 addition & 1 deletion src/Data/RDF/Graph/AdjHashMap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ instance Rdf AdjHashMap where
-- where subjPredMaps = HashMap.toList spoMap
-- in concatMap (\t -> show t ++ "\n") ts

showGraph' :: RDF AdjHashMap -> [Char]
showGraph' :: RDF AdjHashMap -> String
showGraph' ((AdjHashMap ((spoMap, _), _, _))) =
let ts = concatMap (uncurry tripsSubj) subjPredMaps
where subjPredMaps = HashMap.toList spoMap
Expand Down
2 changes: 1 addition & 1 deletion src/Data/RDF/Graph/HashMapSP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ instance Rdf HashSP where
-- let ts = (concatMap (\((s,p),oList) -> map (Triple s p) oList) . HashMap.toList) tsMap
-- in concatMap (\t -> show t ++ "\n") ts

showGraph' :: RDF HashSP -> [Char]
showGraph' :: RDF HashSP -> String
showGraph' (HashSP (tsMap,_,_)) =
let ts = (concatMap (\((s,p),oList) -> map (Triple s p) oList) . HashMap.toList) tsMap
in concatMap (\t -> show t ++ "\n") ts
Expand Down
2 changes: 1 addition & 1 deletion src/Data/RDF/Graph/TList.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,7 @@ instance Rdf TList where
query = query'
showGraph = showGraph'

showGraph' :: RDF TList -> [Char]
showGraph' :: RDF TList -> String
showGraph' gr = concatMap (\t -> show t ++ "\n") (expandTriples gr)

prefixMappings' :: RDF TList -> PrefixMappings
Expand Down
26 changes: 13 additions & 13 deletions src/Data/RDF/IRI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,12 +19,12 @@ module Data.RDF.IRI
) where

import Data.Semigroup (Semigroup(..))
import Data.Maybe (fromMaybe, isJust)
import Data.Maybe (maybe, isJust)
import Data.Functor
import Data.List (intersperse)
import Control.Applicative
import Control.Monad (guard)
import Control.Arrow ((***), (&&&), (>>>))
import Control.Arrow (first, (&&&), (>>>))
import Data.Char (isAlpha, isDigit, isAlphaNum, toUpper, toLower)
import Data.Text (Text)
import qualified Data.Text as T
Expand Down Expand Up @@ -95,18 +95,18 @@ data SchemaError
-- [TODO] use Builder
serializeIRI :: IRIRef -> Text
serializeIRI (IRIRef s a p q f) = mconcat
[ fromMaybe mempty (scheme <$> s)
, fromMaybe mempty (authority <$> a)
[ maybe mempty scheme s
, maybe mempty authority a
, path p
, fromMaybe mempty (query <$> q)
, fromMaybe mempty (fragment <$> f)]
, maybe mempty query q
, maybe mempty fragment f ]
where
scheme (Scheme s') = s' <> ":"
authority (Authority u (Host h) p') = mconcat
[ "//"
, fromMaybe mempty (userInfo <$> u)
, maybe mempty userInfo u
, h
, fromMaybe mempty (port <$> p') ]
, maybe mempty port p' ]
userInfo (UserInfo u) = u <> "@"
port (Port p') = (":" <>) . T.pack . show $ p'
path (Path p') = p'
Expand All @@ -123,7 +123,7 @@ parseRelIRI :: Text -> Either String IRIRef
parseRelIRI = P.parseOnly $ irelativeRefParser <* (P.endOfInput <?> "Unexpected characters at the end")

validateIRI :: Text -> Either String Text
validateIRI t = const t <$> parseIRI t
validateIRI t = t <$ parseIRI t

-- | IRI parsing and resolution according to algorithm 5.2 from RFC3986
-- See: http://www.ietf.org/rfc/rfc3986.txt
Expand Down Expand Up @@ -270,7 +270,7 @@ ipathRootlessParser' = mconcat <$> sequence [isegmentNzParser, ipathAbEmptyParse

-- ipath-empty = 0<ipchar>
ipathEmptyParser :: Parser (Maybe Authority, Path)
ipathEmptyParser = const (Nothing, mempty) <$> ipathEmptyParser'
ipathEmptyParser = (Nothing, mempty) <$ ipathEmptyParser'

ipathEmptyParser' :: Parser Text
ipathEmptyParser' = P.string mempty <?> "Empty path"
Expand Down Expand Up @@ -406,7 +406,7 @@ ipV6AddressParser = do
h16 = parseBetween 1 4 (P.takeWhile isHexaDigit)
ipNotElided (leading, lengthL) =
guard (lengthL == 7 && isDecOctet (last leading)) *> partialIpV4 <|>
guard (lengthL == 8) *> pure mempty
(guard (lengthL == 8) $> mempty)
ipElided (_, lengthL) = do
guard $ lengthL <= 8
elision <- P.string "::"
Expand Down Expand Up @@ -476,10 +476,10 @@ isSubDelims c = c `elem` ("!$&'()*+,;=" :: String)
iauthWithPathParser :: Parser (Maybe Authority, Path)
iauthWithPathParser = do
void (P.string "//")
curry (Just *** id) <$> iauthorityParser <*> ipathAbEmptyParser
curry (first Just) <$> iauthorityParser <*> ipathAbEmptyParser

isHexaDigit :: Char -> Bool
isHexaDigit c = (c >= '0' && c <= '9') ||
isHexaDigit c = (isDigit c) ||
(c >= 'a' && c <= 'f') ||
(c >= 'A' && c <= 'F')

Expand Down
3 changes: 2 additions & 1 deletion src/Data/RDF/Query.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ module Data.RDF.Query (

import Prelude hiding (pred)
import Data.List
import Data.Maybe (fromMaybe)
import Data.RDF.Types
import qualified Data.RDF.Namespace as NS
import Data.Text (Text)
Expand Down Expand Up @@ -156,7 +157,7 @@ expandNode _ n = n
-- Also expands "a" to "http://www.w3.org/1999/02/22-rdf-syntax-ns#type".
expandURI :: PrefixMappings -> Text -> Text
expandURI _ "a" = NS.mkUri NS.rdf "type"
expandURI pms iri = maybe iri id $ foldl' f Nothing (NS.toPMList pms)
expandURI pms iri = fromMaybe iri $ foldl' f Nothing (NS.toPMList pms)
where f :: Maybe Text -> (Text, Text) -> Maybe Text
f x (p, u) = x <|> (T.append u <$> T.stripPrefix (T.append p ":") iri)

Expand Down
12 changes: 5 additions & 7 deletions src/Data/RDF/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -188,7 +188,7 @@ uriValidate = either (const Nothing) Just . isRdfURI

-- |Same as 'uriValidate', but on 'String' rather than 'Text'
uriValidateString :: String -> Maybe String
uriValidateString = liftA T.unpack . uriValidate . fromString
uriValidateString = fmap T.unpack . uriValidate . fromString

isRdfURI :: Text -> Either ParseError Text
isRdfURI t = parse (iriFragment <* eof) ("Invalid URI: " ++ T.unpack t) t
Expand Down Expand Up @@ -624,12 +624,10 @@ canonicalizerTable =
doubleUri = "http://www.w3.org/2001/XMLSchema#double"

_integerStr, _decimalStr, _doubleStr :: Text -> Text
_integerStr t =
if T.length t == 1
then t
else if T.head t == '0'
then _integerStr (T.tail t)
else t
_integerStr t
| T.length t == 1 = t
| T.head t == '0' = _integerStr (T.tail t)
| otherwise = t

-- exponent: [eE] ('-' | '+')? [0-9]+
-- ('-' | '+') ? ( [0-9]+ '.' [0-9]* exponent | '.' ([0-9])+ exponent | ([0-9])+ exponent )
Expand Down
8 changes: 4 additions & 4 deletions src/Text/RDF/RDF4H/NTriplesParser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module Text.RDF.RDF4H.NTriplesParser

import Prelude hiding (readFile)
import Data.Semigroup ((<>))
import Data.Char (isDigit, isLetter, isAlphaNum)
import Data.Char (isDigit, isLetter, isAlphaNum, isAsciiUpper, isAsciiLower)
import Control.Applicative
import Control.Monad (void)

Expand All @@ -39,7 +39,7 @@ import System.IO (IOMode(..), withFile, hSetNewlineMode, noNewlineTranslation, h
-- class.
data NTriplesParser = NTriplesParser

data NTriplesParserCustom = NTriplesParserCustom Parser
newtype NTriplesParserCustom = NTriplesParserCustom Parser

-- |'NTriplesParser' is an instance of 'RdfParser' using parsec based parsers.
instance RdfParser NTriplesParser where
Expand Down Expand Up @@ -165,8 +165,8 @@ nt_blank_node_label = do
-- [157s] PN_CHARS_BASE ::= [A-Z] | [a-z] | [#x00C0-#x00D6] | [#x00D8-#x00F6] | [#x00F8-#x02FF] | [#x0370-#x037D] | [#x037F-#x1FFF] | [#x200C-#x200D] | [#x2070-#x218F] | [#x2C00-#x2FEF] | [#x3001-#xD7FF] | [#xF900-#xFDCF] | [#xFDF0-#xFFFD] | [#x10000-#xEFFFF]
nt_pn_chars_base :: CharParsing m => m Char
nt_pn_chars_base = try $ satisfy isBaseChar
where isBaseChar c = (c >= 'A' && c <= 'Z')
|| (c >= 'a' && c <= 'z')
where isBaseChar c = (isAsciiUpper c)
|| (isAsciiLower c)
|| (c >= '\x00C0' && c <= '\x00D6')
|| (c >= '\x00D8' && c <= '\x00F6')
|| (c >= '\x00F8' && c <= '\x02FF')
Expand Down
2 changes: 1 addition & 1 deletion src/Text/RDF/RDF4H/ParserUtils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ _parseURL parseFunc url = do
case ex of
(HttpExceptionRequest _req content) ->
case content of
ConnectionTimeout -> do
ConnectionTimeout ->
return $ errResult "Connection timed out"
_ -> return $ errResult ("HttpExceptionRequest content: " ++ show content)
(InvalidUrlException{}) ->
Expand Down
11 changes: 6 additions & 5 deletions src/Text/RDF/RDF4H/TurtleParser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ import Text.RDF.RDF4H.NTriplesParser
import Text.Parsec (runParser, ParseError)
import qualified Data.Text as T
import Data.Sequence (Seq, (|>))
import Data.Functor (($>))
import qualified Data.Foldable as F
import Control.Monad
import Text.Parser.Char
Expand Down Expand Up @@ -176,7 +177,7 @@ t_sparql_base = do
updateBaseUrl (Just $ Just newBaseIri)

t_verb :: (MonadState ParseState m, CharParsing m, LookAheadParsing m) => m ()
t_verb = try t_predicate <|> (char 'a' *> pure rdfTypeNode) >>= setPredicate
t_verb = try t_predicate <|> (char 'a' $> rdfTypeNode) >>= setPredicate

-- grammar rule: [11] predicate ::= iri
t_predicate :: (MonadState ParseState m, CharParsing m, LookAheadParsing m) => m Node
Expand All @@ -199,7 +200,7 @@ t_pn_local = do
xs <- option "" $ try $ do
let recsve = (t_pn_chars_str <|> string ":" <|> t_plx) <|>
(t_pn_chars_str <|> string ":" <|> t_plx <|> try (string "." <* lookAhead (try recsve))) <|>
(t_pn_chars_str <|> string ":" <|> t_plx <|> try (string "." *> notFollowedBy t_ws *> pure "."))
(t_pn_chars_str <|> string ":" <|> t_plx <|> try (string "." *> notFollowedBy t_ws $> "."))
concat <$> many recsve
pure (T.pack (x ++ xs))
where
Expand Down Expand Up @@ -235,7 +236,7 @@ t_subject = iri <|> t_blankNode <|> t_collection >>= setSubject
-- [137s] BlankNode ::= BLANK_NODE_LABEL | ANON
t_blankNode :: (CharParsing m, MonadState ParseState m) => m Node
t_blankNode = do
genID <- try t_blank_node_label <|> (t_anon *> pure mempty)
genID <- try t_blank_node_label <|> (t_anon $> mempty)
mp <- currGenIdLookup
maybe (newBN genID) getExistingBN (Map.lookup genID mp)
where
Expand Down Expand Up @@ -297,7 +298,7 @@ t_collection = withConstantSubjectPredicate $
void (many t_ws)
return root
where
empty_list = lookAhead (char ')') *> return rdfNilNode
empty_list = lookAhead (char ')') $> rdfNilNode
non_empty_list = do
ns <- sepEndBy1 element (some t_ws)
addTripleForObject rdfNilNode
Expand Down Expand Up @@ -507,7 +508,7 @@ updateBaseUrl val = _modifyState val no no no no no
-- combines get_current and increment into a single function
nextIdCounter :: MonadState ParseState m => m Integer
nextIdCounter = get >>= \(bUrl, dUrl, i, pms, s, p, ts, genMap) ->
put (bUrl, dUrl, i+1, pms, s, p, ts, genMap) *> pure i
put (bUrl, dUrl, i+1, pms, s, p, ts, genMap) $> i

nextBlankNode :: MonadState ParseState m => m Node
nextBlankNode = BNodeGen . fromIntegral <$> nextIdCounter
Expand Down
8 changes: 4 additions & 4 deletions src/Text/RDF/RDF4H/XmlParser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ instance RdfParser XmlParser where


-- |Global state for the parser
data GParseState = GParseState { stateGenId :: Int
newtype GParseState = GParseState { stateGenId :: Int
}
deriving(Show)

Expand All @@ -91,7 +91,7 @@ data LParseState = LParseState { stateBaseUrl :: BaseUrl
}
deriving(Show)

data ParserException = ParserException String
newtype ParserException = ParserException String
deriving (Show,Typeable)
instance Exception ParserException

Expand All @@ -102,7 +102,7 @@ instance Exception ParserException
-- Returns either a @ParseFailure@ or a new RDF containing the parsed triples.
parseFile' :: (Rdf a) => Maybe BaseUrl -> Maybe Text -> String -> IO (Either ParseFailure (RDF a))
parseFile' bUrl dUrl fpath =
TIO.readFile fpath >>= return . parseXmlRDF bUrl dUrl
parseXmlRDF bUrl dUrl <$> TIO.readFile fpath

-- |Parse the document at the given location URL as an XML document, using an optional @BaseUrl@
-- as the base URI, and using the given document URL as the URI of the XML document itself.
Expand Down Expand Up @@ -438,7 +438,7 @@ my_expandURI
-- |Make a UNode from an absolute string
mkUNode :: forall a. (ArrowIf a) => a String Node
mkUNode = choiceA [ (arr (isJust . unodeValidate . T.pack)) :-> (arr (unode . T.pack))
, arr (\_ -> True) :-> arr (\uri -> throw (ParserException ("Invalid URI: " ++ uri)))
, arr (const True) :-> arr (\uri -> throw (ParserException ("Invalid URI: " ++ uri)))
]

-- |Make a UNode from a rdf:ID element, expanding relative URIs
Expand Down
Loading

0 comments on commit 4fd2edf

Please sign in to comment.