| Copyright | (c) gspia 2020- | 
|---|---|
| License | BSD | 
| Maintainer | gspia | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Fcf.Data.Text
Description
Fcf.Data.Text
We mimick Data.Text but on type level. The internal representation is based on type level lists.
Synopsis
- data Text = Text [Symbol]
- data Empty :: Exp Text
- data Singleton :: Symbol -> Exp Text
- data FromList :: [Symbol] -> Exp Text
- data ToList :: Text -> Exp [Symbol]
- data ToSymbol :: Text -> Exp Symbol
- data Null :: Text -> Exp Bool
- data Length :: Text -> Exp Nat
- data Append :: Text -> Text -> Exp Text
- data Cons :: Symbol -> Text -> Exp Text
- data Snoc :: Text -> Symbol -> Exp Text
- data Uncons :: Text -> Exp (Maybe (Symbol, Text))
- data Unsnoc :: Text -> Exp (Maybe (Symbol, Text))
- data Head :: Text -> Exp (Maybe Symbol)
- data Tail :: Text -> Exp (Maybe Text)
- data Init :: Text -> Exp (Maybe Text)
- data CompareLength :: Text -> Nat -> Exp Ordering
- data FMap :: (Symbol -> Exp Symbol) -> Text -> Exp Text
- data Intercalate :: Text -> [Text] -> Exp Text
- data Intersperse :: Symbol -> Text -> Exp Text
- data Reverse :: Text -> Exp Text
- data Replace :: Text -> Text -> Text -> Exp Text
- data Concat :: [Text] -> Exp Text
- data FConcatMap :: (Symbol -> Exp Text) -> Text -> Exp Text
- data Any :: (Symbol -> Exp Bool) -> Text -> Exp Bool
- data All :: (Symbol -> Exp Bool) -> Text -> Exp Bool
- data Take :: Nat -> Text -> Exp Text
- data TakeEnd :: Nat -> Text -> Exp Text
- data Drop :: Nat -> Text -> Exp Text
- data DropEnd :: Nat -> Text -> Exp Text
- data TakeWhile :: (Symbol -> Exp Bool) -> Text -> Exp Text
- data TakeWhileEnd :: (Symbol -> Exp Bool) -> Text -> Exp Text
- data DropWhile :: (Symbol -> Exp Bool) -> Text -> Exp Text
- data DropWhileEnd :: (Symbol -> Exp Bool) -> Text -> Exp Text
- data DropAround :: (Symbol -> Exp Bool) -> Text -> Exp Text
- data Strip :: Text -> Exp Text
- data SplitOn :: Text -> Text -> Exp [Text]
- data Split :: (Symbol -> Exp Bool) -> Text -> Exp [Text]
- data Lines :: Text -> Exp [Text]
- data Words :: Text -> Exp [Text]
- data Unlines :: [Text] -> Exp Text
- data Unwords :: [Text] -> Exp Text
- data IsPrefixOf :: Text -> Text -> Exp Bool
- data IsSuffixOf :: Text -> Text -> Exp Bool
- data IsInfixOf :: Text -> Text -> Exp Bool
Documentation
Text is a data structure, that is, a list to hold type-level symbols of
 length one.
