{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
module Data.StringVariants.NonEmptyText.Internal where
import Control.DeepSeq (NFData)
import Control.Monad (when)
import Data.Aeson (FromJSON (..), ToJSON, withText)
import Data.ByteString
import Data.Coerce
import Data.Data (Data)
import Data.Hashable (Hashable)
import Data.MonoTraversable
import Data.Proxy
import Data.Sequences
import Data.String.Conversions (ConvertibleStrings (..), cs)
import Data.StringVariants.Util (textHasNoMeaningfulContent, textIsWhitespace)
import Data.Text (Text)
import Data.Text qualified as T
import GHC.Generics (Generic)
import GHC.TypeLits (ErrorMessage (..), KnownNat, Nat, TypeError, natVal, type (<=))
import Language.Haskell.TH.Quote
import Language.Haskell.TH.Syntax (Lift (..), TyLit (..), Type (..))
import Test.QuickCheck
import Prelude
newtype NonEmptyText (n :: Nat) = NonEmptyText Text
  deriving stock (Typeable (NonEmptyText n)
Typeable (NonEmptyText n) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> NonEmptyText n -> c (NonEmptyText n))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (NonEmptyText n))
-> (NonEmptyText n -> Constr)
-> (NonEmptyText n -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (NonEmptyText n)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (NonEmptyText n)))
-> ((forall b. Data b => b -> b)
    -> NonEmptyText n -> NonEmptyText n)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> NonEmptyText n -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> NonEmptyText n -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> NonEmptyText n -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> NonEmptyText n -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> NonEmptyText n -> m (NonEmptyText n))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> NonEmptyText n -> m (NonEmptyText n))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> NonEmptyText n -> m (NonEmptyText n))
