Safe Haskell | None |
---|---|
Language | Haskell2010 |
static-text combinators are defined for members of IsStaticText
class. The package includes IsStaticText
instances for several
common types.
This module is meant to be imported qualifed, e.g.
import qualified Data.StaticText as S
Synopsis
- create :: forall a i. (IsStaticText a, KnownNat i) => a -> Maybe (Static a i)
- createLeft :: forall a i. (IsStaticText a, KnownNat i) => Elem a -> a -> Static a i
- createRight :: forall a i. (IsStaticText a, KnownNat i) => Elem a -> a -> Static a i
- st :: LitS -> Q Exp
- replicate :: forall a i. (IsStaticText a, KnownNat i) => Elem a -> Static a i
- append :: forall a m n. IsStaticText a => Static a m -> Static a n -> Static a (m + n)
- take :: forall a m n. (IsStaticText a, KnownNat m, KnownNat n, n <= m) => Static a m -> Static a n
- drop :: forall a m n. (IsStaticText a, KnownNat m, KnownNat n, n <= m) => Static a m -> Static a n
- map :: IsStaticText a => (Elem a -> Elem a) -> Static a m -> Static a m
- padLeft :: forall a m n. (IsStaticText a, KnownNat m, KnownNat (n - m), n ~ ((n - m) + m), m <= n) => Elem a -> Static a m -> Static a n
- padRight :: forall a m n. (IsStaticText a, KnownNat m, KnownNat (n - m), n ~ (m + (n - m)), m <= n) => Elem a -> Static a m -> Static a n
- length :: forall a m. KnownNat m => Static a m -> Int
- data family Static a (i :: Nat)
- class IsStaticText a where
- type Elem a
- unsafeCreate :: a -> Static a i
- unwrap :: Static a i -> a
Constructing static texts
See also unsafeCreate
create :: forall a i. (IsStaticText a, KnownNat i) => a -> Maybe (Static a i) Source #
Safely create a Static if it matches target length.
>>>
create "foobar" :: Maybe (Static String 6)
Just "foobar">>>
create "barbaz" :: Maybe (Static String 8)
Nothing
This is safer than unsafeCreate
and unlike with createLeft
/
createRight
the source value is left unchanged. However, this
implies a further run-time check for Nothing values.
createLeft :: forall a i. (IsStaticText a, KnownNat i) => Elem a -> a -> Static a i Source #
Safely create a Static, possibly altering the source to match target length. If target length is less than that of the source, the source gets truncated. If target length is greater, the source is padded using the provided basic element. Elements on the left are preferred.
>>>
createLeft ' ' "foobarbaz" :: Static String 6
"foobar">>>
createLeft '#' "foobarbaz" :: Static String 12
"foobarbaz###"
createRight :: forall a i. (IsStaticText a, KnownNat i) => Elem a -> a -> Static a i Source #
Just like createLeft
, except that elements on the right are preferred.
>>>
createRight '@' "foobarbaz" :: Static String 6
"barbaz">>>
createRight '!' "foobarbaz" :: Static String 12
"!!!foobarbaz"
Type-safe Static constructor macro for string literals.
Example:
$(st "Foobar")
compiles to
unsafeCreate "Foobar" :: forall a. (IsString a, IsStaticText a) => Static a 6
where 6 is the string length obtained at compile time.
replicate :: forall a i. (IsStaticText a, KnownNat i) => Elem a -> Static a i Source #
Construct a new Static from a basic element.
>>>
replicate '=' :: Static String 10
"=========="
Working with static texts
append :: forall a m n. IsStaticText a => Static a m -> Static a n -> Static a (m + n) Source #
Append two Statics together.
>>>
append $(st "foo") $(st "bar") :: Static String 6
"foobar"
take :: forall a m n. (IsStaticText a, KnownNat m, KnownNat n, n <= m) => Static a m -> Static a n Source #
Reduce Static length, preferring elements on the left.
>>>
take $(st "Foobar") :: Static String 3
"Foo"
drop :: forall a m n. (IsStaticText a, KnownNat m, KnownNat n, n <= m) => Static a m -> Static a n Source #
Reduce Static length, preferring elements on the right.
>>>
drop $(st "Foobar") :: Static String 2
"ar"
map :: IsStaticText a => (Elem a -> Elem a) -> Static a m -> Static a m Source #
Map a Static to a Static of the same length.
>>>
map toUpper $(st "Hello") :: Static String 5
"HELLO"
padLeft :: forall a m n. (IsStaticText a, KnownNat m, KnownNat (n - m), n ~ ((n - m) + m), m <= n) => Elem a -> Static a m -> Static a n Source #
Fill a Static with extra elements up to target length, padding original elements to the left.
padRight :: forall a m n. (IsStaticText a, KnownNat m, KnownNat (n - m), n ~ (m + (n - m)), m <= n) => Elem a -> Static a m -> Static a n Source #
Like padLeft
, but original elements are padded to the right.
IsStaticText class
data family Static a (i :: Nat) Source #
Data family which wraps values of the underlying type giving
them a type-level length. Static t 6
means a value of type t
of
length 6.
Instances
class IsStaticText a where Source #
Class of types which can be assigned a type-level length.
unsafeCreate :: a -> Static a i Source #
Simply wrap a value in a Static as is, assuming any length.
When implementing new IsStaticText instances, make this simply apply the constructor of Static.
This should only be used to implement IsStaticText.
For example, an expression like
>>>
unsafeCreate "somestring" :: Static String 50
"somestring"
will typecheck, although the stored length information will not match actual string size. This may result in wrong behaviour of all functions defined for IsStaticText.
unwrap :: Static a i -> a Source #
Forget type-level length, obtaining the underlying value.