text-ascii-1.1: ASCII string and character processing.
Copyright(C) 2021 Koz Ross
LicenseApache 2.0
MaintainerKoz Ross <koz.ross@retro-freedom.nz>
Stabilitystable
PortabilityGHC only
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Ascii.Unsafe

Description

A wrapper for partial type class instances and functions.

This module is designed for qualified importing:

import qualified Text.Ascii.Unsafe as Unsafe
Synopsis

Types

newtype Unsafe (a :: Type) Source #

A wrapper for a type, designating that partial type class methods or other functions are available for it.

We set the role of the type argument of Unsafe to nominal. Among other things, it means that this type can't be coerced or derived through. This ensures clear indication when (and to what extent) non-total operations occur in any code using them.

Since: 1.0.1

Constructors

Unsafe 

Fields

Instances

Instances details
Functor Unsafe Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Methods

fmap :: (a -> b) -> Unsafe a -> Unsafe b #

(<$) :: a -> Unsafe b -> Unsafe a #

Monoid a => Monoid (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Methods

mempty :: Unsafe a #

mappend :: Unsafe a -> Unsafe a -> Unsafe a #

mconcat :: [Unsafe a] -> Unsafe a #

Semigroup a => Semigroup (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Methods

(<>) :: Unsafe a -> Unsafe a -> Unsafe a #

sconcat :: NonEmpty (Unsafe a) -> Unsafe a #

stimes :: Integral b => b -> Unsafe a -> Unsafe a #

Bounded a => Bounded (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Methods

minBound :: Unsafe a #

maxBound :: Unsafe a #

Enum (Unsafe AsciiChar) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

IsList a => IsList (Unsafe a) Source # 
Instance details

Defined in Text.Ascii.Unsafe

Associated Types

type Item (Unsafe a) #

Methods

fromList :: [Item (Unsafe a)] -> Unsafe a #

fromListN :: Int -> [Item (Unsafe a)] -> Unsafe a #

toList :: Unsafe a -> [Item (Unsafe a)] #

Read (Unsafe AsciiChar) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Read (Unsafe AsciiText) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Show a => Show (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Methods

showsPrec :: Int -> Unsafe a -> ShowS #

show :: Unsafe a -> String #

showList :: [Unsafe a] -> ShowS #

FoldCase a => FoldCase (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Methods

foldCase :: Unsafe a -> Unsafe a #

foldCaseList :: [Unsafe a] -> [Unsafe a]

NFData a => NFData (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Methods

rnf :: Unsafe a -> () #

Eq a => Eq (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Methods

(==) :: Unsafe a -> Unsafe a -> Bool #

(/=) :: Unsafe a -> Unsafe a -> Bool #

Ord a => Ord (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Methods

compare :: Unsafe a -> Unsafe a -> Ordering #

(<) :: Unsafe a -> Unsafe a -> Bool #

(<=) :: Unsafe a -> Unsafe a -> Bool #

(>) :: Unsafe a -> Unsafe a -> Bool #

(>=) :: Unsafe a -> Unsafe a -> Bool #

max :: Unsafe a -> Unsafe a -> Unsafe a #

min :: Unsafe a -> Unsafe a -> Unsafe a #

Hashable a => Hashable (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

Methods

hashWithSalt :: Int -> Unsafe a -> Int #

hash :: Unsafe a -> Int #

Stream a => Stream (Unsafe a) Source # 
Instance details

Defined in Text.Ascii.Unsafe

Associated Types

type Token (Unsafe a) #

type Tokens (Unsafe a) #

TraversableStream a => TraversableStream (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

VisualStream a => VisualStream (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

type Item (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

type Item (Unsafe a) = Item a
type Token (Unsafe a) Source #

Since: 1.0.1

Instance details

Defined in Text.Ascii.Unsafe

type Token (Unsafe a) = Token a
type Tokens (Unsafe a) Source # 
Instance details

Defined in Text.Ascii.Unsafe

type Tokens (Unsafe a) = Tokens a

Text functions

head :: Unsafe AsciiText -> AsciiChar Source #

Yield the first character of the text.

Requirements: Text is not empty.

>>> head . Unsafe $ [ascii| "catboy" |]
'0x63'

Complexity: \(\Theta(1)\)

Since: 1.0.1

last :: Unsafe AsciiText -> AsciiChar Source #

Yield the last character of the text.

Requirements: Text is not empty.

>>> last . Unsafe $ [ascii| "catboy" |]
'0x79'

Complexity: \(\Theta(1)\)

Since: 1.0.1

tail :: Unsafe AsciiText -> Unsafe AsciiText Source #

Yield the text without its first character.

Requirements: Text is not empty.

>>> tail . Unsafe $ [ascii| "catboy" |]
"atboy"

Complexity: \(\Theta(1)\)

Since: 1.0.1

init :: Unsafe AsciiText -> Unsafe AsciiText Source #

Yield the text without its last character.

Requirements: Text is not empty.

>>> init . Unsafe $ [ascii| "catboy" |]
"catbo"

Complexity: \(\Theta(1)\)

Since: 1.0.1

foldl1 :: (AsciiChar -> AsciiChar -> AsciiChar) -> Unsafe AsciiText -> AsciiChar Source #

Left-associative fold of a text without a base case.

Requirements: Text is not empty.

Complexity: \(\Theta(n)\)

Since: 1.0.1

foldl1' :: (AsciiChar -> AsciiChar -> AsciiChar) -> Unsafe AsciiText -> AsciiChar Source #

Left-associative fold of a text without a base case, strict in the accumulator.

Requirements: Text is not empty.

Complexity: \(\Theta(n)\)

Since: 1.0.1

foldr1 :: (AsciiChar -> AsciiChar -> AsciiChar) -> Unsafe AsciiText -> AsciiChar Source #

Right-associative fold of a text without a base case.

Requirements: Text is not empty.

Complexity: \(\Theta(n)\)

Since: 1.0.1

foldr1' :: (AsciiChar -> AsciiChar -> AsciiChar) -> Unsafe AsciiText -> AsciiChar Source #

Right-associative fold of a text without a base case, strict in the accumulator.

Requirements: Text is not empty.

Complexity: \(\Theta(n)\)

Since: 1.0.1

maximum :: Unsafe AsciiText -> AsciiChar Source #

Yield the character in the text whose byte representation is numerically the largest.

Requirements: Text is not empty.

>>> maximum . Unsafe $ [ascii| "catboy" |]
'0x79'
>>> maximum . Unsafe $ [ascii| "nyan~" |]
'0x7e'

Complexity: \(\Theta(n)\)

Since: 1.0.1

minimum :: Unsafe AsciiText -> AsciiChar Source #

Yield the character in the text whose byte representation is numerically the smallest.

Requirements: Text is not empty.

>>> minimum . Unsafe $ [ascii| "catboy" |]
'0x61'
>>> minimum . Unsafe $ [ascii| " nyan" |]
'0x20'

Complexity: \(\Theta(n)\)

Since: 1.0.1

scanl1 Source #

Arguments

:: (AsciiChar -> AsciiChar -> AsciiChar)

accumulator -> element -> new accumulator

-> Unsafe AsciiText

Input of length \(n\)

-> Unsafe AsciiText

Output of length \(n - 1\)

scanl1 is similar to foldl1, but returns a list of successive values from the left.

Requirements: Text is not empty.

Complexity: \(\Theta(n)\)

Since: 1.0.1

scanr1 Source #

Arguments

:: (AsciiChar -> AsciiChar -> AsciiChar)

element -> accumulator -> new accumulator

-> Unsafe AsciiText

Input of length \(n\)

-> Unsafe AsciiText

Output of length \(n - 1\)

scanr1 is similar to foldr1, but returns a list of successive values from the right.

Requirements: Text is not empty.

Complexity: \(\Theta(n)\)

Since: 1.0.1

index :: Unsafe AsciiText -> Int -> AsciiChar Source #

Yield the character at the given position.

Requirements: The position must be at least 0, and at most the length of the text - 1.

>>> index (Unsafe [ascii| "catboy" |]) 0
'0x63'
>>> index (Unsafe $ [ascii| "catboy" |]) 4
'0x6f'

Complexity: \(\Theta(1)\)

Since: 1.0.1