-> Data (NonEmptyText n)
NonEmptyText n -> Constr
NonEmptyText n -> DataType
(forall b. Data b => b -> b) -> NonEmptyText n -> NonEmptyText n
forall (n :: Nat). KnownNat n => Typeable (NonEmptyText n)
forall (n :: Nat). KnownNat n => NonEmptyText n -> Constr
forall (n :: Nat). KnownNat n => NonEmptyText n -> DataType
forall (n :: Nat).
KnownNat n =>
(forall b. Data b => b -> b) -> NonEmptyText n -> NonEmptyText n
forall (n :: Nat) u.
KnownNat n =>
Int -> (forall d. Data d => d -> u) -> NonEmptyText n -> u
forall (n :: Nat) u.
KnownNat n =>
(forall d. Data d => d -> u) -> NonEmptyText n -> [u]
forall (n :: Nat) r r'.
KnownNat n =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptyText n -> r
forall (n :: Nat) r r'.
KnownNat n =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptyText n -> r
forall (n :: Nat) (m :: * -> *).
(KnownNat n, Monad m) =>
(forall d. Data d => d -> m d)
-> NonEmptyText n -> m (NonEmptyText n)
forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> NonEmptyText n -> m (NonEmptyText n)
forall (n :: Nat) (c :: * -> *).
KnownNat n =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonEmptyText n)
forall (n :: Nat) (c :: * -> *).
KnownNat n =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonEmptyText n -> c (NonEmptyText n)
forall (n :: Nat) (t :: * -> *) (c :: * -> *).
(KnownNat n, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (NonEmptyText n))
forall (n :: Nat) (t :: * -> * -> *) (c :: * -> *).
(KnownNat n, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonEmptyText n))
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> NonEmptyText n -> u
forall u. (forall d. Data d => d -> u) -> NonEmptyText n -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptyText n -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptyText n -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NonEmptyText n -> m (NonEmptyText n)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonEmptyText n -> m (NonEmptyText n)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonEmptyText n)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonEmptyText n -> c (NonEmptyText n)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (NonEmptyText n))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonEmptyText n))
$cgfoldl :: forall (n :: Nat) (c :: * -> *).
KnownNat n =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonEmptyText n -> c (NonEmptyText n)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonEmptyText n -> c (NonEmptyText n)
$cgunfold :: forall (n :: Nat) (c :: * -> *).
KnownNat n =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonEmptyText n)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonEmptyText n)
$ctoConstr :: forall (n :: Nat). KnownNat n => NonEmptyText n -> Constr
toConstr :: NonEmptyText n -> Constr
$cdataTypeOf :: forall (n :: Nat). KnownNat n => NonEmptyText n -> DataType
dataTypeOf :: NonEmptyText n -> DataType
$cdataCast1 :: forall (n :: Nat) (t :: * -> *) (c :: * -> *).
(KnownNat n, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (NonEmptyText n))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (NonEmptyText n))
$cdataCast2 :: forall (n :: Nat) (t :: * -> * -> *) (c :: * -> *).
(KnownNat n, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonEmptyText n))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonEmptyText n))
$cgmapT :: forall (n :: Nat).
KnownNat n =>
(forall b. Data b => b -> b) -> NonEmptyText n -> NonEmptyText n
gmapT :: (forall b. Data b => b -> b) -> NonEmptyText n -> NonEmptyText n
$cgmapQl :: forall (n :: Nat) r r'.
KnownNat n =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptyText n -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptyText n -> r
$cgmapQr :: forall (n :: Nat) r r'.
KnownNat n =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptyText n -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptyText n -> r
$cgmapQ :: forall (n :: Nat) u.
KnownNat n =>
(forall d. Data d => d -> u) -> NonEmptyText n -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> NonEmptyText n -> [u]
$cgmapQi :: forall (n :: Nat) u.
KnownNat n =>
Int -> (forall d. Data d => d -> u) -> NonEmptyText n -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> NonEmptyText n -> u
$cgmapM :: forall (n :: Nat) (m :: * -> *).
(KnownNat n, Monad m) =>
(forall d. Data d => d -> m d)
-> NonEmptyText n -> m (NonEmptyText n)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NonEmptyText n -> m (NonEmptyText n)
$cgmapMp :: forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> NonEmptyText n -> m (NonEmptyText n)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonEmptyText n -> m (NonEmptyText n)
$cgmapMo :: forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> NonEmptyText n -> m (NonEmptyText n)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonEmptyText n -> m (NonEmptyText n)
Data, (forall x. NonEmptyText n -> Rep (NonEmptyText n) x)
-> (forall x. Rep (NonEmptyText n) x -> NonEmptyText n)
-> Generic (NonEmptyText n)
forall (n :: Nat) x. Rep (NonEmptyText n) x -> NonEmptyText n
forall (n :: Nat) x. NonEmptyText n -> Rep (NonEmptyText n) x
forall x. Rep (NonEmptyText n) x -> NonEmptyText n
forall x. NonEmptyText n -> Rep (NonEmptyText n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall (n :: Nat) x. NonEmptyText n -> Rep (NonEmptyText n) x
from :: forall x. NonEmptyText n -> Rep (NonEmptyText n) x
$cto :: forall (n :: Nat) x. Rep (NonEmptyText n) x -> NonEmptyText n
to :: forall x. Rep (NonEmptyText n) x -> NonEmptyText n
Generic, Int -> NonEmptyText n -> ShowS
[NonEmptyText n] -> ShowS
NonEmptyText n -> String
(Int -> NonEmptyText n -> ShowS)
-> (NonEmptyText n -> String)
-> ([NonEmptyText n] -> ShowS)
-> Show (NonEmptyText n)
forall (n :: Nat). Int -> NonEmptyText n -> ShowS
forall (n :: Nat). [NonEmptyText n] -> ShowS
forall (n :: Nat). NonEmptyText n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall (n :: Nat). Int -> NonEmptyText n -> ShowS
showsPrec :: Int -> NonEmptyText n -> ShowS
$cshow :: forall (n :: Nat). NonEmptyText n -> String
show :: NonEmptyText n -> String
$cshowList :: forall (n :: Nat). [NonEmptyText n] -> ShowS
showList :: [NonEmptyText n] -> ShowS
Show, ReadPrec [NonEmptyText n]
ReadPrec (NonEmptyText n)
Int -> ReadS (NonEmptyText n)
ReadS [NonEmptyText n]
(Int -> ReadS (NonEmptyText n))
-> ReadS [NonEmptyText n]
-> ReadPrec (NonEmptyText n)
-> ReadPrec [NonEmptyText n]
-> Read (NonEmptyText n)
forall (n :: Nat). ReadPrec [NonEmptyText n]
forall (n :: Nat). ReadPrec (NonEmptyText n)
forall (n :: Nat). Int -> ReadS (NonEmptyText n)
forall (n :: Nat). ReadS [NonEmptyText n]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall (n :: Nat). Int -> ReadS (NonEmptyText n)
readsPrec :: Int -> ReadS (NonEmptyText n)
$creadList :: forall (n :: Nat). ReadS [NonEmptyText n]
readList :: ReadS [NonEmptyText n]
$creadPrec :: forall (n :: Nat). ReadPrec (NonEmptyText n)
readPrec :: ReadPrec (NonEmptyText n)
$creadListPrec :: forall (n :: Nat). ReadPrec [NonEmptyText n]
readListPrec :: ReadPrec [NonEmptyText n]
Read, (forall (m :: * -> *). Quote m => NonEmptyText n -> m Exp)
-> (forall (m :: * -> *).
    Quote m =>
    NonEmptyText n -> Code m (NonEmptyText n))
-> Lift (NonEmptyText n)
forall (n :: Nat) (m :: * -> *). Quote m => NonEmptyText n -> m Exp
forall (n :: Nat) (m :: * -> *).
Quote m =>
NonEmptyText n -> Code m (NonEmptyText n)
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => NonEmptyText n -> m Exp
forall (m :: * -> *).
Quote m =>
NonEmptyText n -> Code m (NonEmptyText n)
$clift :: forall (n :: Nat) (m :: * -> *). Quote m => NonEmptyText n -> m Exp
lift :: forall (m :: * -> *). Quote m => NonEmptyText n -> m Exp
$cliftTyped :: forall (n :: Nat) (m :: * -> *).
Quote m =>
NonEmptyText n -> Code m (NonEmptyText n)
liftTyped :: forall (m :: * -> *).
Quote m =>
NonEmptyText n -> Code m (NonEmptyText n)
Lift)
  deriving newtype (NonEmptyText n -> NonEmptyText n -> Bool
(NonEmptyText n -> NonEmptyText n -> Bool)
-> (NonEmptyText n -> NonEmptyText n -> Bool)
-> Eq (NonEmptyText n)
forall (n :: Nat). NonEmptyText n -> NonEmptyText n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall (n :: Nat). NonEmptyText n -> NonEmptyText n -> Bool
== :: NonEmptyText n -> NonEmptyText n -> Bool
$c/= :: forall (n :: Nat). NonEmptyText n -> NonEmptyText n -> Bool
/= :: NonEmptyText n -> NonEmptyText n -> Bool
Eq, Eq (NonEmptyText n)
Eq (NonEmptyText n) =>
(NonEmptyText n -> NonEmptyText n -> Ordering)
-> (NonEmptyText n -> NonEmptyText n -> Bool)
-> (NonEmptyText n -> NonEmptyText n -> Bool)
-> (NonEmptyText n -> NonEmptyText n -> Bool)
-> (NonEmptyText n -> NonEmptyText n -> Bool)
-> (NonEmptyText n -> NonEmptyText n -> NonEmptyText n)
-> (NonEmptyText n -> NonEmptyText n -> NonEmptyText n)
-> Ord (NonEmptyText n)
NonEmptyText n -> NonEmptyText n -> Bool
NonEmptyText n -> NonEmptyText n -> Ordering
NonEmptyText n -> NonEmptyText n -> NonEmptyText n
forall (n :: Nat). Eq (NonEmptyText n)
forall (n :: Nat). NonEmptyText n -> NonEmptyText n -> Bool
forall (n :: Nat). NonEmptyText n -> NonEmptyText n -> Ordering
forall (n :: Nat).
NonEmptyText n -> NonEmptyText n -> NonEmptyText n
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: forall (n :: Nat). NonEmptyText n -> NonEmptyText n -> Ordering
compare :: NonEmptyText n -> NonEmptyText n -> Ordering
$c< :: forall (n :: Nat). NonEmptyText n -> NonEmptyText n -> Bool
< :: NonEmptyText n -> NonEmptyText n -> Bool
$c<= :: forall (n :: Nat). NonEmptyText n -> NonEmptyText n -> Bool
<= :: NonEmptyText n -> NonEmptyText n -> Bool
$c> :: forall (n :: Nat). NonEmptyText n -> NonEmptyText n -> Bool
> :: NonEmptyText n -> NonEmptyText n -> Bool
$c>= :: forall (n :: Nat). NonEmptyText n -> NonEmptyText n -> Bool
>= :: NonEmptyText n -> NonEmptyText n -> Bool
$cmax :: forall (n :: Nat).
NonEmptyText n -> NonEmptyText n -> NonEmptyText n
max :: NonEmptyText n -> NonEmptyText n -> NonEmptyText n
$cmin :: forall (n :: Nat).
NonEmptyText n -> NonEmptyText n -> NonEmptyText n
min :: NonEmptyText n -> NonEmptyText n -> NonEmptyText n
Ord, [NonEmptyText n] -> Value
[NonEmptyText n] -> Encoding
NonEmptyText n -> Bool
NonEmptyText n -> Value
NonEmptyText n -> Encoding
(NonEmptyText n -> Value)
-> (NonEmptyText n -> Encoding)
-> ([NonEmptyText n] -> Value)
-> ([NonEmptyText n] -> Encoding)
-> (NonEmptyText n -> Bool)
-> ToJSON (NonEmptyText n)
forall (n :: Nat). [NonEmptyText n] -> Value
forall (n :: Nat). [NonEmptyText n] -> Encoding
forall (n :: Nat). NonEmptyText n -> Bool
forall (n :: Nat). NonEmptyText n -> Value
forall (n :: Nat). NonEmptyText n -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall (n :: Nat). NonEmptyText n -> Value
toJSON :: NonEmptyText n -> Value
$ctoEncoding :: forall (n :: Nat). NonEmptyText n -> Encoding
toEncoding :: NonEmptyText n -> Encoding
$ctoJSONList :: forall (n :: Nat). [NonEmptyText n] -> Value
toJSONList :: [NonEmptyText n] -> Value
$ctoEncodingList :: forall (n :: Nat). [NonEmptyText n] -> Encoding
toEncodingList :: [NonEmptyText n] -> Encoding
$comitField :: forall (n :: Nat). NonEmptyText n -> Bool
omitField :: NonEmptyText n -> Bool
ToJSON, Eq (Element (NonEmptyText n)) =>
Element (NonEmptyText n) -> NonEmptyText n -> Bool
NonEmptyText n -> Bool
NonEmptyText n -> Int
NonEmptyText n -> Int64
NonEmptyText n -> [Element (NonEmptyText n)]
NonEmptyText n -> Element (NonEmptyText n)
(Element (NonEmptyText n) -> Bool) -> NonEmptyText n -> Bool
(Element (NonEmptyText n) -> Element (NonEmptyText n) -> Ordering)
-> NonEmptyText n -> Element (NonEmptyText n)
(Element (NonEmptyText n)
 -> Element (NonEmptyText n) -> Element (NonEmptyText n))
-> NonEmptyText n -> Element (NonEmptyText n)
(forall m.
 Monoid m =>
 (Element (NonEmptyText n) -> m) -> NonEmptyText n -> m)
-> (forall b.
    (Element (NonEmptyText n) -> b -> b) -> b -> NonEmptyText n -> b)
-> (forall a.
    (a -> Element (NonEmptyText n) -> a) -> a -> NonEmptyText n -> a)
-> (NonEmptyText n -> [Element (NonEmptyText n)])
-> ((Element (NonEmptyText n) -> Bool) -> NonEmptyText n -> Bool)
-> ((Element (NonEmptyText n) -> Bool) -> NonEmptyText n -> Bool)
-> (NonEmptyText n -> Bool)
-> (NonEmptyText n -> Int)
-> (NonEmptyText n -> Int64)
-> (forall i. Integral i => NonEmptyText n -> i -> Ordering)
-> (forall (f :: * -> *) b.
    Applicative f =>
    (Element (NonEmptyText n) -> f b) -> NonEmptyText n -> f ())
-> (forall (f :: * -> *) b.
    Applicative f =>
    NonEmptyText n -> (Element (NonEmptyText n) -> f b) -> f ())
-> (forall (m :: * -> *).
    Applicative m =>
    (Element (NonEmptyText n) -> m ()) -> NonEmptyText n -> m ())
-> (forall (m :: * -> *).
    Applicative m =>
    NonEmptyText n -> (Element (NonEmptyText n) -> m ()) -> m ())
-> (forall (m :: * -> *) a.
    Monad m =>
    (a -> Element (NonEmptyText n) -> m a)
    -> a -> NonEmptyText n -> m a)
-> (forall m.
    Semigroup m =>
    (Element (NonEmptyText n) -> m) -> NonEmptyText n -> m)
-> ((Element (NonEmptyText n)
     -> Element (NonEmptyText n) -> Element (NonEmptyText n))
    -> NonEmptyText n -> Element (NonEmptyText n))
-> ((Element (NonEmptyText n)
     -> Element (NonEmptyText n) -> Element (NonEmptyText n))
    -> NonEmptyText n -> Element (NonEmptyText n))
-> (NonEmptyText n -> Element (NonEmptyText n))
-> (NonEmptyText n -> Element (NonEmptyText n))
-> (NonEmptyText n -> Element (NonEmptyText n))
-> (NonEmptyText n -> Element (NonEmptyText n))
-> ((Element (NonEmptyText n)
     -> Element (NonEmptyText n) -> Ordering)
    -> NonEmptyText n -> Element (NonEmptyText n))
-> ((Element (NonEmptyText n)
     -> Element (NonEmptyText n) -> Ordering)
    -> NonEmptyText n -> Element (NonEmptyText n))
-> (Eq (Element (NonEmptyText n)) =>
    Element (NonEmptyText n) -> NonEmptyText n -> Bool)
-> (Eq (Element (NonEmptyText n)) =>
    Element (NonEmptyText n) -> NonEmptyText n -> Bool)
-> MonoFoldable (NonEmptyText n)
forall (n :: Nat).
Eq (Element (NonEmptyText n)) =>
Element (NonEmptyText n) -> NonEmptyText n -> Bool
forall (n :: Nat). NonEmptyText n -> Bool
forall (n :: Nat). NonEmptyText n -> Int
forall (n :: Nat). NonEmptyText n -> Int64
forall (n :: Nat). NonEmptyText n -> [Element (NonEmptyText n)]
forall (n :: Nat). NonEmptyText n -> Element (NonEmptyText n)
forall (n :: Nat).
(Element (NonEmptyText n) -> Bool) -> NonEmptyText n -> Bool
forall (n :: Nat).
(Element (NonEmptyText n) -> Element (NonEmptyText n) -> Ordering)
-> NonEmptyText n -> Element (NonEmptyText n)
forall (n :: Nat).
(Element (NonEmptyText n)
 -> Element (NonEmptyText n) -> Element (NonEmptyText n))
-> NonEmptyText n -> Element (NonEmptyText n)
forall (n :: Nat) i. Integral i => NonEmptyText n -> i -> Ordering
forall (n :: Nat) m.
Semigroup m =>
(Element (NonEmptyText n) -> m) -> NonEmptyText n -> m
forall (n :: Nat) m.
Monoid m =>
(Element (NonEmptyText n) -> m) -> NonEmptyText n -> m
forall (n :: Nat) a.
(a -> Element (NonEmptyText n) -> a) -> a -> NonEmptyText n -> a
forall (n :: Nat) b.
(Element (NonEmptyText n) -> b -> b) -> b -> NonEmptyText n -> b
forall (n :: Nat) (m :: * -> *).
Applicative m =>
NonEmptyText n -> (Element (NonEmptyText n) -> m ()) -> m ()
forall (n :: Nat) (m :: * -> *).
Applicative m =>
(Element (NonEmptyText n) -> m ()) -> NonEmptyText n -> m ()
forall (n :: Nat) (m :: * -> *) a.
Monad m =>
(a -> Element (NonEmptyText n) -> m a)
-> a -> NonEmptyText n -> m a
forall (n :: Nat) (f :: * -> *) b.
Applicative f =>
NonEmptyText n -> (Element (NonEmptyText n) -> f b) -> f ()
forall (n :: Nat) (f :: * -> *) b.
Applicative f =>
(Element (NonEmptyText n) -> f b) -> NonEmptyText n -> f ()
forall i. Integral i => NonEmptyText n -> i -> Ordering
forall m.
Semigroup m =>
(Element (NonEmptyText n) -> m) -> NonEmptyText n -> m
forall m.
Monoid m =>
(Element (NonEmptyText n) -> m) -> NonEmptyText n -> m
forall a.
(a -> Element (NonEmptyText n) -> a) -> a -> NonEmptyText n -> a
forall b.
(Element (NonEmptyText n) -> b -> b) -> b -> NonEmptyText n -> b
forall mono.
(forall m. Monoid m => (Element mono -> m) -> mono -> m)
-> (forall b. (Element mono -> b -> b) -> b -> mono -> b)
-> (forall a. (a -> Element mono -> a) -> a -> mono -> a)
-> (mono -> [Element mono])
-> ((Element mono -> Bool) -> mono -> Bool)
-> ((Element mono -> Bool) -> mono -> Bool)
-> (mono -> Bool)
-> (mono -> Int)
-> (mono -> Int64)
-> (forall i. Integral i => mono -> i -> Ordering)
-> (forall (f :: * -> *) b.
    Applicative f =>
    (Element mono -> f b) -> mono -> f ())
-> (forall (f :: * -> *) b.
    Applicative f =>
    mono -> (Element mono -> f b) -> f ())
-> (forall (m :: * -> *).
    Applicative m =>
    (Element mono -> m ()) -> mono -> m ())
-> (forall (m :: * -> *).
    Applicative m =>
    mono -> (Element mono -> m ()) -> m ())
-> (forall (m :: * -> *) a.
    Monad m =>
    (a -> Element mono -> m a) -> a -> mono -> m a)
-> (forall m. Semigroup m => (Element mono -> m) -> mono -> m)
-> ((Element mono -> Element mono -> Element mono)
    -> mono -> Element mono)
-> ((Element mono -> Element mono -> Element mono)
    -> mono -> Element mono)
-> (mono -> Element mono)
-> (mono -> Element mono)
-> (mono -> Element mono)
-> (mono -> Element mono)
-> ((Element mono -> Element mono -> Ordering)
    -> mono -> Element mono)
-> ((Element mono -> Element mono -> Ordering)
    -> mono -> Element mono)
-> (Eq (Element mono) => Element mono -> mono -> Bool)
-> (Eq (Element mono) => Element mono -> mono -> Bool)
-> MonoFoldable mono
forall (m :: * -> *).
Applicative m =>
NonEmptyText n -> (Element (NonEmptyText n) -> m ()) -> m ()
forall (m :: * -> *).
Applicative m =>
(Element (NonEmptyText n) -> m ()) -> NonEmptyText n -> m ()
forall (m :: * -> *) a.
Monad m =>
(a -> Element (NonEmptyText n) -> m a)
-> a -> NonEmptyText n -> m a
forall (f :: * -> *) b.
Applicative f =>
NonEmptyText n -> (Element (NonEmptyText n) -> f b) -> f ()
forall (f :: * -> *) b.
Applicative f =>
(Element (NonEmptyText n) -> f b) -> NonEmptyText n -> f ()
$cofoldMap :: forall (n :: Nat) m.
Monoid m =>
(Element (NonEmptyText n) -> m) -> NonEmptyText n -> m
ofoldMap :: forall m.
Monoid m =>
(Element (NonEmptyText n) -> m) -> NonEmptyText n -> m
$cofoldr :: forall (n :: Nat) b.
(Element (NonEmptyText n) -> b -> b) -> b -> NonEmptyText n -> b
ofoldr :: forall b.
(Element (NonEmptyText n) -> b -> b) -> b -> NonEmptyText n -> b
$cofoldl' :: forall (n :: Nat) a.
(a -> Element (NonEmptyText n) -> a) -> a -> NonEmptyText n -> a
ofoldl' :: forall a.
(a -> Element (NonEmptyText n) -> a) -> a -> NonEmptyText n -> a
$cotoList :: forall (n :: Nat). NonEmptyText n -> [Element (NonEmptyText n)]
otoList :: NonEmptyText n -> [Element (NonEmptyText n)]
$coall :: forall (n :: Nat).
(Element (NonEmptyText n) -> Bool) -> NonEmptyText n -> Bool
oall :: (Element (NonEmptyText n) -> Bool) -> NonEmptyText n -> Bool
$coany :: forall (n :: Nat).
(Element (NonEmptyText n) -> Bool) -> NonEmptyText n -> Bool
oany :: (Element (NonEmptyText n) -> Bool) -> NonEmptyText n -> Bool
$conull :: forall (n :: Nat). NonEmptyText n -> Bool
onull :: NonEmptyText n -> Bool
$colength :: forall (n :: Nat). NonEmptyText n -> Int
olength :: NonEmptyText n -> Int
$colength64 :: forall (n :: Nat). NonEmptyText n -> Int64
olength64 :: NonEmptyText n -> Int64
$cocompareLength :: forall (n :: Nat) i. Integral i => NonEmptyText n -> i -> Ordering
ocompareLength :: forall i. Integral i => NonEmptyText n -> i -> Ordering
$cotraverse_ :: forall (n :: Nat) (f :: * -> *) b.
Applicative f =>
(Element (NonEmptyText n) -> f b) -> NonEmptyText n -> f ()
otraverse_ :: forall (f :: * -> *) b.
Applicative f =>
(Element (NonEmptyText n) -> f b) -> NonEmptyText n -> f ()
$cofor_ :: forall (n :: Nat) (f :: * -> *) b.
Applicative f =>
NonEmptyText n -> (Element (NonEmptyText n) -> f b) -> f ()
ofor_ :: forall (f :: * -> *) b.
Applicative f =>
NonEmptyText n -> (Element (NonEmptyText n) -> f b) -> f ()
$comapM_ :: forall (n :: Nat) (m :: * -> *).
Applicative m =>
(Element (NonEmptyText n) -> m ()) -> NonEmptyText n -> m ()
omapM_ :: forall (m :: * -> *).
Applicative m =>
(Element (NonEmptyText n) -> m ()) -> NonEmptyText n -> m ()
$coforM_ :: forall (n :: Nat) (m :: * -> *).
Applicative m =>
NonEmptyText n -> (Element (NonEmptyText n) -> m ()) -> m ()
oforM_ :: forall (m :: * -> *).
Applicative m =>
NonEmptyText n -> (Element (NonEmptyText n) -> m ()) -> m ()
$cofoldlM :: forall (n :: Nat) (m :: * -> *) a.
Monad m =>
(a -> Element (NonEmptyText n) -> m a)
-> a -> NonEmptyText n -> m a
ofoldlM :: forall (m :: * -> *) a.
Monad m =>
(a -> Element (NonEmptyText n) -> m a)
-> a -> NonEmptyText n -> m a
$cofoldMap1Ex :: forall (n :: Nat) m.
Semigroup m =>
(Element (NonEmptyText n) -> m) -> NonEmptyText n -> m
ofoldMap1Ex :: forall m.
Semigroup m =>
(Element (NonEmptyText n) -> m) -> NonEmptyText n -> m
$cofoldr1Ex :: forall (n :: Nat).
(Element (NonEmptyText n)
 -> Element (NonEmptyText n) -> Element (NonEmptyText n))
-> NonEmptyText n -> Element (NonEmptyText n)
ofoldr1Ex :: (Element (NonEmptyText n)
 -> Element (NonEmptyText n) -> Element (NonEmptyText n))
-> NonEmptyText n -> Element (NonEmptyText n)
$cofoldl1Ex' :: forall (n :: Nat).
(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)
$cheadEx :: forall (n :: Nat). NonEmptyText n -> Element (NonEmptyText n)
headEx :: NonEmptyText n -> Element (NonEmptyText n)
$clastEx :: forall (n :: Nat). NonEmptyText n -> Element (NonEmptyText n)
lastEx :: NonEmptyText n -> Element (NonEmptyText n)
$cunsafeHead :: forall (n :: Nat). NonEmptyText n -> Element (NonEmptyText n)
unsafeHead :: NonEmptyText n -> Element (NonEmptyText n)
$cunsafeLast :: forall (n :: Nat). NonEmptyText n -> Element (NonEmptyText n)
unsafeLast :: NonEmptyText n -> Element (NonEmptyText n)
$cmaximumByEx :: forall (n :: Nat).
(Element (NonEmptyText n) -> Element (NonEmptyText n) -> Ordering)
-> NonEmptyText n -> Element (NonEmptyText n)
maximumByEx :: (Element (NonEmptyText n) -> Element (NonEmptyText n) -> Ordering)
-> NonEmptyText n -> Element (NonEmptyText n)
$cminimumByEx :: forall (n :: Nat).
(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)
$coelem :: forall (n :: Nat).
Eq (Element (NonEmptyText n)) =>
Element (NonEmptyText n) -> NonEmptyText n -> Bool
oelem :: Eq (Element (NonEmptyText n)) =>
Element (NonEmptyText n) -> NonEmptyText n -> Bool
$conotElem :: forall (n :: Nat).
Eq (Element (NonEmptyText n)) =>
Element (NonEmptyText n) -> NonEmptyText n -> Bool
onotElem :: Eq (Element (NonEmptyText n)) =>
Element (NonEmptyText n) -> NonEmptyText n -> Bool
MonoFoldable, Eq (NonEmptyText n)
Eq (NonEmptyText n) =>
(Int -> NonEmptyText n -> Int)
-> (NonEmptyText n -> Int) -> Hashable (NonEmptyText n)
Int -> NonEmptyText n -> Int
NonEmptyText n -> Int
forall (n :: Nat). Eq (NonEmptyText n)
forall (n :: Nat). Int -> NonEmptyText n -> Int
forall (n :: Nat). NonEmptyText n -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: forall (n :: Nat). Int -> NonEmptyText n -> Int
hashWithSalt :: Int -> NonEmptyText n -> Int
$chash :: forall (n :: Nat). NonEmptyText n -> Int
hash :: NonEmptyText n -> Int
Hashable, NonEmptyText n -> ()
(NonEmptyText n -> ()) -> NFData (NonEmptyText n)
forall (n :: Nat). NonEmptyText n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall (n :: Nat). NonEmptyText n -> ()
rnf :: NonEmptyText n -> ()
NFData)
type instance Element (NonEmptyText _n) = Char
instance (KnownNat n, 1 <= n) => FromJSON (NonEmptyText n) where
  parseJSON :: Value -> Parser (NonEmptyText n)