Instances
Creation
data Empty :: Exp Text Source #
Empty
Example
>>>:kind! (Eval Empty :: Text)(Eval Empty :: Text) :: Text = 'Text '[]
See also the other examples in this module.
data Singleton :: Symbol -> Exp Text Source #
Singleton
Example
>>>:kind! Eval (Singleton "a")Eval (Singleton "a") :: Text = 'Text '["a"]
data FromList :: [Symbol] -> Exp Text Source #
Use FromList to construct a Text from type-level list.
Example
:kind! Eval (FromList '["h", "e", "l", "l", "u", "r", "e", "i"]) Eval (FromList '["h", "e", "l", "l", "u", "r", "e", "i"]) :: Text = 'Text '["h", "e", "l", "l", "u", "r", "e", "i"]
data ToList :: Text -> Exp [Symbol] Source #
Get the type-level list out of the Text.
Example
>>>:kind! Eval (ToList =<< FromList '["a", "b"])Eval (ToList =<< FromList '["a", "b"]) :: [Symbol] = '["a", "b"]
data ToSymbol :: Text -> Exp Symbol Source #
ToSymbol
Example
>>>:kind! Eval (ToSymbol =<< FromList '["w", "o", "r", "d"])Eval (ToSymbol =<< FromList '["w", "o", "r", "d"]) :: Symbol = "word"
Basic Interface
data Null :: Text -> Exp Bool Source #
Null
Example
>>>:kind! Eval (Null =<< FromList '["a", "b"])Eval (Null =<< FromList '["a", "b"]) :: Bool = 'False>>>:kind! Eval (Null =<< Empty)Eval (Null =<< Empty) :: Bool = 'True
data Length :: Text -> Exp Nat Source #
Length
Example
>>>:kind! Eval (Length =<< FromList '["a", "b"])Eval (Length =<< FromList '["a", "b"]) :: Nat = 2
data Append :: Text -> Text -> Exp Text Source #
Append two type-level texts.
Example
>>>:kind! Eval (Append ('Text '["a", "a"]) ('Text '["m", "u"]))Eval (Append ('Text '["a", "a"]) ('Text '["m", "u"])) :: Text = 'Text '["a", "a", "m", "u"]
data Cons :: Symbol -> Text -> Exp Text Source #
Add a symbol to the beginning of a type-level text.
Example
>>>:kind! Eval (Cons "h" ('Text '["a", "a", "m", "u"]))Eval (Cons "h" ('Text '["a", "a", "m", "u"])) :: Text = 'Text '["h", "a", "a", "m", "u"]
data Snoc :: Text -> Symbol -> Exp Text Source #
Add a symbol to the end of a type-level text.
Example
>>>:kind! Eval (Snoc ('Text '["a", "a", "m"]) "u")Eval (Snoc ('Text '["a", "a", "m"]) "u") :: Text = 'Text '["a", "a", "m", "u"]
data Uncons :: Text -> Exp (Maybe (Symbol, Text)) Source #
Get the first symbol from type-level text.
Example
>>>:kind! Eval (Uncons ('Text '["h", "a", "a", "m", "u"]))Eval (Uncons ('Text '["h", "a", "a", "m", "u"])) :: Maybe (Symbol, Text) = 'Just '("h", 'Text '["a", "a", "m", "u"])
>>>:kind! Eval (Uncons ('Text '[]))Eval (Uncons ('Text '[])) :: Maybe (Symbol, Text) = 'Nothing
data Unsnoc :: Text -> Exp (Maybe (Symbol, Text)) Source #
Get the last symbol from type-level text.
Example
>>>:kind! Eval (Unsnoc ('Text '["a", "a", "m", "u", "n"]))Eval (Unsnoc ('Text '["a", "a", "m", "u", "n"])) :: Maybe (Symbol, Text) = 'Just '("n", 'Text '["a", "a", "m", "u"])
>>>:kind! Eval (Unsnoc ('Text '[]))Eval (Unsnoc ('Text '[])) :: Maybe (Symbol, Text) = 'Nothing
data Head :: Text -> Exp (Maybe Symbol) Source #
Get the first symbol of type-level text.
Example
>>>:kind! Eval (Head ('Text '["a", "a", "m", "u"]))Eval (Head ('Text '["a", "a", "m", "u"])) :: Maybe Symbol = 'Just "a"
>>>:kind! Eval (Head ('Text '[]))Eval (Head ('Text '[])) :: Maybe Symbol = 'Nothing
data Tail :: Text -> Exp (Maybe Text) Source #
Get the tail of a type-level text.
Example
>>>:kind! Eval (Tail ('Text '["h", "a", "a", "m", "u"]))Eval (Tail ('Text '["h", "a", "a", "m", "u"])) :: Maybe Text = 'Just ('Text '["a", "a", "m", "u"])
>>>:kind! Eval (Tail ('Text '[]))Eval (Tail ('Text '[])) :: Maybe Text = 'Nothing
data Init :: Text -> Exp (Maybe Text) Source #
Take all except the last symbol from type-level text.
Example
>>>:kind! Eval (Init ('Text '["a", "a", "m", "u", "n"]))Eval (Init ('Text '["a", "a", "m", "u", "n"])) :: Maybe Text = 'Just ('Text '["a", "a", "m", "u"])
>>>:kind! Eval (Init ('Text '[]))Eval (Init ('Text '[])) :: Maybe Text = 'Nothing
data CompareLength :: Text -> Nat -> Exp Ordering Source #
Compare the length of type-level text to given Nat and give the Ordering.
Example
>>>:kind! Eval (CompareLength ('Text '["a", "a", "m", "u"]) 3)Eval (CompareLength ('Text '["a", "a", "m", "u"]) 3) :: Ordering = 'GT
Instances
| type Eval (CompareLength txt n :: Ordering -> Type) Source # | |
| Defined in Fcf.Data.Text | |
Transformation
data FMap :: (Symbol -> Exp Symbol) -> Text -> Exp Text Source #
FMap for type-level text.
Example
>>>:{data IsIsymb :: Symbol -> Exp Bool type instance Eval (IsIsymb s) = Eval ("i" S.== s) data Isymb2e :: Symbol -> Exp Symbol type instance Eval (Isymb2e s) = Eval (If (IsIsymb @@ s) (Pure "e") (Pure s) ) :}
>>>:kind! Eval (FMap Isymb2e ('Text '["i","m","u"]))Eval (FMap Isymb2e ('Text '["i","m","u"])) :: Text = 'Text '["e", "m", "u"]
data Intercalate :: Text -> [Text] -> Exp Text Source #
Intercalate for type-level text.
Example
>>>:kind! Eval (Intercalate ('Text '[" ", "&", " "]) ('[ 'Text '["a", "a", "m", "u"], 'Text '["v", "a", "l", "o"]]))Eval (Intercalate ('Text '[" ", "&", " "]) ('[ 'Text '["a", "a", "m", "u"], 'Text '["v", "a", "l", "o"]])) :: Text = 'Text '["a", "a", "m", "u", " ", "&", " ", "v", "a", "l", "o"]
Instances
| type Eval (Intercalate (Text txt) txts :: Text -> Type) Source # | |
| Defined in Fcf.Data.Text | |
data Intersperse :: Symbol -> Text -> Exp Text Source #
Intersperse for type-level text.
Example
>>>:kind! Eval (Intersperse "." ('Text '["a", "a", "m", "u"]))Eval (Intersperse "." ('Text '["a", "a", "m", "u"])) :: Text = 'Text '["a", ".", "a", ".", "m", ".", "u"]
Instances
| type Eval (Intersperse s (Text txt) :: Text -> Type) Source # | |
| Defined in Fcf.Data.Text | |
data Reverse :: Text -> Exp Text Source #
Reverse for type-level text.
Example
>>>:kind! Eval (Reverse ('Text '["a", "a", "m", "u"]))Eval (Reverse ('Text '["a", "a", "m", "u"])) :: Text = 'Text '["u", "m", "a", "a"]
>>>:kind! Eval (Reverse =<< Reverse ('Text '["a", "a", "m", "u"]))Eval (Reverse =<< Reverse ('Text '["a", "a", "m", "u"])) :: Text = 'Text '["a", "a", "m", "u"]
data Replace :: Text -> Text -> Text -> Exp Text Source #
Replace for type-level text.
Example
>>>:kind! Eval (Replace ('Text '["t","u"]) ('Text '["l","a"]) ('Text '["t","u","u","t","u","t","t","a","a"]))Eval (Replace ('Text '["t","u"]) ('Text '["l","a"]) ('Text '["t","u","u","t","u","t","t","a","a"])) :: Text = 'Text '["l", "a", "u", "l", "a", "t", "t", "a", "a"]
Special Folds
data Concat :: [Text] -> Exp Text Source #
Concat for type-level text.
Example
>>>:kind! Eval (Concat '[ 'Text '["l","a"], 'Text '["k","a","n","a"]])Eval (Concat '[ 'Text '["l","a"], 'Text '["k","a","n","a"]]) :: Text = 'Text '["l", "a", "k", "a", "n", "a"]
data FConcatMap :: (Symbol -> Exp Text) -> Text -> Exp Text Source #
FConcatMap for type-level text.
Example
>>>:{data IsIsymb :: Symbol -> Exp Bool type instance Eval (IsIsymb s) = Eval ("i" S.== s) data Isymb2aa :: Symbol -> Exp Text type instance Eval (Isymb2aa s) = Eval (If (IsIsymb @@ s) (Pure ('Text '["a","a"])) (Pure ('Text '[s])) ) :}
>>>:kind! Eval (FConcatMap Isymb2aa ('Text '["i","m","u"," ","i","h"]))Eval (FConcatMap Isymb2aa ('Text '["i","m","u"," ","i","h"])) :: Text = 'Text '["a", "a", "m", "u", " ", "a", "a", "h"]
data Any :: (Symbol -> Exp Bool) -> Text -> Exp Bool Source #
Any for type-level text.
Example
>>>:kind! Eval (Any S.IsDigit ('Text '["a","a","m","u","1"]))Eval (Any S.IsDigit ('Text '["a","a","m","u","1"])) :: Bool = 'True
>>>:kind! Eval (Any S.IsDigit ('Text '["a","a","m","u"]))Eval (Any S.IsDigit ('Text '["a","a","m","u"])) :: Bool = 'False
data All :: (Symbol -> Exp Bool) -> Text -> Exp Bool Source #
All for type-level text.
Example
>>>:kind! Eval (All S.IsDigit ('Text '["a","a","m","u","1"]))Eval (All S.IsDigit ('Text '["a","a","m","u","1"])) :: Bool = 'False
>>>:kind! Eval (All S.IsDigit ('Text '["3","2","1"]))Eval (All S.IsDigit ('Text '["3","2","1"])) :: Bool = 'True
Substrings
data Take :: Nat -> Text -> Exp Text Source #
Take for type-level text.
Example
>>>:kind! Eval (Take 4 ('Text '["a", "a", "m", "u", "n"]))Eval (Take 4 ('Text '["a", "a", "m", "u", "n"])) :: Text = 'Text '["a", "a", "m", "u"]
data TakeEnd :: Nat -> Text -> Exp Text Source #
TakeEnd for type-level text.
Example
>>>:kind! Eval (TakeEnd 4 ('Text '["h", "a", "a", "m", "u"]))Eval (TakeEnd 4 ('Text '["h", "a", "a", "m", "u"])) :: Text = 'Text '["a", "a", "m", "u"]
data Drop :: Nat -> Text -> Exp Text Source #
Drop for type-level text.
Example
>>>:kind! Eval (Drop 2 ('Text '["a", "a", "m", "u", "n", "a"]))Eval (Drop 2 ('Text '["a", "a", "m", "u", "n", "a"])) :: Text = 'Text '["m", "u", "n", "a"]
data DropEnd :: Nat -> Text -> Exp Text Source #
DropEnd for type-level text.
Example
>>>:kind! Eval (DropEnd 2 ('Text '["a", "a", "m", "u", "n", "a"]))Eval (DropEnd 2 ('Text '["a", "a", "m", "u", "n", "a"])) :: Text = 'Text '["a", "a", "m", "u"]
data TakeWhile :: (Symbol -> Exp Bool) -> Text -> Exp Text Source #
TakeWhile for type-level text.
Example
>>>:kind! Eval (TakeWhile (Not <=< S.IsDigit) ('Text '["a","a","m","u","1","2"]))Eval (TakeWhile (Not <=< S.IsDigit) ('Text '["a","a","m","u","1","2"])) :: Text = 'Text '["a", "a", "m", "u"]
data TakeWhileEnd :: (Symbol -> Exp Bool) -> Text -> Exp Text Source #
TakeWhileEnd for type-level text.
Example
>>>:kind! Eval (TakeWhileEnd (Not <=< S.IsDigit) ('Text '["1","2","a","a","m","u"]))Eval (TakeWhileEnd (Not <=< S.IsDigit) ('Text '["1","2","a","a","m","u"])) :: Text = 'Text '["a", "a", "m", "u"]
data DropWhile :: (Symbol -> Exp Bool) -> Text -> Exp Text Source #
DropWhile for type-level text.
Example
>>>:kind! Eval (DropWhile S.IsDigit ('Text '["1","2","a","a","m","u"]))Eval (DropWhile S.IsDigit ('Text '["1","2","a","a","m","u"])) :: Text = 'Text '["a", "a", "m", "u"]
data DropWhileEnd :: (Symbol -> Exp Bool) -> Text -> Exp Text Source #
DropWhileEnd for type-level text. === Example
>>>:kind! Eval (DropWhileEnd S.IsDigit ('Text '["a","a","m","u","1","2"]))Eval (DropWhileEnd S.IsDigit ('Text '["a","a","m","u","1","2"])) :: Text = 'Text '["a", "a", "m", "u"]
data DropAround :: (Symbol -> Exp Bool) -> Text -> Exp Text Source #
DropAround for type-level text.
Example
>>>:kind! Eval (DropAround S.IsDigit ('Text '["3","4","a","a","m","u","1","2"]))Eval (DropAround S.IsDigit ('Text '["3","4","a","a","m","u","1","2"])) :: Text = 'Text '["a", "a", "m", "u"]
Instances
| type Eval (DropAround f txt :: Text -> Type) Source # | |
| Defined in Fcf.Data.Text | |
data Strip :: Text -> Exp Text Source #
Strip the space, newline and tab -symbols from the beginning and and of type-level text.
Example
>>>:kind! Eval (Strip ('Text '[" ", " ", "a", "a", "m", "u", " ", "\n"]))Eval (Strip ('Text '[" ", " ", "a", "a", "m", "u", " ", "\n"])) :: Text = 'Text '["a", "a", "m", "u"]
Breaking etc
data SplitOn :: Text -> Text -> Exp [Text] Source #
SplitOn for type-level text.
Example
>>>:kind! Eval (SplitOn (Eval (FromList '["a", "b"])) (Eval (FromList '[ "c", "d", "a", "b", "f", "g", "a", "b", "h"])))Eval (SplitOn (Eval (FromList '["a", "b"])) (Eval (FromList '[ "c", "d", "a", "b", "f", "g", "a", "b", "h"]))) :: [Text] = '[ 'Text '["c", "d"], 'Text '["f", "g"], 'Text '["h"]]
data Split :: (Symbol -> Exp Bool) -> Text -> Exp [Text] Source #
Split for type-level text.
Example
>>>:kind! Eval (Split S.IsSpace (Eval (FromList '[ "c", "d", " ", "b", "f", " ", "a", "b", "h"])))Eval (Split S.IsSpace (Eval (FromList '[ "c", "d", " ", "b", "f", " ", "a", "b", "h"]))) :: [Text] = '[ 'Text '["c", "d"], 'Text '["b", "f"], 'Text '["a", "b", "h"]]
data Lines :: Text -> Exp [Text] Source #
Lines for type-level text.
Example
>>>:kind! Eval (Lines =<< FromList '[ "o", "k", "\n", "h", "m", "m ", "\n", "a", "b"])Eval (Lines =<< FromList '[ "o", "k", "\n", "h", "m", "m ", "\n", "a", "b"]) :: [Text] = '[ 'Text '["o", "k"], 'Text '["h", "m", "m "], 'Text '["a", "b"]]
data Words :: Text -> Exp [Text] Source #
Words for type-level text.
Example
>>>:kind! Eval (Words =<< FromList '[ "o", "k", " ", "h", "m", "m ", "\n", "a", "b"])Eval (Words =<< FromList '[ "o", "k", " ", "h", "m", "m ", "\n", "a", "b"]) :: [Text] = '[ 'Text '["o", "k"], 'Text '["h", "m", "m "], 'Text '["a", "b"]]
data Unlines :: [Text] -> Exp Text Source #
Unlines for type-level text. This adds a newline to each Text and then concats them.
Example
>>>:kind! Eval (Unlines '[ 'Text '["o", "k"], 'Text '["h", "m", "m "], 'Text '["a", "b"]])Eval (Unlines '[ 'Text '["o", "k"], 'Text '["h", "m", "m "], 'Text '["a", "b"]]) :: Text = 'Text '["o", "k", "\n", "h", "m", "m ", "\n", "a", "b", "\n"]
data Unwords :: [Text] -> Exp Text Source #
Unwords for type-level text. This uses Intercalate to add space-symbol
 between the given texts.
