Created
April 19, 2020 21:53
-
-
Save ChrisPenner/4b77aa2590f51050c92178ae4eacc174 to your computer and use it in GitHub Desktop.
Optics for doing some text manipulation
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE OverloadedStrings #-} | |
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE QuasiQuotes #-} | |
{-# LANGUAGE FlexibleContexts #-} | |
module Lib where | |
import Control.Lens | |
import Control.Applicative | |
import qualified Data.Text as T | |
import Data.Function (on) | |
import Data.Char (isSpace) | |
import Text.RawString.QQ (r) | |
-- takingN :: Int -> Traversal' T.Text T.Text | |
-- takingN n handler txt = | |
-- liftA2 (<>) (handler prefix) (pure suffix) | |
-- where | |
-- (prefix, suffix) = T.splitAt n txt | |
-- droppingN :: Int -> Traversal' T.Text T.Text | |
-- droppingN n handler txt = | |
-- liftA2 (<>) (pure prefix) (handler suffix) | |
-- where | |
-- (prefix, suffix) = T.splitAt n txt | |
takingN :: Int -> Traversal' T.Text T.Text | |
takingN n = splittingAt n . _1 | |
droppingN :: Int -> Traversal' T.Text T.Text | |
droppingN n = splittingAt n . _2 | |
splittingAt :: Int -> Iso' T.Text (T.Text, T.Text) | |
splittingAt n = iso to' from' | |
where | |
to' :: T.Text -> (T.Text, T.Text) | |
to' = T.splitAt n | |
from' :: (T.Text, T.Text) -> T.Text | |
from' (a, b) = a <> b | |
-- spacePreservingWords :: Applicative f => (T.Text -> f T.Text) -> T.Text -> f T.Text | |
words' :: Traversal' T.Text T.Text | |
words' = splitOnPredicate isSpace | |
splitOnPredicate :: (Char -> Bool) -> IndexedTraversal' Int T.Text T.Text | |
splitOnPredicate p = indexing (collecting . traversed . _Right) | |
where | |
collecting :: Iso' T.Text [Either T.Text T.Text] | |
collecting = iso collect collapse | |
collect :: T.Text -> [Either T.Text T.Text] | |
collect t = map toEither $ T.groupBy ((==) `on` p) t | |
collapse :: [Either T.Text T.Text] -> T.Text | |
collapse = foldOf (traversed . both) | |
toEither t | |
| (T.all p t) = Left t | |
| otherwise = Right t | |
rows :: IndexedTraversal' Int T.Text T.Text | |
rows = splitOnPredicate (== '\n') | |
columns :: IndexedTraversal' Int T.Text T.Text | |
columns = splitOnPredicate (== '|') | |
alice :: T.Text | |
alice = "Alice was beginning to get very tired of sitting by her sister on the bank, and of having nothing to do: once or twice she had peeped into the book her sister was reading, but it had no pictures or conversations in it, \"and what is the use of a book,” thought Alice \"without pictures or conversations?" | |
table :: T.Text | |
table = [r|name | city | |
Derek | Portland | |
Chris | Saskatoon|] |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment