{- This file is part of settings. - - Written in 2015 by fr33domlover . - - ♡ Copying is an act of love. Please copy, reuse and share. - - The author(s) have dedicated all copyright and related and neighboring - rights to this software to the public domain worldwide. This software is - distributed without any warranty. - - You should have received a copy of the CC0 Public Domain Dedication along - with this software. If not, see - . -} module Data.Settings.Route ( parseRoute , parseRoute' , showRoute , showRoute' ) where import Data.List (intercalate) import Data.Settings.Types -- | Split a path string into its components, if it's a valid path -- syntactically. parseRoute :: OptPath -> Maybe OptRoute parseRoute = parseRoute' '\\' '.' {-parseRoute "" = Just [] parseRoute s = case break (== '.') s of ("", _) -> Nothing (p, "") -> Just [p] (p, (c:cs)) -> case parseRoute cs of Nothing -> Nothing Just ps -> Just $ p : ps-} -- | Like 'parseRoute', but allows to choose the escape character (e.g. @'\'@) -- and the path separator character (e.g. @'.'@). parseRoute' :: Char -> Char -> OptPath -> Maybe OptRoute parseRoute' esc sep = f [] "" where f [] "" "" = Just [] f route "" "" = Nothing f route part "" = Just $ reverse $ reverse part : route f route part [c] | c == esc = Nothing | c == sep = Nothing | otherwise = f route (c : part) "" f route part (a:r@(b:s)) | a == esc && b == esc = f route (esc : part) s | a == esc && b == sep = f route (sep : part) s | a == esc = Nothing | a == sep = f (reverse part : route) "" r | otherwise = f route (a : part) r -- | Create a string representation of a path, with the parts separated by -- periods, and literal periods escaped using backslashes. showRoute :: OptRoute -> OptPath showRoute = showRoute' '\\' '.' -- | Like 'showRoute', but allows to choose the escape character (e.g. @'\\'@) -- and the path separator character (e.g. @'.'@). showRoute' :: Char -> Char -> OptRoute -> OptPath showRoute' esc sep = intercalate [sep] . map escape where escape = foldr f "" f c s | c == esc = esc : esc : s | c == sep = esc : sep : s | otherwise = c : s