parseJSON = String
-> (Text -> Parser (NonEmptyText n))
-> Value
-> Parser (NonEmptyText n)
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"NonEmptyText" ((Text -> Parser (NonEmptyText n))
 -> Value -> Parser (NonEmptyText n))
-> (Text -> Parser (NonEmptyText n))
-> Value
-> Parser (NonEmptyText n)
forall a b. (a -> b) -> a -> b
$ \Text
t -> do
    Text -> Parser ()
forall {m :: * -> *}. MonadFail m => Text -> m ()
performInboundValidations Text
t
    case Text -> Maybe (NonEmptyText n)
forall (n :: Nat).
(KnownNat n, 1 <= n) =>
Text -> Maybe (NonEmptyText n)
mkNonEmptyText Text
t of
      Maybe (NonEmptyText n)
Nothing -> String -> Parser (NonEmptyText n)
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser (NonEmptyText n))
-> String -> Parser (NonEmptyText n)
forall a b. (a -> b) -> a -> b
$ String
"Data/StringVariants/NonEmptyText.hs: invalid NonEmptyText: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
t
      Just NonEmptyText n
nonEmptyText -> NonEmptyText n -> Parser (NonEmptyText n)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NonEmptyText n
nonEmptyText
    where
      
      
      
      
      
      
      performInboundValidations :: Text -> m ()
