static-text-0.2.0.1: Lists, Texts, ByteStrings and Vectors of statically known length

Safe HaskellNone
LanguageHaskell2010

Data.StaticText

Contents

Description

static-text provides type-level safety for basic operations on string-like types (finite lists of elements), such as Data.Text, String (and all lists), Data.ByteString and Data.Vector. Use it when you need static guarantee on lengths of strings produced in your code.

An example application would be a network exchange protocol built of packets with fixed-width fields:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
import Data.StaticText

mkPacket :: ByteString -> Static 32 ByteString
mkPacket inp =
  -- 5-character version signature
  $(st "PKT10") `append`
  -- 25-character payload
  payload `append`
  -- 2-character payload checksum
  checksum
  where
    payload = createLeft 0x20 inp
    checksum :: Static 2 ByteString
    checksum = createLeft 0x20 $
               pack $ show $ Data.Static.length payload `mod` 100

message :: Static 64 ByteString
message = mkPacket "Hello" `append` mkPacket "world"

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

Constructing static texts

See also unsafeCreate

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"

st :: LitS -> Q Exp Source #

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.

create :: forall a i. (IsStaticText a, KnownNat i) => a -> Maybe (Static a i) Source #

Attempt to 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.

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.

length :: forall a m. KnownNat m => Static a m -> Int Source #

Obtain value-level length.

IsStaticText class

class IsStaticText a where Source #

Class of types which can be assigned a type-level length.

Minimal complete definition

unsafeCreate, unwrap, length, append, replicate, map, take, drop

Associated Types

data 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.

type Elem a Source #

Basic element type. For IsStaticText [a], this is a.

Methods

unsafeCreate :: a -> Static a i Source #

Simply wrap a value in a Static as is, assuming any length.

WARNING Use it only when you know what you're doing.

For example, an expression like

unsafeCreate "somestring" :: Static String 50

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.

When writing new IsStaticText instances, make this simply apply the constructor of Static.

unwrap :: Static a i -> a Source #

Forget type-level length, obtaining the underlying value.

Instances

IsStaticText ShortByteString Source #

IsStaticText instance for ShortByteString uses intermediate ByteStrings (pinned) for all modification operations.

IsStaticText ByteString Source # 
IsStaticText Text Source # 

Associated Types

data Static Text (i :: Nat) :: * Source #

type Elem Text :: * Source #

IsStaticText [a] Source # 

Associated Types

data Static [a] (i :: Nat) :: * Source #

type Elem [a] :: * Source #

Methods

unsafeCreate :: [a] -> Static [a] i Source #

unwrap :: Static [a] i -> [a] Source #

length :: [a] -> Int Source #

append :: [a] -> [a] -> [a] Source #

replicate :: Int -> Elem [a] -> [a] Source #

map :: (Elem [a] -> Elem [a]) -> [a] -> [a] Source #

take :: Int -> [a] -> [a] Source #

drop :: Int -> [a] -> [a] Source #

IsStaticText (Vector a) Source # 

Associated Types

data Static (Vector a) (i :: Nat) :: * Source #

type Elem (Vector a) :: * Source #

Methods

unsafeCreate :: Vector a -> Static (Vector a) i Source #

unwrap :: Static (Vector a) i -> Vector a Source #

length :: Vector a -> Int Source #

append :: Vector a -> Vector a -> Vector a Source #

replicate :: Int -> Elem (Vector a) -> Vector a Source #

map :: (Elem (Vector a) -> Elem (Vector a)) -> Vector a -> Vector a Source #

take :: Int -> Vector a -> Vector a Source #

drop :: Int -> Vector a -> Vector a Source #