text1-0.0.4: Non-empty values of `Data.Text`.

Safe HaskellNone
LanguageHaskell2010

Data.Text1

Synopsis

Documentation

data Text1 Source #

Constructors

Text1 Char Text 

Instances

Eq Text1 Source # 

Methods

(==) :: Text1 -> Text1 -> Bool #

(/=) :: Text1 -> Text1 -> Bool #

Data Text1 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Text1 -> c Text1 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Text1 #

toConstr :: Text1 -> Constr #

dataTypeOf :: Text1 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Text1) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Text1) #

gmapT :: (forall b. Data b => b -> b) -> Text1 -> Text1 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Text1 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Text1 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Text1 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Text1 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Text1 -> m Text1 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Text1 -> m Text1 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Text1 -> m Text1 #

Ord Text1 Source # 

Methods

compare :: Text1 -> Text1 -> Ordering #

(<) :: Text1 -> Text1 -> Bool #

(<=) :: Text1 -> Text1 -> Bool #

(>) :: Text1 -> Text1 -> Bool #

(>=) :: Text1 -> Text1 -> Bool #

max :: Text1 -> Text1 -> Text1 #

min :: Text1 -> Text1 -> Text1 #

Show Text1 Source # 

Methods

showsPrec :: Int -> Text1 -> ShowS #

show :: Text1 -> String #

showList :: [Text1] -> ShowS #

Semigroup Text1 Source #
((x <> y) <> z) == (x <> (y <> z :: Text1))

Methods

(<>) :: Text1 -> Text1 -> Text1 #

sconcat :: NonEmpty Text1 -> Text1 #

stimes :: Integral b => b -> Text1 -> Text1 #

Binary Text1 Source # 

Methods

put :: Text1 -> Put #

get :: Get Text1 #

putList :: [Text1] -> Put #

Reversing Text1 Source # 

Methods

reversing :: Text1 -> Text1 #

IsText1 Text1 Source # 
AsSingle Text1 Char Source # 
AsText1 p f Text1 Source # 

Methods

_Text1 :: Optic' * * p f Text1 Text1 Source #

OneAnd Text1 Text1 Char Char Text Text Source # 
IsText (Maybe Text1) Source # 
Cons (Maybe Text1) (Maybe Text1) Char Char Source # 
Snoc (Maybe Text1) (Maybe Text1) Char Char Source # 

length1 :: Text1 -> Int Source #

>>> fmap length1 ("a" ^? _Text1)
Just 1
>>> fmap length1 ("abc" ^? _Text1)
Just 3
length1 t >= 1

compareLength1 :: Text1 -> Int -> Ordering Source #

>>> fmap (`compareLength1` 1) ("a" ^? _Text1)
Just EQ
>>> fmap (`compareLength1` 3) ("a" ^? _Text1)
Just LT
>>> fmap (`compareLength1` 1) ("abc" ^? _Text1)
Just GT
>>> fmap (`compareLength1` 3) ("abc" ^? _Text1)
Just EQ
>>> fmap (`compareLength1` 5) ("abc" ^? _Text1)
Just LT
compareLength1 t 1 /= LT

_head1 :: Lens' Text1 Char Source #

>>> fmap (^. _head1) ("a" ^? _Text1)
Just 'a'
>>> fmap (^. _head1) ("abc" ^? _Text1)
Just 'a'
>>> fmap (_head1 %~ toUpper) ("abc" ^? _Text1)
Just "Abc"

_tail1 :: Lens' Text1 Text Source #

>>> fmap (^. _tail1) ("a" ^? _Text1)
Just ""
>>> fmap (^. _tail1) ("abc" ^? _Text1)
Just "bc"
>>> fmap (_tail1 %~ Text.toUpper) ("abc" ^? _Text1)
Just "aBC"

_last1 :: Lens' Text1 Char Source #

>>> fmap (^. _last1) ("a" ^? _Text1)
Just 'a'
>>> fmap (^. _last1) ("abc" ^? _Text1)
Just 'c'
>>> fmap (_last1 %~ toUpper) ("abc" ^? _Text1)
Just "abC"

_init1 :: Lens' Text1 Text Source #

>>> fmap (^. _init1) ("a" ^? _Text1)
Just ""
>>> fmap (^. _init1) ("abc" ^? _Text1)
Just "ab"
>>> fmap (_init1 %~ Text.toUpper) ("a" ^? _Text1)
Just "a"
>>> fmap (_init1 %~ Text.toUpper) ("abc" ^? _Text1)
Just "ABc"

class AsText1 p f s where Source #

Methods

_Text1 :: Optic' p f s Text1 Source #

class AsSingle c a | c -> a where Source #

Methods

_Single :: Prism' c a Source #

class OneAnd s t a b x y | s -> a, s -> x, t -> b, t -> y, s b -> t, x b -> t, t a -> s, y a -> s where Source #

Methods

_OneAnd :: Iso s t (a, x) (b, y) Source #

Instances

OneAnd Text1 Text1 Char Char Text Text Source # 
OneAnd (NonEmpty a) (NonEmpty b) a b [a] [b] Source # 

Methods

_OneAnd :: Iso (NonEmpty a) (NonEmpty b) (a, [a]) (b, [b]) Source #