performInboundValidations Text
t = do
        Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text -> Bool
textHasNoMeaningfulContent Text
t) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
          String -> m ()
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$
            String
"Data/StringVariants/NonEmptyText.hs: NonEmptyText has no meaningful content in the field: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
t
        Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\NUL') Text
t) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
          String -> m ()
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$
            String
"Data/StringVariants/NonEmptyText.hs: NonEmptyText has a \\NUL byte in its contents: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
t
instance ConvertibleStrings (NonEmptyText n) Text where
  convertString :: NonEmptyText n -> Text
convertString (NonEmptyText Text
t) = Text
t
instance ConvertibleStrings (NonEmptyText n) String where
  convertString :: NonEmptyText n -> String
convertString (NonEmptyText Text
t) = Text -> String
forall a b. ConvertibleStrings a b => a -> b
cs Text
t
instance ConvertibleStrings (NonEmptyText n) ByteString where
  convertString :: NonEmptyText n -> ByteString
convertString (NonEmptyText Text
t) = Text -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs Text
t
instance (KnownNat n, 1 <= n) => Arbitrary (NonEmptyText n) where
  arbitrary :: Gen (NonEmptyText n)
arbitrary =
    forall (n :: Nat). Text -> NonEmptyText n
NonEmptyText @n (Text -> NonEmptyText n) -> Gen Text -> Gen (NonEmptyText n)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
      Int
