fcf-containers-0.6.0: Data structures and algorithms for first-class-families
Copyright(c) gspia 2020-
LicenseBSD
Maintainergspia
Safe HaskellSafe
LanguageHaskell2010

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

Documentation

data Text Source #

Text is a data structure, that is, a list to hold type-level symbols of length one.

Constructors

Text Symbol 

Instances

Instances details
type Eval Empty Source # 
Instance details

Defined in Fcf.Data.Text

type Eval Empty = 'Text ""
type Eval (Unwords txts :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Unwords txts :: Text -> Type) = Eval (Intercalate ('Text " ") txts)
type Eval (Unlines txts :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Unlines txts :: Text -> Type) = Eval (Concat =<< FMap (Flip Append (Singleton @@ "\n")) txts)
type Eval (Strip txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Strip txt :: Text -> Type) = Eval (DropAround IsSpaceDelim txt)
type Eval (Concat lst :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Concat lst :: Text -> Type) = 'Text (ToSymbol2 @@ Eval (FMap ToSymbol lst))
type Eval (Reverse txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Reverse txt :: Text -> Type) = Eval (FromList =<< ((Reverse :: [Text] -> [Text] -> Type) =<< ToList txt))
type Eval (FromList txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (FromList txt :: Text -> Type) = 'Text (ToSymbol2 @@ Eval (FMap ToSymbol txt))
type Eval (Singleton s :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Singleton s :: Text -> Type) = 'Text s
type Eval (DropAround f txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (DropAround f txt :: Text -> Type) = Eval (DropWhile f =<< DropWhileEnd f txt)
type Eval (DropWhileEnd f ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (DropWhileEnd f ('Text lst) :: Text -> Type)
type Eval (DropWhile f ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (DropWhile f ('Text lst) :: Text -> Type)
type Eval (TakeWhileEnd f ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (TakeWhileEnd f ('Text lst) :: Text -> Type)
type Eval (TakeWhile f ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (TakeWhile f ('Text lst) :: Text -> Type)
type Eval (DropEnd n ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (DropEnd n ('Text lst) :: Text -> Type)
type Eval (Drop n ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Drop n ('Text lst) :: Text -> Type)
type Eval (TakeEnd n ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (TakeEnd n ('Text lst) :: Text -> Type)
type Eval (Take n ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Take n ('Text lst) :: Text -> Type)
type Eval (FConcatMap f ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (FConcatMap f ('Text lst) :: Text -> Type) = Eval (Concat =<< FMap f (ToList lst))
type Eval (Intersperse s ('Text txt) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Intersperse s ('Text txt) :: Text -> Type)
type Eval (Intercalate txt txts :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Intercalate txt txts :: Text -> Type) = Eval (FromList =<< (Intercalate '[txt] =<< FMap ToList txts))
type Eval (FMap f txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (FMap f txt :: Text -> Type)
type Eval (Append ('Text s1) ('Text s2) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Append ('Text s1) ('Text s2) :: Text -> Type) = 'Text (AppendSymbol s1 s2)
type Eval (Snoc ('Text sym) s :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Snoc ('Text sym) s :: Text -> Type) = 'Text (AppendSymbol sym s)
type Eval (Cons s ('Text sym) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Cons s ('Text sym) :: Text -> Type) = 'Text (AppendSymbol s sym)
type Eval (Replace orig new txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Replace orig new txt :: Text -> Type) = Eval (Intercalate new =<< SplitOn orig txt)
type Eval (Words txt :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Words txt :: [Text] -> Type) = Eval (Split IsSpaceDelim txt)
type Eval (Lines txt :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Lines txt :: [Text] -> Type) = Eval (Split IsNewLine txt)
type Eval (ToList txt :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (ToList txt :: [Text] -> Type)
type Eval (Unsnoc txt :: Maybe (Symbol, Text) -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Unsnoc txt :: Maybe (Symbol, Text) -> Type) = Eval (FMap (Second Reverse :: (Symbol, Text) -> (Symbol, Text) -> Type) =<< (Uncons =<< Reverse txt))
type Eval (Uncons txt :: Maybe (Symbol, Text) -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Uncons txt :: Maybe (Symbol, Text) -> Type) = Eval (PairMaybeToMaybePair '(Eval (Head txt), Eval (Tail txt)))
type Eval (Init txt :: Maybe Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Init txt :: Maybe Text -> Type) = Eval (FMap FromList =<< ((Init :: [Text] -> Maybe [Text] -> Type) =<< ToList txt))
type Eval (Tail ('Text sym) :: Maybe Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Tail ('Text sym) :: Maybe Text -> Type) = Eval (FMap Singleton =<< Uncons sym)
type Eval (Split p ('Text txt) :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Split p ('Text txt) :: [Text] -> Type)
type Eval (SplitOn ('Text sep) ('Text txt) :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (SplitOn ('Text sep) ('Text txt) :: [Text] -> Type)

Creation

data Empty :: Exp Text Source #

Empty

Example

Expand
>>> :kind! (Eval Empty :: Text)
(Eval Empty :: Text) :: Text
= 'Text ""

See also the other examples in this module.

Instances

Instances details
type Eval Empty Source # 
Instance details

Defined in Fcf.Data.Text

type Eval Empty = 'Text ""

data Singleton :: Symbol -> Exp Text Source #

Singleton

Example

Expand
>>> :kind! Eval (Singleton "a")
Eval (Singleton "a") :: Text
= 'Text "a"

Instances

Instances details
type Eval (Singleton s :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Singleton s :: Text -> Type) = 'Text s

data FromList :: [Text] -> Exp Text Source #

Instances

Instances details
type Eval (FromList txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (FromList txt :: Text -> Type) = 'Text (ToSymbol2 @@ Eval (FMap ToSymbol txt))

data ToList :: Text -> Exp [Text] Source #

Split Text to single character Text list.

Example

Expand
>>> :kind! Eval (ToList =<< FromSymbolList '["a", "b"])
Eval (ToList =<< FromSymbolList '["a", "b"]) :: [Text]
= '[ 'Text "a", 'Text "b"]

Instances

Instances details
type Eval (ToList txt :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (ToList txt :: [Text] -> Type)

data ToSymbol :: Text -> Exp Symbol Source #

ToSymbol

Example

Expand
>>> :kind! Eval (ToSymbol =<< FromSymbolList '["w", "o", "r", "d"])
Eval (ToSymbol =<< FromSymbolList '["w", "o", "r", "d"]) :: Symbol
= "word"

Instances

Instances details
type Eval (ToSymbol ('Text sym) :: Symbol -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (ToSymbol ('Text sym) :: Symbol -> Type) = sym

Basic Interface

data Null :: Text -> Exp Bool Source #

Null

Example

Expand
>>> :kind! Eval (Null ('Text "ab"))
Eval (Null ('Text "ab")) :: Bool
= 'False
>>> :kind! Eval (Null =<< Empty)
Eval (Null =<< Empty) :: Bool
= 'True

Instances

Instances details
type Eval (Null txt :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Null txt :: Bool -> Type) = Eval (If (Eval (Eval (Length txt) == 0)) (Pure 'True) (Pure 'False))

data Length :: Text -> Exp Nat Source #

Length

Example

Expand
>>> :kind! Eval (Length =<< Singleton "ab")
Eval (Length =<< Singleton "ab") :: Nat
= 2

Instances

Instances details
type Eval (Length ('Text sym) :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Length ('Text sym) :: Nat -> Type) = Eval (Length (ToList sym))

data Append :: Text -> Text -> Exp Text Source #

Append two type-level texts.

Example

Expand
>>> :kind! Eval (Append ('Text "aa") ('Text "mu"))
Eval (Append ('Text "aa") ('Text "mu")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (Append ('Text s1) ('Text s2) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Append ('Text s1) ('Text s2) :: Text -> Type) = 'Text (AppendSymbol s1 s2)

data Cons :: Symbol -> Text -> Exp Text Source #

Add a symbol to the beginning of a type-level text.

Example

Expand
>>> :kind! Eval (Cons "h" ('Text "aamu"))
Eval (Cons "h" ('Text "aamu")) :: Text
= 'Text "haamu"

Instances

Instances details
type Eval (Cons s ('Text sym) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Cons s ('Text sym) :: Text -> Type) = 'Text (AppendSymbol s sym)

data Snoc :: Text -> Symbol -> Exp Text Source #

Add a symbol to the end of a type-level text.

Example

Expand
>>> :kind! Eval (Snoc ('Text "aam") "u")
Eval (Snoc ('Text "aam") "u") :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (Snoc ('Text sym) s :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Snoc ('Text sym) s :: Text -> Type) = 'Text (AppendSymbol sym s)

data Uncons :: Text -> Exp (Maybe (Symbol, Text)) Source #

Get the first symbol from type-level text.

Example

Expand
>>> :kind! Eval (Uncons ('Text "haamu"))
Eval (Uncons ('Text "haamu")) :: Maybe (Symbol, Text)
= 'Just '("h", 'Text "aamu")
>>> :kind! Eval (Uncons ('Text ""))
Eval (Uncons ('Text "")) :: Maybe (Symbol, Text)
= 'Nothing

Instances

Instances details
type Eval (Uncons txt :: Maybe (Symbol, Text) -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Uncons txt :: Maybe (Symbol, Text) -> Type) = Eval (PairMaybeToMaybePair '(Eval (Head txt), Eval (Tail txt)))

data Unsnoc :: Text -> Exp (Maybe (Symbol, Text)) Source #

Get the last symbol from type-level text.

Example

Expand
>>> :kind! Eval (Unsnoc ('Text "aamun"))
Eval (Unsnoc ('Text "aamun")) :: Maybe (Symbol, Text)
= 'Just '("n", 'Text "aamu")
>>> :kind! Eval (Unsnoc ('Text ""))
Eval (Unsnoc ('Text "")) :: Maybe (Symbol, Text)
= 'Nothing

Instances

Instances details
type Eval (Unsnoc txt :: Maybe (Symbol, Text) -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Unsnoc txt :: Maybe (Symbol, Text) -> Type) = Eval (FMap (Second Reverse :: (Symbol, Text) -> (Symbol, Text) -> Type) =<< (Uncons =<< Reverse txt))

data Head :: Text -> Exp (Maybe Symbol) Source #

Get the first symbol of type-level text.

Example

Expand
>>> :kind! Eval (Head ('Text "aamu"))
Eval (Head ('Text "aamu")) :: Maybe Symbol
= 'Just "a"
>>> :kind! Eval (Head ('Text ""))
Eval (Head ('Text "")) :: Maybe Symbol
= 'Nothing

Instances

Instances details
type Eval (Head ('Text sym) :: Maybe Symbol -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Head ('Text sym) :: Maybe Symbol -> Type) = Eval (If (Eval (Eval (Length ('Text sym)) == 0)) (Pure ('Nothing :: Maybe Symbol)) (Pure ('Just (Head1 sym (CmpSymbol sym "\128")))))

data Tail :: Text -> Exp (Maybe Text) Source #

Get the tail of a type-level text.

Example

Expand
>>> :kind! Eval (Tail ('Text "haamu"))
Eval (Tail ('Text "haamu")) :: Maybe Text
= 'Just ('Text "aamu")
>>> :kind! Eval (Tail ('Text ""))
Eval (Tail ('Text "")) :: Maybe Text
= 'Nothing

Instances

Instances details
type Eval (Tail ('Text sym) :: Maybe Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Tail ('Text sym) :: Maybe Text -> Type) = Eval (FMap Singleton =<< Uncons sym)

data Init :: Text -> Exp (Maybe Text) Source #

Take all except the last symbol from type-level text.

Example

Expand
>>> :kind! Eval (Init ('Text "aamun"))
Eval (Init ('Text "aamun")) :: Maybe Text
= 'Just ('Text "aamu")
>>> :kind! Eval (Init ('Text ""))
Eval (Init ('Text "")) :: Maybe Text
= 'Nothing

Instances

Instances details
type Eval (Init txt :: Maybe Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Init txt :: Maybe Text -> Type) = Eval (FMap FromList =<< ((Init :: [Text] -> Maybe [Text] -> Type) =<< ToList txt))

data CompareLength :: Text -> Nat -> Exp Ordering Source #

Compare the length of type-level text to given Nat and give the Ordering.

Example

Expand
>>> :kind! Eval (CompareLength ('Text "aamu") 3)
Eval (CompareLength ('Text "aamu") 3) :: Ordering
= 'GT

Instances

Instances details
type Eval (CompareLength txt n :: Ordering -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (CompareLength txt n :: Ordering -> Type) = CmpNat (Length @@ txt) n

Transformation

data FMap :: (Symbol -> Exp Symbol) -> Text -> Exp Text Source #

FMap for type-level text.

Example

Expand
>>> :{
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 "imu"))
Eval (FMap Isymb2e ('Text "imu")) :: Text
= 'Text "emu"

Instances

Instances details
type Eval (FMap f txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (FMap f txt :: Text -> Type)

data Intercalate :: Text -> [Text] -> Exp Text Source #

Intercalate for type-level text.

Example

Expand
>>> :kind! Eval (Intercalate ('Text " & ") ('[ 'Text "aamu", 'Text "valo"]))
Eval (Intercalate ('Text " & ") ('[ 'Text "aamu", 'Text "valo"])) :: Text
= 'Text "aamu & valo"

Instances

Instances details
type Eval (Intercalate txt txts :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Intercalate txt txts :: Text -> Type) = Eval (FromList =<< (Intercalate '[txt] =<< FMap ToList txts))

data Intersperse :: Symbol -> Text -> Exp Text Source #

Intersperse for type-level text.

Example

Expand
>>> :kind! Eval (Intersperse "." ('Text "aamu"))
Eval (Intersperse "." ('Text "aamu")) :: Text
= 'Text "a.a.m.u"

Instances

Instances details
type Eval (Intersperse s ('Text txt) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Intersperse s ('Text txt) :: Text -> Type)

data Reverse :: Text -> Exp Text Source #

Reverse for type-level text.

Example

Expand
>>> :kind! Eval (Reverse ('Text "aamu"))
Eval (Reverse ('Text "aamu")) :: Text
= 'Text "umaa"
>>> :kind! Eval (Reverse =<< Reverse ('Text "aamu"))
Eval (Reverse =<< Reverse ('Text "aamu")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (Reverse txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Reverse txt :: Text -> Type) = Eval (FromList =<< ((Reverse :: [Text] -> [Text] -> Type) =<< ToList txt))

data Replace :: Text -> Text -> Text -> Exp Text Source #

Replace for type-level text.

Example

Expand
>>> :kind! Eval (Replace ('Text "tu") ('Text "la") ('Text "tuututtaa"))
Eval (Replace ('Text "tu") ('Text "la") ('Text "tuututtaa")) :: Text
= 'Text "laulattaa"

Instances

Instances details
type Eval (Replace orig new txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Replace orig new txt :: Text -> Type) = Eval (Intercalate new =<< SplitOn orig txt)

Special Folds

data Concat :: [Text] -> Exp Text Source #

Concat for type-level text.

Example

Expand
>>> :kind! Eval (Concat '[ 'Text "la", 'Text "kana"])
Eval (Concat '[ 'Text "la", 'Text "kana"]) :: Text
= 'Text "lakana"

Instances

Instances details
type Eval (Concat lst :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Concat lst :: Text -> Type) = 'Text (ToSymbol2 @@ Eval (FMap ToSymbol lst))

data FConcatMap :: (Symbol -> Exp Text) -> Text -> Exp Text Source #

FConcatMap for type-level text.

Example

Expand
>>> :{
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 "aa"))
        (Pure ('Text s))
    )
:}
>>> :kind! Eval (FConcatMap Isymb2aa ('Text "imu ih"))
Eval (FConcatMap Isymb2aa ('Text "imu ih")) :: Text
= 'Text "aamu aah"

Instances

Instances details
type Eval (FConcatMap f ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (FConcatMap f ('Text lst) :: Text -> Type) = Eval (Concat =<< FMap f (ToList lst))

data Any :: (Symbol -> Exp Bool) -> Text -> Exp Bool Source #

Any for type-level text.

Example

Expand
>>> :kind! Eval (Any S.IsDigit ('Text "aamu1"))
Eval (Any S.IsDigit ('Text "aamu1")) :: Bool
= 'True
>>> :kind! Eval (Any S.IsDigit ('Text "aamu"))
Eval (Any S.IsDigit ('Text "aamu")) :: Bool
= 'False

Instances

Instances details
type Eval (Any f ('Text sym) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Any f ('Text sym) :: Bool -> Type) = Eval (Any f (ToList sym))

data All :: (Symbol -> Exp Bool) -> Text -> Exp Bool Source #

All for type-level text.

Example

Expand
>>> :kind! Eval (All S.IsDigit ('Text "aamu1"))
Eval (All S.IsDigit ('Text "aamu1")) :: Bool
= 'False
>>> :kind! Eval (All S.IsDigit ('Text "321"))
Eval (All S.IsDigit ('Text "321")) :: Bool
= 'True

Instances

Instances details
type Eval (All f ('Text lst) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (All f ('Text lst) :: Bool -> Type) = Eval (All f (ToList lst))

Substrings

data Take :: Nat -> Text -> Exp Text Source #

Take for type-level text.

Example

Expand
>>> :kind! Eval (Take 4 ('Text "aamun"))
Eval (Take 4 ('Text "aamun")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (Take n ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Take n ('Text lst) :: Text -> Type)

data TakeEnd :: Nat -> Text -> Exp Text Source #

TakeEnd for type-level text.

Example

Expand
>>> :kind! Eval (TakeEnd 4 ('Text "haamu"))
Eval (TakeEnd 4 ('Text "haamu")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (TakeEnd n ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (TakeEnd n ('Text lst) :: Text -> Type)

data Drop :: Nat -> Text -> Exp Text Source #

Drop for type-level text.

Example

Expand
>>> :kind! Eval (Drop 2 ('Text "aamuna"))
Eval (Drop 2 ('Text "aamuna")) :: Text
= 'Text "muna"

Instances

Instances details
type Eval (Drop n ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Drop n ('Text lst) :: Text -> Type)

data DropEnd :: Nat -> Text -> Exp Text Source #

DropEnd for type-level text.

Example

Expand
>>> :kind! Eval (DropEnd 2 ('Text "aamuna"))
Eval (DropEnd 2 ('Text "aamuna")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (DropEnd n ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (DropEnd n ('Text lst) :: Text -> Type)

data TakeWhile :: (Symbol -> Exp Bool) -> Text -> Exp Text Source #

TakeWhile for type-level text.

Example

Expand
>>> :kind! Eval (TakeWhile (Not <=< S.IsDigit) ('Text "aamu12"))
Eval (TakeWhile (Not <=< S.IsDigit) ('Text "aamu12")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (TakeWhile f ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (TakeWhile f ('Text lst) :: Text -> Type)

data TakeWhileEnd :: (Symbol -> Exp Bool) -> Text -> Exp Text Source #

TakeWhileEnd for type-level text.

Example

Expand
>>> :kind! Eval (TakeWhileEnd (Not <=< S.IsDigit) ('Text "12aamu"))
Eval (TakeWhileEnd (Not <=< S.IsDigit) ('Text "12aamu")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (TakeWhileEnd f ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (TakeWhileEnd f ('Text lst) :: Text -> Type)

data DropWhile :: (Symbol -> Exp Bool) -> Text -> Exp Text Source #

DropWhile for type-level text.

Example

Expand
>>> :kind! Eval (DropWhile S.IsDigit ('Text "12aamu"))
Eval (DropWhile S.IsDigit ('Text "12aamu")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (DropWhile f ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (DropWhile f ('Text lst) :: Text -> Type)

data DropWhileEnd :: (Symbol -> Exp Bool) -> Text -> Exp Text Source #

DropWhileEnd for type-level text. === Example

>>> :kind! Eval (DropWhileEnd S.IsDigit ('Text "aamu12"))
Eval (DropWhileEnd S.IsDigit ('Text "aamu12")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (DropWhileEnd f ('Text lst) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (DropWhileEnd f ('Text lst) :: Text -> Type)

data DropAround :: (Symbol -> Exp Bool) -> Text -> Exp Text Source #

DropAround for type-level text.

Example

Expand
>>> :kind! Eval (DropAround S.IsDigit ('Text "34aamu12"))
Eval (DropAround S.IsDigit ('Text "34aamu12")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (DropAround f txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (DropAround f txt :: Text -> Type) = Eval (DropWhile f =<< DropWhileEnd f txt)

data Strip :: Text -> Exp Text Source #

Strip the space, newline and tab -symbols from the beginning and and of type-level text.

Example

Expand
>>> :kind! Eval (Strip ('Text "  aamu \n"))
Eval (Strip ('Text "  aamu \n")) :: Text
= 'Text "aamu"

Instances

Instances details
type Eval (Strip txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Strip txt :: Text -> Type) = Eval (DropAround IsSpaceDelim txt)

Breaking etc

data SplitOn :: Text -> Text -> Exp [Text] Source #

SplitOn for type-level text.

Example

Expand
>>> :kind! Eval (SplitOn ('Text "ab") ('Text "cdabfgabh"))
Eval (SplitOn ('Text "ab") ('Text "cdabfgabh")) :: [Text]
= '[ 'Text "cd", 'Text "fg", 'Text "h"]

Instances

Instances details
type Eval (SplitOn ('Text sep) ('Text txt) :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (SplitOn ('Text sep) ('Text txt) :: [Text] -> Type)

data Split :: (Symbol -> Exp Bool) -> Text -> Exp [Text] Source #

Split for type-level text.

Example

Expand
>>> :kind! Eval (Split S.IsSpace (Eval (Singleton "cd bf abh")))
Eval (Split S.IsSpace (Eval (Singleton "cd bf abh"))) :: [Text]
= '[ 'Text "cd", 'Text "bf", 'Text "abh"]

Instances

Instances details
type Eval (Split p ('Text txt) :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Split p ('Text txt) :: [Text] -> Type)

data Lines :: Text -> Exp [Text] Source #

Lines for type-level text.

Example

Expand
>>> :kind! Eval (Lines =<< Singleton "ok\nhmm\nab")
Eval (Lines =<< Singleton "ok\nhmm\nab") :: [Text]
= '[ 'Text "ok", 'Text "hmm", 'Text "ab"]

Instances

Instances details
type Eval (Lines txt :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Lines txt :: [Text] -> Type) = Eval (Split IsNewLine txt)

data Words :: Text -> Exp [Text] Source #

Words for type-level text.

Example

Expand
>>> :kind! Eval (Words =<< Singleton "ok hmm\nab")
Eval (Words =<< Singleton "ok hmm\nab") :: [Text]
= '[ 'Text "ok", 'Text "hmm", 'Text "ab"]

Instances

Instances details
type Eval (Words txt :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Words txt :: [Text] -> Type) = Eval (Split IsSpaceDelim txt)

data Unlines :: [Text] -> Exp Text Source #

Unlines for type-level text. This adds a newline to each Text and then concats them.

Example

Expand
>>> :kind! Eval (Unlines '[ 'Text "ok", 'Text "hmm", 'Text "ab"])
Eval (Unlines '[ 'Text "ok", 'Text "hmm", 'Text "ab"]) :: Text
= 'Text "ok\nhmm\nab\n"

Instances

Instances details
type Eval (Unlines txts :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Unlines txts :: Text -> Type) = Eval (Concat =<< FMap (Flip Append (Singleton @@ "\n")) txts)

data Unwords :: [Text] -> Exp Text Source #

Unwords for type-level text. This uses Intercalate to add space-symbol between the given texts.

Example

Expand
>>> :kind! Eval (Unwords '[ 'Text "ok", 'Text "hmm", 'Text "ab"])
Eval (Unwords '[ 'Text "ok", 'Text "hmm", 'Text "ab"]) :: Text
= 'Text "ok hmm ab"

Instances

Instances details
type Eval (Unwords txts :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (Unwords txts :: Text -> Type) = Eval (Intercalate ('Text " ") txts)

Predicates

data IsPrefixOf :: Text -> Text -> Exp Bool Source #

IsPrefixOf for type-level text.

Example

Expand
>>> :kind! Eval (IsPrefixOf ('Text "aa") ('Text "aamiainen"))
Eval (IsPrefixOf ('Text "aa") ('Text "aamiainen")) :: Bool
= 'True

Instances

Instances details
type Eval (IsPrefixOf ('Text l1) ('Text l2) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (IsPrefixOf ('Text l1) ('Text l2) :: Bool -> Type) = Eval (IsPrefixOf (ToList l1) (ToList l2))

data IsSuffixOf :: Text -> Text -> Exp Bool Source #

IsSuffixOf for type-level text.

Example

Expand
>>> :kind! Eval (IsSuffixOf ('Text "nen") ('Text "aamiainen"))
Eval (IsSuffixOf ('Text "nen") ('Text "aamiainen")) :: Bool
= 'True

Instances

Instances details
type Eval (IsSuffixOf ('Text l1) ('Text l2) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (IsSuffixOf ('Text l1) ('Text l2) :: Bool -> Type) = Eval (IsSuffixOf (ToList l1) (ToList l2))

data IsInfixOf :: Text -> Text -> Exp Bool Source #

IsInfixOf for type-level text.

Example

Expand
>>> :kind! Eval (IsInfixOf ('Text "mia") ('Text "aamiainen"))
Eval (IsInfixOf ('Text "mia") ('Text "aamiainen")) :: Bool
= 'True

Instances

Instances details
type Eval (IsInfixOf ('Text l1) ('Text l2) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Text

type Eval (IsInfixOf ('Text l1) ('Text l2) :: Bool -> Type) = Eval (IsInfixOf (ToList l1) (ToList l2))