Skip to content

Commit

Permalink
added custom curly expand
Browse files Browse the repository at this point in the history
  • Loading branch information
stastnypremysl committed Mar 28, 2021
1 parent 6d3d020 commit f89f0b2
Show file tree
Hide file tree
Showing 5 changed files with 343 additions and 84 deletions.
3 changes: 3 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@
# Revision history for curly-expander

## 0.3.0.0
* Added customCurlyExpand function.

## 0.2.0.3
* Improved README

Expand Down
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
# curly-expander
This is tool for curly brackets expanding, similar to bash curly expanding.
This is tool for curly brackets expanding, similar to bash curly expanding. It also contain an extended version of it.

Please refer to the package description on [Hackage](https://hackage.haskell.org/package/curly-expander-0.2.0.2/docs/Text-CurlyExpander.html) for more information.
288 changes: 208 additions & 80 deletions Text/CurlyExpander.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,21 @@ Maintainer : p-w@stty.cz
Stability : testing
Portability : POSIX
This is the main module of the curly-expander package.
This is the main (and only) module of the curly-expander package.
-}

{-# LANGUAGE OverloadedStrings #-}

module Text.CurlyExpander (curlyExpand) where
module Text.CurlyExpander
(
curlyExpand,
BackslashConfig (NoHandle, Preserve, Standard),
ExpandConfig (ExpandConfig, quotePairs, backslashConfig, persistQuotePairs, allowOneElementExpand),
defaultExpandConfig,
customCurlyExpand
)
where

import qualified Data.Text as T
import qualified Data.Text.Lazy as L
Expand All @@ -24,100 +32,222 @@ import Text.Parsec.Text

import Data.Char

-- | This configuration specify, how should be backslashes handled.
-- It is part of `ExpandConfig`.
data BackslashConfig =
-- | If no handle is used, then backslashes are not handled in any special way.
NoHandle |

cumulatorComma :: Parser [L.Text]
cumulatorComma = do
atoms <- (try p_range) <|> (try p_char_range) <|> p_atoms
return atoms

where
p_range :: Parser [L.Text]
p_range = do
nb1 <- many1 digit
_ <- string ".."
nb2 <- many1 digit
-- | If preserve is used, backslashes are processed, any backslashed char is processed as nonspecial char
-- and backslashes aren't deleted from result.
Preserve |

return$ map (toLazyText . decimal) $ get_range (read nb1) (read nb2)
where
get_range :: Int -> Int -> [Int]
get_range n1 n2
| n1 > n2 = reverse$ get_range n2 n1
| otherwise = [n1..n2]

p_char_range :: Parser [L.Text]
p_char_range = do
char1 <- anyChar
_ <- string ".."
char2 <- anyChar

return [ L.pack [p] | p <- get_range char1 char2 ]
where
get_range :: Char -> Char -> [Char]
get_range c1 c2
| n1 > n2 = reverse$ get_range c2 c1
| otherwise = map chr [n1..n2]
-- | If standard is used, backslashes are processed, any backslashed char is processed as nonspecial char
-- and backslashes are deleted from result.
Standard
deriving Eq

where
n1 = ord c1
n2 = ord c2

p_atoms :: Parser [L.Text]
p_atoms = do
molecule <- many1$ try p_atom
terminal_atom <- innerInputP
return $ (concat molecule) ++ terminal_atom
-- | The curly braces expand config.
-- It is used in `customCurlyExpand`.
data ExpandConfig = ExpandConfig {
-- | The configuration, which defines, how should be backslashes handled (\\)
backslashConfig :: BackslashConfig,

p_atom :: Parser [L.Text]
p_atom = do
-- | Quote pairs, which encloses a substrings, tells expander, that the substring shouldn't be expanded.
-- For example (\"[\", \"]\") pairs tells to expander, that anything inside [ANYTHING] shouldn't be expanded.
quotePairs :: [(String, String)],

atom <- innerInputP
_ <- char ','
return atom
-- | If true, quote pairs aren't deleted. Otherwise they are deleted from a result.
persistQuotePairs :: Bool,

-- | If true, curly brackets around one element will be deleted. Otherwise they are persisted.
allowOneElementExpand :: Bool
}

bracketP :: Parser [L.Text]
bracketP = do

_ <- char '{'
ret <- cumulatorComma
_ <- char '}'
-- | The default curly braces expand function config.
-- By default backslashes are not handeled, there are no quote pairs and one element expand is forbidden.
-- See the source code for details.
defaultExpandConfig :: ExpandConfig
defaultExpandConfig = ExpandConfig {
backslashConfig = NoHandle,
quotePairs = [],
persistQuotePairs = False,
allowOneElementExpand = False
}

return$ ret
-- | Custom curly braces (brackets) expand function.
-- It works in the same way as curlyExpand, bud accept custom configuration `ExpandConfig` in the first argument.

charP :: Parser [L.Text]
charP = do
c <- anyChar
return [L.pack [c]]
customCurlyExpand :: ExpandConfig -> T.Text -> [T.Text]
customCurlyExpand config input =
case parse inputP "bracket expansion"$ input of
Left _ -> [input]
Right ret -> map L.toStrict ret

nonSpecialCharP :: Parser [L.Text]
nonSpecialCharP = do
c <- noneOf ",}"
return [L.pack [c]]
where
cumulatorComma :: Parser [L.Text]
cumulatorComma = do
atoms <- (try p_range) <|> (try p_char_range) <|> p_atoms
return atoms

where
p_range :: Parser [L.Text]
p_range = do
nb1 <- many1 digit
_ <- string ".."
nb2 <- many1 digit

innerNonEmptyInputP :: Parser [L.Text]
innerNonEmptyInputP = do
molecule <- (try bracketP <|> nonSpecialCharP)
rest <- innerInputP
return$ map (toLazyText . decimal) $ get_range (read nb1) (read nb2)
where
get_range :: Int -> Int -> [Int]
get_range n1 n2
| n1 > n2 = reverse$ get_range n2 n1
| otherwise = [n1..n2]

p_char_range :: Parser [L.Text]
p_char_range = do
char1 <- anyChar
_ <- string ".."
char2 <- anyChar

return [ L.pack [p] | p <- get_range char1 char2 ]
where
get_range :: Char -> Char -> [Char]
get_range c1 c2
| n1 > n2 = reverse$ get_range c2 c1
| otherwise = map chr [n1..n2]

where
n1 = ord c1
n2 = ord c2

p_atoms :: Parser [L.Text]
p_atoms = do
molecule <- moleculeP
terminal_atom <- innerInputP
return $ (concat molecule) ++ terminal_atom

where
moleculeP :: Parser [[L.Text]]
moleculeP =
if allowOneElementExpand config; then
many (try p_atom)
else
many1 (try p_atom)

p_atom :: Parser [L.Text]
p_atom = do

atom <- innerInputP
_ <- char ','
return atom


bracketP :: Parser [L.Text]
bracketP = do

_ <- char '{'
ret <- cumulatorComma
_ <- char '}'

return$ ret

charP :: Parser [L.Text]
charP = do
c <- anyChar
return [L.pack [c]]

nonSpecialCharP :: Parser [L.Text]
nonSpecialCharP = do
c <- noneOf ",}"
return [L.pack [c]]

backslashedP :: Parser [L.Text]
backslashedP = do
if handleBackslash then do
_ <- char '\\'
c <- anyChar

return$ getReturnValue c
else do
unexpected "Char is not backslashed."

return [ L.append a b | a <- molecule, b <- rest ]
where
handleBackslash :: Bool
handleBackslash =
if backslashConfig config == NoHandle then
False
else
True

getReturnValue :: Char -> [L.Text]
getReturnValue c =
if backslashConfig config == Preserve then
[ L.pack ['\\', c] ]
else
[ L.pack [c] ]

specialQuotedP :: (String, String) -> Parser [L.Text]
specialQuotedP (lQuote,rQuote) = do
_ <- string lQuote
ret <- quoteNext

return$ [enrichReturnValue ret]
where
quoteClosure :: Parser L.Text
quoteClosure = do
_ <- string rQuote
return ""

quoteNextChar :: Parser L.Text
quoteNextChar = do
c <- anyChar
rest <- quoteNext
return$ L.pack [c] `L.append` rest

quoteNext :: Parser L.Text
quoteNext = (try quoteClosure <|> quoteNextChar)

enrichReturnValue :: L.Text -> L.Text
enrichReturnValue ret =
if persistQuotePairs config; then
(L.pack lQuote) `L.append` ret `L.append` (L.pack rQuote)
else
ret


quotedP :: [(String, String)] -> Parser [L.Text]
quotedP (quotes : rest) = (try$ specialQuotedP quotes) <|> quotedP rest
quotedP [] = unexpected "String is not quoted."

allQuotedP :: Parser [L.Text]
allQuotedP = quotedP$ quotePairs config

innerInputP :: Parser [L.Text]
innerInputP = (innerNonEmptyInputP <|> emptyInputP)
innerNonEmptyInputP :: Parser [L.Text]
innerNonEmptyInputP = do
molecule <- (backslashedP <|> try allQuotedP <|> try bracketP <|> nonSpecialCharP)
rest <- innerInputP

nonEmptyInputP :: Parser [L.Text]
nonEmptyInputP = do
molecule <- (try bracketP <|> charP)
rest <- inputP
return [ L.append a b | a <- molecule, b <- rest ]

return [ L.append a b | a <- molecule, b <- rest ]
innerInputP :: Parser [L.Text]
innerInputP = (innerNonEmptyInputP <|> emptyInputP)

emptyInputP :: Parser [L.Text]
emptyInputP = do
return [""]
nonEmptyInputP :: Parser [L.Text]
nonEmptyInputP = do
molecule <- (backslashedP <|> try allQuotedP <|> try bracketP <|> charP)
rest <- inputP

inputP :: Parser [L.Text]
inputP = (nonEmptyInputP <|> emptyInputP)

return [ L.append a b | a <- molecule, b <- rest ]

emptyInputP :: Parser [L.Text]
emptyInputP = do
return [""]

inputP :: Parser [L.Text]
inputP = (nonEmptyInputP <|> emptyInputP)

-- | Curly braces (brackets) expand function
--
Expand All @@ -141,7 +271,5 @@ inputP = (nonEmptyInputP <|> emptyInputP)

curlyExpand :: T.Text -> [T.Text]
curlyExpand input =
case parse inputP "bracket expansion"$ input of
Left _ -> [input]
Right ret -> map L.toStrict ret
customCurlyExpand defaultExpandConfig input

11 changes: 8 additions & 3 deletions curly-expander.cabal
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
cabal-version: 3.0

name: curly-expander
version: 0.2.0.3
version: 0.3.0.0
synopsis: Curly braces (brackets) expanding
description: A library for curly braces (brackets) expanding - similar to bash curly expanding
description: A library for curly braces (brackets) expanding - similar to bash curly expanding. It also contain an extended version of it.

license: LGPL-3.0-only
license-file: LICENSE
Expand Down Expand Up @@ -47,11 +47,16 @@ test-suite nested-case-test
main-is: NestedCaseTest.hs
type: exitcode-stdio-1.0

test-suite custom-case-test
import: tests
main-is: CustomCaseTest.hs
type: exitcode-stdio-1.0

source-repository head
type: git
location: https://github.com/stastnypremysl/curly-expander

source-repository this
type: git
location: https://github.com/stastnypremysl/curly-expander
tag: 0.2.0.3
tag: 0.3.0.0
Loading

0 comments on commit f89f0b2

Please sign in to comment.