--Cookbook.Recipes.Detect --Detect is a regex-like library with a defined standard, but in Recipes because it uses generic functions to implement them. module Cookbook.Recipes.Detect(represent,toRepex,strpex,strmatch,containingPattern,withPattern) where import Data.Maybe import qualified Cookbook.Ingredients.Lists.Access as Ac -- | Represent a list using symbols, and if it's not found, return Nothing. represent :: (Eq a) => [([a],b)] -> a -> (Maybe b) represent [] _ = Nothing represent ((a,b):c) item = if item `elem` a then (Just b) else represent c item -- | Filter maybes out, replacing Nothings with a failsafe "catch-all" toRepex :: (Eq a) => [([a],b)] -> [a] -> b-> [b] toRepex a b failsafe= map (\c -> case c of (Just x) -> x;_ -> failsafe) (map (represent a) b) --Standardized functions -- | Standard interface to "toRepex" for strings. strpex :: String -> String strpex x = toRepex [(['a'..'z'],'@'),(['A'..'Z'],'!'),(['0'..'9'],'#'),([':'..'@']++['\\'..'`']++[' '..'/'],'&')] x '_' -- | Does the string contain the standard strpex pattern? strmatch :: String -> String -> Bool strmatch x c = (strpex x) `Ac.contains` c -- | All lines containing this pattern containingPattern :: [String] -> String -> [String] containingPattern x c = filter (flip strmatch c) x -- | All patterns matching the pattern withPattern :: [String] -> String -> [String] withPattern [] _ = [] withPattern a@(x:xs) c = if strpex takeX == c then takeX : withPattern xs c else withPattern xs c where takeX = (take (length c) x)