{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Headroom.Data.Text
( read
, commonLinesPrefix
, replaceFirst
, mapLines
, mapLinesF
, fromLines
, toLines
)
where
import RIO
import qualified RIO.Text as T
import qualified RIO.Text.Partial as TP
commonLinesPrefix :: Text
-> Maybe Text
commonLinesPrefix :: Text -> Maybe Text
commonLinesPrefix Text
text = [Text] -> Maybe Text -> Maybe Text
go (Text -> [Text]
toLines Text
text) Maybe Text
forall a. Maybe a
Nothing
where
go :: [Text] -> Maybe Text -> Maybe Text
go [] Maybe Text
acc = Maybe Text
acc
go (Text
x : [Text]
xs) Maybe Text
Nothing = [Text] -> Maybe Text -> Maybe Text
go [Text]
xs (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
x)
go (Text
x : [Text]
xs) (Just Text
acc) = case Text -> Text -> Maybe (Text, Text, Text)
T.commonPrefixes Text
x Text
acc of
Just (Text
n, Text
_, Text
_) -> [Text] -> Maybe Text -> Maybe Text
go [Text]
xs (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
n)
Maybe (Text, Text, Text)
_ -> Maybe Text
forall a. Maybe a
Nothing
replaceFirst :: Text -> Text -> Text -> Text
replaceFirst :: Text -> Text -> Text -> Text
replaceFirst Text
ptrn Text
substitution Text
text | Text -> Bool
T.null Text
ptrn Bool -> Bool -> Bool
|| Text -> Bool
T.null Text
back = Text
text
| Bool
otherwise = Text
processed
where
(Text
front, Text
back) = Text -> Text -> (Text, Text)
TP.breakOn Text
ptrn Text
text
processed :: Text
processed = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
front, Text
substitution, Int -> Text -> Text
T.drop (Text -> Int
T.length Text
ptrn) Text
back]
mapLines :: (Text -> Text)
-> Text
-> Text
mapLines :: (Text -> Text) -> Text -> Text
mapLines Text -> Text
fn = (Text -> Maybe Text) -> Text -> Text
forall (t :: * -> *).
Foldable t =>
(Text -> t Text) -> Text -> Text
mapLinesF (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> (Text -> Text) -> Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text
fn)
mapLinesF :: Foldable t
=> (Text -> t Text)
-> Text
-> Text
mapLinesF :: (Text -> t Text) -> Text -> Text
mapLinesF Text -> t Text
f = [Text] -> Text
fromLines ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Text]] -> [Text]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Text]] -> [Text]) -> (Text -> [[Text]]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (t Text -> [Text]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (t Text -> [Text]) -> [t Text] -> [[Text]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ([t Text] -> [[Text]]) -> (Text -> [t Text]) -> Text -> [[Text]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [t Text]
go ([Text] -> [t Text]) -> (Text -> [Text]) -> Text -> [t Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
toLines
where
go :: [Text] -> [t Text]
go [] = []
go (Text
x : [Text]
xs) = Text -> t Text
f Text
x t Text -> [t Text] -> [t Text]
forall a. a -> [a] -> [a]
: [Text] -> [t Text]
go [Text]
xs
read :: Read a
=> Text
-> Maybe a
read :: Text -> Maybe a
read = String -> Maybe a
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe a) -> (Text -> String) -> Text -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
fromLines :: [Text]
-> Text
fromLines :: [Text] -> Text
fromLines = Text -> [Text] -> Text
T.intercalate Text
"\n"
toLines :: Text
-> [Text]
toLines :: Text -> [Text]
toLines Text
input | Text -> Bool
T.null Text
input = []
| Bool
otherwise = (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n') Text
input