module Text.Regex.Do.Replace.Template
(Template(..),
ReplaceOne(),
Formatable) where
import Prelude as P hiding ((<),(>))
import Text.Regex.Do.Replace.Fast as S (replace)
import Text.Regex.Do.Type.Convert
import Data.ByteString as B
import Data.Text as T
type Formatable a = (Template a [a], Template a [(a,a)])
class Template a repl where
(<)::a -> repl -> a
(>)::repl -> a -> a
(>) repl0 :: repl
repl0 template0 :: a
template0 = a
template0 a -> repl -> a
forall a repl. Template a repl => a -> repl -> a
< repl
repl0
instance ReplaceOne Int a =>
Template a [a] where
< :: a -> [a] -> a
(<) t0 :: a
t0 a0 :: [a]
a0 = CustomerFn a a -> a -> [a] -> a
forall a b. CustomerFn a b -> b -> [a] -> b
foldr_idx CustomerFn a a
forall k v. ReplaceOne k v => v -> (k, v) -> v
foldFn_idx a
t0 [a]
a0
foldFn_idx::ReplaceOne k v =>
v -> (k, v) -> v
foldFn_idx :: v -> (k, v) -> v
foldFn_idx v0 :: v
v0 (i0 :: k
i0, body1 :: v
body1) = v -> k -> v -> v
forall idx a. ReplaceOne idx a => a -> idx -> a -> a
replaceOne v
body1 k
i0 v
v0
instance ReplaceOne a a =>
Template a [(a, a)] where
< :: a -> [(a, a)] -> a
(<) = ((a, a) -> a -> a) -> a -> [(a, a)] -> a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
P.foldr (a, a) -> a -> a
forall k v. ReplaceOne k v => (k, v) -> v -> v
foldFn_map
foldFn_map::ReplaceOne k v =>
(k, v) -> v -> v
foldFn_map :: (k, v) -> v -> v
foldFn_map (k0 :: k
k0, v0 :: v
v0) body1 :: v
body1 = v -> k -> v -> v
forall idx a. ReplaceOne idx a => a -> idx -> a -> a
replaceOne v
body1 k
k0 v
v0
type CustomerFn a b = (a -> (Int,b) -> b)
foldr_idx::CustomerFn a b -> b -> [a] -> b
foldr_idx :: CustomerFn a b -> b -> [a] -> b
foldr_idx fn0 :: CustomerFn a b
fn0 init1 :: b
init1 list0 :: [a]
list0 = b
b1
where i0 :: Int
i0 = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [a]
list0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1
(-1,b1 :: b
b1) = (a -> (Int, b) -> (Int, b)) -> (Int, b) -> [a] -> (Int, b)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
P.foldr (CustomerFn a b -> a -> (Int, b) -> (Int, b)
forall a b. CustomerFn a b -> a -> (Int, b) -> (Int, b)
foldFn CustomerFn a b
fn0) (Int
i0,b
init1) [a]
list0
foldFn::CustomerFn a b -> a -> (Int, b) -> (Int, b)
foldFn :: CustomerFn a b -> a -> (Int, b) -> (Int, b)
foldFn fn0 :: CustomerFn a b
fn0 val0 :: a
val0 t0 :: (Int, b)
t0@(i0 :: Int
i0, _) = (Int
i0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1, b
b1)
where b1 :: b
b1 = CustomerFn a b
fn0 a
val0 (Int, b)
t0
class ReplaceOne idx a where
replaceOne::a -> idx -> a -> a
instance ReplaceOne Int String where
replaceOne :: String -> Int -> String -> String
replaceOne body0 :: String
body0 k0 :: Int
k0 v0 :: String
v0 = ByteString -> String
toString ByteString
bs1
where pat1 :: ByteString
pat1 = String -> ByteString
toByteString (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ "{" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int -> String
forall a. Show a => a -> String
show Int
k0) String -> String -> String
forall a. [a] -> [a] -> [a]
++ "}"
repl1 :: ByteString
repl1 = String -> ByteString
toByteString String
v0
bs1 :: ByteString
bs1 = ByteString -> ByteString -> ByteString -> ByteString
S.replace ByteString
pat1 ByteString
repl1 (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ String -> ByteString
toByteString String
body0
instance ReplaceOne String String where
replaceOne :: String -> String -> String -> String
replaceOne body0 :: String
body0 k0 :: String
k0 v0 :: String
v0 = ByteString -> String
toString ByteString
bs1
where pat1 :: ByteString
pat1 = String -> ByteString
toByteString (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ "{" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
k0 String -> String -> String
forall a. [a] -> [a] -> [a]
++ "}"
repl1 :: ByteString
repl1 = String -> ByteString
toByteString String
v0
bs1 :: ByteString
bs1 = ByteString -> ByteString -> ByteString -> ByteString
S.replace ByteString
pat1 ByteString
repl1 (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ String -> ByteString
toByteString String
body0
instance ReplaceOne Int ByteString where
replaceOne :: ByteString -> Int -> ByteString -> ByteString
replaceOne body0 :: ByteString
body0 k0 :: Int
k0 v0 :: ByteString
v0 = ByteString -> ByteString -> ByteString -> ByteString
S.replace ByteString
pat1 ByteString
repl1 ByteString
body0
where pat1 :: ByteString
pat1 = String -> ByteString
toByteString (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ "{" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int -> String
forall a. Show a => a -> String
show Int
k0) String -> String -> String
forall a. [a] -> [a] -> [a]
++ "}"
repl1 :: ByteString
repl1 = ByteString
v0
instance ReplaceOne ByteString ByteString where
replaceOne :: ByteString -> ByteString -> ByteString -> ByteString
replaceOne body0 :: ByteString
body0 k0 :: ByteString
k0 v0 :: ByteString
v0 = ByteString -> ByteString -> ByteString -> ByteString
S.replace ByteString
pat1 ByteString
repl1 ByteString
body0
where pat1 :: ByteString
pat1 = [ByteString] -> ByteString
B.concat [String -> ByteString
toByteString "{", ByteString
k0, String -> ByteString
toByteString "}"]
repl1 :: ByteString
repl1 = ByteString
v0
instance ReplaceOne Int Text where
replaceOne :: Text -> Int -> Text -> Text
replaceOne body0 :: Text
body0 k0 :: Int
k0 v0 :: Text
v0 = Text -> Text -> Text -> Text
T.replace Text
pat1 Text
v0 Text
body0
where pat1 :: Text
pat1 = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ "{" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int -> String
forall a. Show a => a -> String
show Int
k0) String -> String -> String
forall a. [a] -> [a] -> [a]
++ "}"
instance ReplaceOne Text Text where
replaceOne :: Text -> Text -> Text -> Text
replaceOne body0 :: Text
body0 k0 :: Text
k0 v0 :: Text
v0 = Text -> Text -> Text -> Text
T.replace Text
pat1 Text
v0 Text
body0
where pat1 :: Text
pat1 = [Text] -> Text
T.concat [String -> Text
T.pack "{", Text
k0, String -> Text
T.pack "}"]