size <- (Int, Int) -> Gen Int
chooseInt (Int
1, Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall {k} (t :: k). Proxy t
Proxy :: Proxy n)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
      
      String
str <- Index String -> Gen (Element String) -> Gen String
forall seq (m :: * -> *).
(IsSequence seq, Monad m) =>
Index seq -> m (Element seq) -> m seq
forall (m :: * -> *).
Monad m =>
Index String -> m (Element String) -> m String
replicateM Int
Index String
size (Gen (Element String) -> Gen String)
-> Gen (Element String) -> Gen String
forall a b. (a -> b) -> a -> b
$ String -> Gen Char
forall a. HasCallStack => [a] -> Gen a
elements [Char
'0' .. Char
'z']
      pure $ String -> Text
T.pack String
str
instance
  TypeError
        ( 'Text "An instance of 'Semigroup (NonEmptyText n)' would violate the "
    ' :<>: 'Text "length guarantees."
    ' :$$: 'Text "Please use '(<>|)' or 'concatWithSpace' to combine the values."
        )
  => Semigroup (NonEmptyText n) where
  <> :: NonEmptyText n -> NonEmptyText n -> NonEmptyText n
(<>) = String -> NonEmptyText n -> NonEmptyText n -> NonEmptyText n
forall a. HasCallStack => String -> a
error String
"unreachable"
mkNonEmptyText :: forall n. (KnownNat n, 1 <= n) => Text -> Maybe (NonEmptyText n)
mkNonEmptyText :: forall (n :: Nat).
(KnownNat n, 1 <= n) =>
Text -> Maybe (NonEmptyText n)
mkNonEmptyText Text
t
  | Text -> Int -> Ordering
