Skip to content
Snippets Groups Projects
Commit 7ae97c33 authored by Iustin Pop's avatar Iustin Pop
Browse files

Make regex-pcre an optional dependency


This patch makes regex-pcre optional, allowing its disable via a
preprocessor define NO_REGEX_PCRE. This define will be added to
config.ac/Makefile.am in the next patch.

The patch also changes multi-line strings into string concatenation,
due to limitations with the CPP language extension.

Signed-off-by: default avatarIustin Pop <iustin@google.com>
Reviewed-by: default avatarGuido Trotter <ultrotter@google.com>
parent 45a36f36
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell, CPP #-}
{-| Implementation of the Ganeti Query2 language.
......@@ -57,7 +57,9 @@ import Data.Ratio (numerator, denominator)
import Text.JSON.Pretty (pp_value)
import Text.JSON.Types
import Text.JSON
#ifndef NO_REGEX_PCRE
import qualified Text.Regex.PCRE as PCRE
#endif
import qualified Ganeti.Constants as C
import Ganeti.THH
......@@ -111,6 +113,13 @@ $(makeJSONInstance ''ItemType)
-- * Sub data types for query2 queries and responses.
-- | Internal type of a regex expression (not exported).
#ifndef NO_REGEX_PCRE
type RegexType = PCRE.Regex
#else
type RegexType = ()
#endif
-- | List of requested fields.
type Fields = [ String ]
......@@ -175,8 +184,8 @@ readFilterArg :: (JSON a) =>
-> [JSValue] -- ^ Single argument
-> Result (Filter a)
readFilterArg constr [flt] = constr <$> readJSON flt
readFilterArg _ v = Error $ "Cannot deserialise field, expected [filter]\
\ but got " ++ show (pp_value (showJSON v))
readFilterArg _ v = Error $ "Cannot deserialise field, expected [filter]" ++
" but got " ++ show (pp_value (showJSON v))
-- | Helper to deserialise an array corresponding to a single field
-- and return the built filter.
......@@ -185,8 +194,9 @@ readFilterField :: (JSON a) =>
-> [JSValue] -- ^ Single argument
-> Result (Filter a)
readFilterField constr [field] = constr <$> readJSON field
readFilterField _ v = Error $ "Cannot deserialise field, expected [fieldname]\
\ but got " ++ show (pp_value (showJSON v))
readFilterField _ v = Error $ "Cannot deserialise field, expected" ++
" [fieldname] but got " ++
show (pp_value (showJSON v))
-- | Helper to deserialise an array corresponding to a field and
-- value, returning the built filter.
......@@ -197,8 +207,8 @@ readFilterFieldValue :: (JSON a, JSON b) =>
readFilterFieldValue constr [field, value] =
constr <$> readJSON field <*> readJSON value
readFilterFieldValue _ v =
Error $ "Cannot deserialise field/value pair, expected [fieldname, value]\
\ but got " ++ show (pp_value (showJSON v))
Error $ "Cannot deserialise field/value pair, expected [fieldname, value]" ++
" but got " ++ show (pp_value (showJSON v))
-- | Inner deserialiser for 'Filter'.
readFilterArray :: (JSON a) => String -> [JSValue] -> Result (Filter a)
......@@ -264,12 +274,12 @@ readFilterValue :: JSValue -> Result FilterValue
readFilterValue (JSString a) = Ok . QuotedString $ fromJSString a
readFilterValue (JSRational _ x) =
if denominator x /= 1
then Error $ "Cannot deserialise numeric filter value,\
\ expecting integral but\
\ got a fractional value: " ++ show x
then Error $ "Cannot deserialise numeric filter value," ++
" expecting integral but got a fractional value: " ++
show x
else Ok . NumericValue $ numerator x
readFilterValue v = Error $ "Cannot deserialise filter value, expecting\
\ string or integer, got " ++ show (pp_value v)
readFilterValue v = Error $ "Cannot deserialise filter value, expecting" ++
" string or integer, got " ++ show (pp_value v)
instance JSON FilterValue where
showJSON = showFilterValue
......@@ -280,19 +290,25 @@ instance JSON FilterValue where
-- we don't re-compile the regex at each match attempt.
data FilterRegex = FilterRegex
{ stringRegex :: String -- ^ The string version of the regex
, compiledRegex :: PCRE.Regex -- ^ The compiled regex
, compiledRegex :: RegexType -- ^ The compiled regex
}
-- | Builder for 'FilterRegex'. We always attempt to compile the
-- regular expression on the initialisation of the data structure;
-- this might fail, if the RE is not well-formed.
mkRegex :: (Monad m) => String -> m FilterRegex
#ifndef NO_REGEX_PCRE
mkRegex str = do
compiled <- case PCRE.getVersion of
Nothing -> fail "regex-pcre library compiled without\
\ libpcre, regex functionality not available"
Nothing -> fail $ "regex-pcre library compiled without" ++
" libpcre, regex functionality not available"
_ -> PCRE.makeRegexM str
return $ FilterRegex str compiled
#else
mkRegex _ =
fail $ "regex-pcre not found at compile time," ++
" regex functionality not available"
#endif
-- | 'Show' instance: we show the constructor plus the string version
-- of the regex.
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment