static-text-0.2.0.7: Lists, Texts, ByteStrings and Vectors of statically known length
Safe HaskellNone
LanguageHaskell2010

Data.StaticText.Class

Description

Class of statically-sized text-like types.

Synopsis

Documentation

class IsStaticText a where Source #

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

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.

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.

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 #

Instances

Instances details
IsStaticText ShortByteString Source #

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

Instance details

Defined in Data.StaticText.Class

IsStaticText ByteString Source # 
Instance details

Defined in Data.StaticText.Class

Associated Types

data Static ByteString i Source #

type Elem ByteString Source #

IsStaticText Text Source # 
Instance details

Defined in Data.StaticText.Class

Associated Types

data Static Text i Source #

type Elem Text Source #

Methods

unsafeCreate :: forall (i :: Nat). Text -> Static Text i Source #

unwrap :: forall (i :: Nat). Static Text i -> Text Source #

length :: Text -> Int Source #

append :: Text -> Text -> Text Source #

replicate :: Int -> Elem Text -> Text Source #

map :: (Elem Text -> Elem Text) -> Text -> Text Source #

take :: Int -> Text -> Text Source #

drop :: Int -> Text -> Text Source #

IsStaticText [a] Source # 
Instance details

Defined in Data.StaticText.Class

Associated Types

data Static [a] i Source #

type Elem [a] Source #

Methods

unsafeCreate :: forall (i :: Nat). [a] -> Static [a] i Source #

unwrap :: forall (i :: Nat). 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 # 
Instance details

Defined in Data.StaticText.Class

Associated Types

data Static (Vector a) i Source #

type Elem (Vector a) Source #

Methods

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

unwrap :: forall (i :: Nat). 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 #