non-empty-text-0.2.1: Non empty Data.Text type
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.NonEmptyText

Synopsis

Documentation

data NonEmptyText Source #

Instances

Instances details
Semigroup NonEmptyText Source # 
Instance details

Defined in Data.NonEmptyText

Generic NonEmptyText Source # 
Instance details

Defined in Data.NonEmptyText

Associated Types

type Rep NonEmptyText :: Type -> Type #

Show NonEmptyText Source # 
Instance details

Defined in Data.NonEmptyText

NFData NonEmptyText Source # 
Instance details

Defined in Data.NonEmptyText

Methods

rnf :: NonEmptyText -> () #

Eq NonEmptyText Source # 
Instance details

Defined in Data.NonEmptyText

Ord NonEmptyText Source # 
Instance details

Defined in Data.NonEmptyText

type Rep NonEmptyText Source # 
Instance details

Defined in Data.NonEmptyText

type Rep NonEmptyText = D1 ('MetaData "NonEmptyText" "Data.NonEmptyText" "non-empty-text-0.2.1-inplace" 'False) (C1 ('MetaCons "NonEmptyText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

Creation

new :: Char -> Text -> NonEmptyText Source #

O(1) Create a new NonEmptyText

>>> new 'h' "ello world"
"hello world"

singleton :: Char -> NonEmptyText Source #

O(1) Convert a character into a NonEmptyText.

>>> singleton 'a'
"a"

toText :: NonEmptyText -> Text Source #

O(n) Convert to NonEmptyText to Text.

The Text result is guaranteed to be non-empty. However, this is not reflected in the type.

fromText :: Text -> Maybe NonEmptyText Source #

O(n) Create a NonEmptyText from Text.

If the original text is empty, this will return Nothing.

>>> fromText "hello"
Just "hello"
>>> fromText ""
Nothing

Basic interface

cons :: Char -> NonEmptyText -> NonEmptyText Source #

O(n) Prefixes the NonEmptyText with one character

snoc :: NonEmptyText -> Char -> NonEmptyText Source #

O(n) Suffixes the NonEmptyText with one character

uncons :: NonEmptyText -> (Char, Text) Source #

O(1) Return the first character and the rest of the NonEmptyText

unsnoc :: NonEmptyText -> (Text, Char) Source #

O(n) Return the beginning of the NonEmptyText, and its last character

append :: NonEmptyText -> NonEmptyText -> NonEmptyText Source #

O(n) Appends one NonEmptyText to another

>>> append <$> fromText "hello," <*> fromText " world."
Just "hello, world."

head :: NonEmptyText -> Char Source #

O(1) Return the first of the NonEmptyText

As opposed to head, this is guaranteed to succeed, as the the text is never empty.

last :: NonEmptyText -> Char Source #

O(1) Return the last character of the NonEmptyText

This never fails.

tail :: NonEmptyText -> Text Source #

O(1) Return all characters of the NonEmptyText but the first one

init :: NonEmptyText -> Text Source #

O(n) Return all character of the NonEmptyText but the last one

length :: NonEmptyText -> Int Source #

O(n) Return the length of the total NonEmptyText.

map :: (Char -> Char) -> NonEmptyText -> NonEmptyText Source #

O(n) map f t is the NonEmptyText obtained by applying f to each element of t.

isSingleton :: NonEmptyText -> Bool Source #

O(1) Check if the string is composed of only one character

Folds

foldl1 :: (Char -> Char -> Char) -> NonEmptyText -> Char Source #

O(n) foldl1 is a left associative fold with no base case, as we know the text cannot be empty.

foldl1' :: (Char -> Char -> Char) -> NonEmptyText -> Char Source #

O(n) A strict version of foldl1.