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

Fcf.Data.NewText

Description

Fcf.Data.NewText

We mimick Data.Text but on type level. The current internal representation of Fcf.Data.Text is based on type level lists. The current (as of early 2023) implementation of this Fcf.Data.Text will be deprecated and replaced with the contents of Fcf.Data.NewText later 2023 as newer version GHC become more widespread.

The old version working with 9.0.x or less will be kept at Fcf.Data.OldText for some time. Similarly, the module Fcf.Data.NewText contains the functions and definitions for better Text type, which will be taken into use after some time.

The Fcf.Data.NewText will replace Fcf.Data.Text eventually.

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
(IsString str, KnownSymbol sym) => KnownVal str ('Text sym :: Text) Source #

Text instance.

Example

Expand
import qualified Data.Text as Txt
:{

afun :: forall r. (r ~ 'FTxt.Text "hmm") => Txt.Text afun = fromType (Proxy @r) :}

afun

"hmm"

Instance details

Defined in Fcf.Data.Reflect

Methods

fromType :: Proxy ('Text sym) -> str Source #

type Eval Empty Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (Concat lst :: Text -> Type) = Eval (FromSymbol =<< (Concat =<< FMap Unpack lst))
type Eval (FromList txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (FromSymbol s :: Text -> Type) = 'Text s
type Eval (FromSymbolList sym :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (Reverse ('Text sym) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (Reverse ('Text sym) :: Text -> Type) = Eval (FromSymbol =<< (ConcatChars =<< ((Reverse :: [Char] -> [Char] -> Type) =<< ToCharList sym)))
type Eval (Singleton c :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (ConcatMap f ('Text sym) :: Text -> Type) = Eval (Concat =<< (FMap f =<< ToCharList sym))
type Eval (ConcatMapCS f ('Text sym) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (ConcatMapCS f ('Text sym) :: Text -> Type) = Eval (FromSymbol =<< (Concat =<< (FMap f =<< ToCharList sym)))
type Eval (ConcatMapSymbol f ('Text sym) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (ConsSymbol s ('Text sym) :: Text -> Type) = 'Text (AppendSymbol s sym)
type Eval (Drop n txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (DropAroundSymbol f txt :: Text -> Type)
type Eval (DropEnd n txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (DropEnd n txt :: Text -> Type) = Eval (FromList =<< ((Reverse :: [Text] -> [Text] -> Type) =<< ((Drop n :: [Text] -> [Text] -> Type) =<< ((Reverse :: [Text] -> [Text] -> Type) =<< ToList txt))))
type Eval (DropWhile f ('Text sym) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (DropWhileEnd f ('Text sym) :: Text -> Type) = Eval (FromSymbol =<< (ConcatChars =<< ((Reverse :: [Char] -> [Char] -> Type) =<< (DropWhile f =<< ((Reverse :: [Char] -> [Char] -> Type) =<< ToCharList sym)))))
type Eval (DropWhileEndSymbol f txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (FMap f ('Text sym) :: Text -> Type) = Eval (FromSymbol =<< (ConcatChars =<< (FMap f =<< ToCharList sym)))
type Eval (FMapSymbol f txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (SnocSymbol ('Text sym) s :: Text -> Type) = 'Text (AppendSymbol sym s)
type Eval (Take n txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (TakeEnd n txt :: Text -> Type) = Eval (FromList =<< ((Reverse :: [Text] -> [Text] -> Type) =<< ((Take n :: [Text] -> [Text] -> Type) =<< ((Reverse :: [Text] -> [Text] -> Type) =<< ToList txt))))
type Eval (TakeWhile f ('Text sym) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (TakeWhileEnd f ('Text sym) :: Text -> Type) = Eval (FromSymbol =<< (ConcatChars =<< ((Reverse :: [Char] -> [Char] -> Type) =<< (TakeWhile f =<< ((Reverse :: [Char] -> [Char] -> Type) =<< ToCharList sym)))))
type Eval (TakeWhileEndSymbol f txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (Replace orig new txt :: Text -> Type) = Eval (Intercalate new =<< SplitOn orig txt)
type Eval (Init ('Text sym) :: Maybe Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (Init ('Text sym) :: Maybe Text -> Type) = Eval (FMap FromSymbol =<< (FMap ConcatChars =<< ((Init :: [Char] -> Maybe [Char] -> Type) =<< ToCharList sym)))
type Eval (Tail ('Text sym) :: Maybe Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (Tail ('Text sym) :: Maybe Text -> Type) = Eval (FMap FromSymbol =<< (FMap (Snd :: (Char, Symbol) -> Symbol -> Type) =<< UnconsSymbol sym))
type Eval (Unsnoc txt :: Maybe (Text, Char) -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (Uncons txt :: Maybe (Char, Text) -> Type) = Eval (PairMaybeToMaybePair '(Eval (Head txt), Eval (Tail txt)))
type Eval (Lines txt :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

type Eval (ToList txt :: [Text] -> Type) = Eval (FMap Singleton =<< ToCharList txt)
type Eval (Words txt :: [Text] -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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

Defined in Fcf.Data.NewText

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.NewText

type Eval Empty = 'Text ""

data Singleton :: Char -> Exp Text Source #

Singleton

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

Instances

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

Defined in Fcf.Data.NewText

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

Instances

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

Defined in Fcf.Data.NewText

data FromSymbolList :: [Symbol] -> Exp Text Source #

Use FromList to construct a Text from type-level list.

Example

Expand

:kind! Eval (FromSymbolList '["h", "e", "l", "l", "u", "r", "e", "i"]) Eval (FromSymbolList '["h", "e", "l", "l", "u", "r", "e", "i"]) :: Text = 'Text "hellurei"

Instances

Instances details
type Eval (FromSymbolList sym :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

data FromSymbol :: Symbol -> Exp Text Source #

FromSymbol

Example

Expand
>>> :kind! Eval (FromSymbol "some text")
Eval (FromSymbol "some text") :: Text
= 'Text "some text"

Instances

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

Defined in Fcf.Data.NewText

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

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

Split text to characters and give them as Text list.

:kind! Eval (ToList =<< FromSymbol "abc")

Eval (ToList =<< FromSymbol "abc") :: [Text] = '[ 'Text "a", 'Text "b", 'Text "c"]

Instances

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

Defined in Fcf.Data.NewText

type Eval (ToList txt :: [Text] -> Type) = Eval (FMap Singleton =<< ToCharList txt)

data ToSymbolList :: Text -> Exp [Symbol] Source #

Get the type-level list out of the Text.

Example

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

Instances

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

Defined in Fcf.Data.NewText

data ToCharList :: Text -> Exp [Char] Source #

Split text to characters and give them as Char list.

:kind! Eval (ToCharList =<< FromSymbol "abc")

Eval (ToCharList =<< FromSymbol "abc") :: [Char] = '[a, b, c]

Instances

Instances details
type Eval (ToCharList ('Text sym) :: [Char] -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (ToCharList ('Text sym) :: [Char] -> Type) = ToCharList @@ sym

data Unpack :: Text -> Exp Symbol Source #

Unpack

Example

Expand
>>> :kind! Eval (Unpack =<< FromSymbol "word")
Eval (Unpack =<< FromSymbol "word") :: Symbol
= "word"

Instances

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

Defined in Fcf.Data.NewText

type Eval (Unpack ('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.NewText

type Eval (Null txt :: Bool -> Type)

data Length :: Text -> Exp Nat Source #

Length

Example

Expand
>>> :kind! Eval (Length =<< FromSymbol "ab")
Eval (Length =<< FromSymbol "ab") :: TL.Natural
= 2

Instances

Instances details
type Eval (Length txt :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (Length txt :: Nat -> Type) = Eval ((Length :: [Char] -> Nat -> Type) =<< ToCharList txt)

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.NewText

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

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

Add a Char 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 c ('Text sym) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

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

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

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

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

Add a Char 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) c :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

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

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

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

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

Get the first Char from type-level text.

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

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

Get the last Char from type-level text.

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

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

Get the first Char of type-level text.

Example

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

Instances

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

Defined in Fcf.Data.NewText

type Eval (Head ('Text sym) :: Maybe Char -> Type) = Eval (FMap (Fst :: (Char, Symbol) -> Char -> Type) =<< UnconsSymbol sym)

data Last :: Text -> Exp (Maybe Char) Source #

Get the last Char of type-level text.

Example

Expand
>>> :kind! Eval (Last ('Text "aamu"))
Eval (Last ('Text "aamu")) :: Maybe Char
= 'Just 'u'
>>> :kind! Eval (Last ('Text ""))
Eval (Last ('Text "")) :: Maybe Char
= 'Nothing

Instances

Instances details
type Eval (Last txt :: Maybe Char -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (Last txt :: Maybe Char -> Type) = Eval (FMap (Snd :: (Text, Char) -> Char -> Type) =<< Unsnoc txt)

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.NewText

type Eval (Tail ('Text sym) :: Maybe Text -> Type) = Eval (FMap FromSymbol =<< (FMap (Snd :: (Char, Symbol) -> Symbol -> Type) =<< UnconsSymbol sym))

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

Take all except the last Char 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 ('Text sym) :: Maybe Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (Init ('Text sym) :: Maybe Text -> Type) = Eval (FMap FromSymbol =<< (FMap ConcatChars =<< ((Init :: [Char] -> Maybe [Char] -> Type) =<< ToCharList sym)))

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.NewText

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

Transformation

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

FMap for type-level text.

Example

Expand
>>> :{
data DigitsToX :: Char -> Exp Char
type instance Eval (DigitsToX c) = Eval
    (If (IsDigit @@ c)
        (Pure 'X')
        (Pure c)
    )
:}
>>> :kind! Eval (FMap DigitsToX ('Text "Some4text5oh9."))
Eval (FMap DigitsToX ('Text "Some4text5oh9.")) :: Text
= 'Text "SomeXtextXohX."

Instances

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

Defined in Fcf.Data.NewText

type Eval (FMap f ('Text sym) :: Text -> Type) = Eval (FromSymbol =<< (ConcatChars =<< (FMap f =<< ToCharList sym)))

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

FMapSymbol for type-level text.

Example

Expand
>>> :{
data IsIsymb :: Symbol -> Exp Bool
type instance Eval (IsIsymb s) = Eval ("i" Sym.== s)
data Isymb2e :: Symbol -> Exp Symbol
type instance Eval (Isymb2e s) = Eval
    (If (IsIsymb @@ s)
        (Pure "e")
        (Pure s)
    )
:}
>>> :kind! Eval (FMapSymbol Isymb2e ('Text "imu"))
Eval (FMapSymbol Isymb2e ('Text "imu")) :: Text
= 'Text "emu"

Instances

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

Defined in Fcf.Data.NewText

data FMapT :: (Text -> Exp Text) -> Text -> Exp Text Source #

Instances

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

Defined in Fcf.Data.NewText

type Eval (FMapT f txt :: Text -> Type) = Eval (FromList =<< (FMap f =<< ToList txt))

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.NewText

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

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

Intersperse Char 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 c ('Text sym) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

Intersperse Symbol for type-level text.

Example

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

Instances

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

Defined in Fcf.Data.NewText

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 ('Text sym) :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (Reverse ('Text sym) :: Text -> Type) = Eval (FromSymbol =<< (ConcatChars =<< ((Reverse :: [Char] -> [Char] -> Type) =<< ToCharList sym)))

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.NewText

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.NewText

type Eval (Concat lst :: Text -> Type) = Eval (FromSymbol =<< (Concat =<< FMap Unpack lst))

data ConcatMap :: (Char -> Exp Text) -> Text -> Exp Text Source #

ConcatMap for type-level text. This takes Char to Text function.

Example

Expand
>>> :{
data DigitsToHoo :: Char -> Exp Text
type instance Eval (DigitsToHoo c) = Eval
    (If (IsDigit @@ c)
        (Pure ( 'Text "hoo"))
        (Singleton c)
    )
:}
>>> :kind! Eval (ConcatMap DigitsToHoo ('Text "haa2hui2"))
Eval (ConcatMap DigitsToHoo ('Text "haa2hui2")) :: Text
= 'Text "haahoohuihoo"

Instances

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

Defined in Fcf.Data.NewText

type Eval (ConcatMap f ('Text sym) :: Text -> Type) = Eval (Concat =<< (FMap f =<< ToCharList sym))

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

FConcatMapSymbol for type-level text. This takes Symbol to Text function.

Example

Expand
>>> :{
data IsIsymb :: Symbol -> Exp Bool
type instance Eval (IsIsymb s) = Eval ("i" Sym.== s)
data Isymb2aa :: Symbol -> Exp Text
type instance Eval (Isymb2aa s) = Eval
    (If (IsIsymb @@ s)
        (Pure ('Text "aa"))
        (Pure ('Text s))
    )
:}
>>> :kind! Eval (ConcatMapSymbol Isymb2aa ('Text "imu ih"))
Eval (ConcatMapSymbol Isymb2aa ('Text "imu ih")) :: Text
= 'Text "aamu aah"

Instances

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

Defined in Fcf.Data.NewText

data ConcatMapCS :: (Char -> Exp Symbol) -> Text -> Exp Text Source #

ConcatMap for type-level text. This takes Char to Symbol function.

Instances

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

Defined in Fcf.Data.NewText

type Eval (ConcatMapCS f ('Text sym) :: Text -> Type) = Eval (FromSymbol =<< (Concat =<< (FMap f =<< ToCharList sym)))

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

Any for type-level text. This takes Char to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

type Eval (Any f ('Text sym) :: Bool -> Type) = Eval ((Any f :: [Char] -> Bool -> Type) =<< ToCharList sym)

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

AnySymbol for type-level text. This takes Symbol to Bool function. Note that the given function needs to be compatible... (i.e. operating with symbols of length 1.

Example

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

Instances

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

Defined in Fcf.Data.NewText

type Eval (AnySymbol f ('Text sym) :: Bool -> Type) = Eval ((Any f :: [Symbol] -> Bool -> Type) =<< (FMap CharToSymbol =<< ToCharList sym))

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

All for type-level text. This takes Char to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

type Eval (All f ('Text sym) :: Bool -> Type) = Eval ((All f :: [Char] -> Bool -> Type) =<< ToCharList sym)

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

AllSymbol for type-level text. This takes Symbol to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

type Eval (AllSymbol f ('Text sym) :: Bool -> Type) = Eval ((All f :: [Symbol] -> Bool -> Type) =<< (FMap CharToSymbol =<< ToCharList sym))

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 txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

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 txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

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 txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

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 txt :: Text -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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

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

TakeWhile for type-level text. This takes Char to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

TakeWhileSymbol for type-level text. This takes Symbol to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

TakeWhileEnd for type-level text. This takes Char to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

type Eval (TakeWhileEnd f ('Text sym) :: Text -> Type) = Eval (FromSymbol =<< (ConcatChars =<< ((Reverse :: [Char] -> [Char] -> Type) =<< (TakeWhile f =<< ((Reverse :: [Char] -> [Char] -> Type) =<< ToCharList sym)))))

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

TakeWhileEndSymbol for type-level text. This takes Symbol to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

DropWhile for type-level text. This takes Char to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

DropWhileEnd for type-level text.

Example

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

Instances

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

Defined in Fcf.Data.NewText

type Eval (DropWhileEnd f ('Text sym) :: Text -> Type) = Eval (FromSymbol =<< (ConcatChars =<< ((Reverse :: [Char] -> [Char] -> Type) =<< (DropWhile f =<< ((Reverse :: [Char] -> [Char] -> Type) =<< ToCharList sym)))))

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

DropWhileEndSymbol for type-level text.

Example

Expand
>>> :kind! Eval (DropWhileEndSymbol Sym.IsDigit ('Text "aamu12"))
Eval (DropWhileEndSymbol Sym.IsDigit ('Text "aamu12")) :: Text
= 'Text "aamu"

Instances

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

Defined in Fcf.Data.NewText

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

DropAround for type-level text. This takes Char to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

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

DropAroundSymbol for type-level text. This takes Symbol to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

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.NewText

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.NewText

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

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

Split for type-level text. This takes Char to Bool function.

Example

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

Instances

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

Defined in Fcf.Data.NewText

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

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

Lines for type-level text.

Example

Expand
>>> :kind! Eval (Lines =<< FromSymbol "ok\nhmm\nab")
Eval (Lines =<< FromSymbol "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.NewText

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

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

Words for type-level text.

Example

Expand
>>> :kind! Eval (Words =<< FromSymbol "ok hmm\nab")
Eval (Words =<< FromSymbol "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.NewText

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

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.NewText

type Eval (Unlines txts :: Text -> Type) = Eval (Concat =<< FMap (Flip Append (FromSymbol @@ "\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.NewText

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 l1 l2 :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (IsPrefixOf l1 l2 :: Bool -> Type) = Eval (IsPrefixOf (Eval (ToList l1)) (Eval (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 l1 l2 :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

type Eval (IsSuffixOf l1 l2 :: Bool -> Type) = Eval (IsSuffixOf (Eval (ToList l1)) (Eval (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 l1 l2 :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.NewText

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