T.compareLength Text
stripped (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall (t :: Nat). Proxy t
forall {k} (t :: k). Proxy t
Proxy @n)) Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT = Maybe (NonEmptyText n)
forall a. Maybe a
Nothing
  | Text -> Bool
textIsWhitespace Text
stripped = Maybe (NonEmptyText n)
forall a. Maybe a
Nothing
  | Bool
otherwise = NonEmptyText n -> Maybe (NonEmptyText n)
forall a. a -> Maybe a
Just (Text -> NonEmptyText n
forall (n :: Nat). Text -> NonEmptyText n
NonEmptyText Text
stripped)
  where
    stripped :: Text
stripped = (Char -> Bool) -> Text -> Text
T.filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\NUL') (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip Text
t
mkNonEmptyTextWithTruncate :: forall n. (KnownNat n, 1 <= n) => Text -> Maybe (NonEmptyText n)
mkNonEmptyTextWithTruncate :: forall (n :: Nat).
(KnownNat n, 1 <= n) =>
Text -> Maybe (NonEmptyText n)
mkNonEmptyTextWithTruncate Text
t
  | Text -> Bool
textIsWhitespace Text
stripped = Maybe (NonEmptyText n)
forall a. Maybe a
Nothing
  | Bool
otherwise = NonEmptyText n -> Maybe (NonEmptyText n)
forall a. a -> Maybe a
Just (Text -> NonEmptyText n
forall (n :: Nat). Text -> NonEmptyText n
NonEmptyText (Text -> NonEmptyText n) -> Text -> NonEmptyText n
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.stripEnd (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.take (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall (t :: Nat). Proxy t
forall {k} (t :: k). Proxy t
Proxy @n)) Text
stripped)
  where
    stripped :: Text