Example
>>>:kind! Eval (Unwords '[ 'Text '["o", "k"], 'Text '["h", "m", "m "], 'Text '["a", "b"]])Eval (Unwords '[ 'Text '["o", "k"], 'Text '["h", "m", "m "], 'Text '["a", "b"]]) :: Text = 'Text '["o", "k", " ", "h", "m", "m ", " ", "a", "b"]
Predicates
data IsPrefixOf :: Text -> Text -> Exp Bool Source #
IsPrefixOf for type-level text.
Example
>>>:kind! Eval (IsPrefixOf ('Text '["a", "a"]) ('Text '["a", "a", "m", "i", "a", "i", "n", "e", "n"]))Eval (IsPrefixOf ('Text '["a", "a"]) ('Text '["a", "a", "m", "i", "a", "i", "n", "e", "n"])) :: Bool = 'True
Instances
| type Eval (IsPrefixOf (Text l1) (Text l2) :: Bool -> Type) Source # | |
| Defined in Fcf.Data.Text | |
data IsSuffixOf :: Text -> Text -> Exp Bool Source #
IsSuffixOf for type-level text.
Example
>>>:kind! Eval (IsSuffixOf ('Text '["n", "e", "n"]) ('Text '["a", "a", "m", "i", "a", "i", "n", "e", "n"]))Eval (IsSuffixOf ('Text '["n", "e", "n"]) ('Text '["a", "a", "m", "i", "a", "i", "n", "e", "n"])) :: Bool = 'True
Instances
| type Eval (IsSuffixOf (Text l1) (Text l2) :: Bool -> Type) Source # | |
| Defined in Fcf.Data.Text | |
data IsInfixOf :: Text -> Text -> Exp Bool Source #
IsInfixOf for type-level text.
Example
>>>:kind! Eval (IsInfixOf ('Text '["m", "i", "a"]) ('Text '["a", "a", "m", "i", "a", "i", "n", "e", "n"]))Eval (IsInfixOf ('Text '["m", "i", "a"]) ('Text '["a", "a", "m", "i", "a", "i", "n", "e", "n"])) :: Bool = 'True