string-variants-0.2.0.0: Constrained text newtypes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.StringVariants.NonEmptyText

Description

 
Synopsis

Non empty text

data NonEmptyText (n :: Nat) Source #

Non Empty Text, requires the input is between 1 and n chars and not just whitespace.

Instances

Instances details
(KnownNat n, 1 <= n) => Arbitrary (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

(KnownNat n, 1 <= n) => FromJSON (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

ToJSON (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

Semigroup (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

Generic (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

Associated Types

type Rep (NonEmptyText n) :: Type -> Type #

Methods

from :: NonEmptyText n -> Rep (NonEmptyText n) x #

to :: Rep (NonEmptyText n) x -> NonEmptyText n #

Read (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

Show (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

Eq (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

Ord (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

MonoFoldable (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

Methods

ofoldMap :: Monoid m => (Element (NonEmptyText n) -> m) -> NonEmptyText n -> m #

ofoldr :: (Element (NonEmptyText n) -> b -> b) -> b -> NonEmptyText n -> b #

ofoldl' :: (a -> Element (NonEmptyText n) -> a) -> a -> NonEmptyText n -> a #

otoList :: NonEmptyText n -> [Element (NonEmptyText n)] #

oall :: (Element (NonEmptyText n) -> Bool) -> NonEmptyText n -> Bool #

oany :: (Element (NonEmptyText n) -> Bool) -> NonEmptyText n -> Bool #

onull :: NonEmptyText n -> Bool #

olength :: NonEmptyText n -> Int #

olength64 :: NonEmptyText n -> Int64 #

ocompareLength :: Integral i => NonEmptyText n -> i -> Ordering #

otraverse_ :: Applicative f => (Element (NonEmptyText n) -> f b) -> NonEmptyText n -> f () #

ofor_ :: Applicative f => NonEmptyText n -> (Element (NonEmptyText n) -> f b) -> f () #

omapM_ :: Applicative m => (Element (NonEmptyText n) -> m ()) -> NonEmptyText n -> m () #

oforM_ :: Applicative m => NonEmptyText n -> (Element (NonEmptyText n) -> m ()) -> m () #

ofoldlM :: Monad m => (a -> Element (NonEmptyText n) -> m a) -> a -> NonEmptyText n -> m a #

ofoldMap1Ex :: Semigroup m => (Element (NonEmptyText n) -> m) -> NonEmptyText n -> m #

ofoldr1Ex :: (Element (NonEmptyText n) -> Element (NonEmptyText n) -> Element (NonEmptyText n)) -> NonEmptyText n -> Element (NonEmptyText n) #

ofoldl1Ex' :: (Element (NonEmptyText n) -> Element (NonEmptyText n) -> Element (NonEmptyText n)) -> NonEmptyText n -> Element (NonEmptyText n) #

headEx :: NonEmptyText n -> Element (NonEmptyText n) #

lastEx :: NonEmptyText n -> Element (NonEmptyText n) #

unsafeHead :: NonEmptyText n -> Element (NonEmptyText n) #

unsafeLast :: NonEmptyText n -> Element (NonEmptyText n) #

maximumByEx :: (Element (NonEmptyText n) -> Element (NonEmptyText n) -> Ordering) -> NonEmptyText n -> Element (NonEmptyText n) #

minimumByEx :: (Element (NonEmptyText n) -> Element (NonEmptyText n) -> Ordering) -> NonEmptyText n -> Element (NonEmptyText n) #

oelem :: Element (NonEmptyText n) -> NonEmptyText n -> Bool #

onotElem :: Element (NonEmptyText n) -> NonEmptyText n -> Bool #

ConvertibleStrings (NonEmptyText n) ByteString Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

ConvertibleStrings (NonEmptyText n) Text Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

ConvertibleStrings (NonEmptyText n) String Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

Lift (NonEmptyText n :: TYPE LiftedRep) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

Methods

lift :: Quote m => NonEmptyText n -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NonEmptyText n -> Code m (NonEmptyText n) #

type Rep (NonEmptyText n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

type Rep (NonEmptyText n) = D1 ('MetaData "NonEmptyText" "Data.StringVariants.NonEmptyText.Internal" "string-variants-0.2.0.0-GSRttUhcM5nBgnx0RSvPug" 'True) (C1 ('MetaCons "NonEmptyText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type Element (NonEmptyText _n) Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText.Internal

type (<=) (x :: k) (y :: k) = (x <=? y) ~ 'True infix 4 #

Comparison (<=) of comparable types, as a constraint.

Since: base-4.16.0.0

Construction

mkNonEmptyText :: forall n. (KnownNat n, 1 <= n) => Text -> Maybe (NonEmptyText n) Source #

unsafeMkNonEmptyText :: forall n. (KnownNat n, 1 <= n) => Text -> NonEmptyText n Source #

Make a NonEmptyText when you can manually verify the length

Conversion

widen :: (1 <= n, n <= m) => NonEmptyText n -> NonEmptyText m Source #

Converts a NonEmptyText to a wider NonEmptyText

Functions

takeNonEmptyText :: forall m n. (KnownNat m, KnownNat n, 1 <= n, n <= m) => NonEmptyText m -> NonEmptyText n Source #

Narrows the maximum length, dropping any remaining trailing characters.

takeNonEmptyTextEnd :: forall m n. (KnownNat m, KnownNat n, 1 <= n, n <= m) => NonEmptyText m -> NonEmptyText n Source #

Narrows the maximum length, dropping any prefix remaining characters.

chunksOfNonEmptyText :: forall chunkSize totalSize. (KnownNat chunkSize, KnownNat totalSize, chunkSize <= totalSize, 1 <= chunkSize) => NonEmptyText totalSize -> [NonEmptyText chunkSize] Source #

O(n) Splits a NonEmptyText into components of length chunkSize. The chunks may be shorter than the chunkSize depending on the length of the input and spacing. Each chunk is stripped of whitespace.

filterNonEmptyText :: (KnownNat n, 1 <= n) => (Char -> Bool) -> NonEmptyText n -> Maybe (NonEmptyText n) Source #

Identical to the normal text filter function, but maintains the type-level invariant that the text length is <= n, unlike unwrapping the text, filtering, then rewrapping the text.

Will return Nothing if the resulting length is zero.

(<>|) :: NonEmptyText n -> NonEmptyText m -> NonEmptyText (n + m) Source #

Concat two NonEmptyText values, with the new maximum length being the sum of the two maximum lengths of the inputs.

Mnemonic: <> for monoid, | from NonEmpty's :| operator

concatWithSpace :: NonEmptyText n -> NonEmptyText m -> NonEmptyText ((n + m) + 1) Source #

Concat two NonEmptyText values with a space in between them. The new maximum length is the sum of the two maximum lengths of the inputs + 1 for the space.

Useful for unwordslike operations, or combining first and last names.

Conversions between Refined and NonEmptyText.

data ContainsNonWhitespaceCharacters Source #

Instances

Instances details
Generic ContainsNonWhitespaceCharacters Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText

Associated Types

type Rep ContainsNonWhitespaceCharacters :: Type -> Type #

Predicate ContainsNonWhitespaceCharacters Text Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText

type Rep ContainsNonWhitespaceCharacters Source # 
Instance details

Defined in Data.StringVariants.NonEmptyText

type Rep ContainsNonWhitespaceCharacters = D1 ('MetaData "ContainsNonWhitespaceCharacters" "Data.StringVariants.NonEmptyText" "string-variants-0.2.0.0-GSRttUhcM5nBgnx0RSvPug" 'False) (C1 ('MetaCons "ContainsNonWhitespaceCharacters" 'PrefixI 'False) (U1 :: Type -> Type))