stripped = (Char -> Bool) -> Text -> Text
T.filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\NUL') (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.stripStart Text
t
unsafeMkNonEmptyText :: forall n. (KnownNat n, 1 <= n) => Text -> NonEmptyText n
unsafeMkNonEmptyText :: forall (n :: Nat). (KnownNat n, 1 <= n) => Text -> NonEmptyText n
unsafeMkNonEmptyText = Text -> NonEmptyText n
forall (n :: Nat). Text -> NonEmptyText n
NonEmptyText
widen :: (1 <= n, n <= m) => NonEmptyText n -> NonEmptyText m
widen :: forall (n :: Nat) (m :: Nat).
(1 <= n, n <= m) =>
NonEmptyText n -> NonEmptyText m
widen = NonEmptyText n -> NonEmptyText m
forall a b. Coercible a b => a -> b
coerce
compileNonEmptyTextKnownLength :: QuasiQuoter
compileNonEmptyTextKnownLength :: QuasiQuoter
compileNonEmptyTextKnownLength =
  QuasiQuoter
    { quoteExp :: String -> Q Exp
quoteExp = \String
s -> do
        let txt :: Text
txt = String -> Text
T.pack String
s
        if Text -> Bool
textHasNoMeaningfulContent Text
txt
          then String -> Q Exp
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid NonEmptyText. Must have at least one non-whitespace, non-control character."
          else [|NonEmptyText $(Text -> Q Exp
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
forall (m :: * -> *). Quote m => Text -> m Exp
lift Text
txt) :: NonEmptyText $(Type -> Q Type
forall a. a -> Q a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Type -> Q Type) -> Type -> Q Type
forall a b. (a -> b) -> a -> b
$ TyLit -> Type
LitT (TyLit -> Type) -> TyLit -> Type
forall a b. (a -> b) -> a -> b
$ Integer -> TyLit
NumTyLit (Integer -> TyLit) -> Integer -> TyLit
forall a b. (a -> b) -> a -> b
$ Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
txt)|]
    , quotePat :: String -> Q Pat
quotePat = String -> String -> Q Pat
forall a. HasCallStack => String -> a
error String
"Known-length NonEmptyText is not currently supported as a pattern"
    , quoteDec :: String -> Q [Dec]
quoteDec = String -> String -> Q [Dec]
forall a. HasCallStack => String -> a
error String
"NonEmptyText is not supported at top-level"
    , quoteType :: String -> Q Type
quoteType = String -> String -> Q Type
forall a. HasCallStack => String -> a
error String
"NonEmptyText is not supported as a type"
    }