string-class-0.1.7.0: String class library

Safe HaskellNone
LanguageHaskell2010

Data.String.Class

Synopsis

Documentation

class (StringCells s, StringRWIO s) => Stringy s Source #

String super class

Instances

class (Eq s, Monoid s, IsString s, Typeable s, StringCell (StringCellChar s), StringCell (StringCellAltChar s), ConvGenString s, ConvString s, ConvStrictByteString s, ConvLazyByteString s, ConvText s, ConvLazyText s) => StringCells s where Source #

Minimal complete definition: StringCellChar; StringCellAltChar; toStringCells; fromStringCells; toMainChar; toAltChar; cons; snoc; either all of head, tail, last, and init, or all of uncons and unsnoc; take, take64 or genericTake; drop, drop64, or genericDrop; and length, length64, or genericLength

Minimal complete definition

toStringCells, fromStringCells, cons, snoc, toMainChar, toAltChar

Associated Types

type StringCellChar s Source #

type StringCellAltChar s Source #

Methods

toStringCells :: StringCells s2 => s -> s2 Source #

fromStringCells :: StringCells s2 => s2 -> s Source #

cons :: StringCellChar s -> s -> s infixr 9 Source #

uncons :: s -> (StringCellChar s, s) infixr 9 Source #

snoc :: s -> StringCellChar s -> s Source #

unsnoc :: s -> (s, StringCellChar s) Source #

altCons :: StringCellAltChar s -> s -> s infixr 9 Source #

altUncons :: s -> (StringCellAltChar s, s) infixr 9 Source #

altSnoc :: s -> StringCellAltChar s -> s Source #

altUnsnoc :: s -> (s, StringCellAltChar s) Source #

toMainChar :: StringCell c => c -> Tagged s (StringCellChar s) Source #

toAltChar :: StringCell c => c -> Tagged s (StringCellAltChar s) Source #

append :: s -> s -> s infixr 9 Source #

Append two strings

concat :: [s] -> s Source #

empty :: s Source #

null :: s -> Bool Source #

head :: s -> StringCellChar s Source #

tail :: s -> s Source #

last :: s -> StringCellChar s Source #

init :: s -> s Source #

altHead :: s -> StringCellAltChar s Source #

altLast :: s -> StringCellAltChar s Source #

unfoldr :: (a -> Maybe (StringCellChar s, a)) -> a -> s Source #

Construction of a string; implementations should behave safely with incorrect lengths

The default implementation of unfoldr is independent from that of altUnfoldr, as well as unfoldrN as and altUnfoldrN.

altUnfoldr :: (a -> Maybe (StringCellAltChar s, a)) -> a -> s Source #

unfoldrN :: Int -> (a -> Maybe (StringCellChar s, a)) -> a -> s Source #

altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar s, a)) -> a -> s Source #

unfoldrN64 :: Int64 -> (a -> Maybe (StringCellChar s, a)) -> a -> s Source #

altUnfoldrN64 :: Int64 -> (a -> Maybe (StringCellAltChar s, a)) -> a -> s Source #

index :: s -> Int -> StringCellChar s Source #

Get the character at the given position

Just like drop, drop64, and the variants of those functions, the default definitions of these three variants are independent of each other, and are defined in terms of head and tail, which can be inefficient.

index64 :: s -> Int64 -> StringCellChar s Source #

genericIndex :: Integral i => s -> i -> StringCellChar s Source #

Index a string at any location

Just like the other generic functions of this module, this function can be significantly slower than index, since the function must be able to support arbitrarily large indices. Consider using index or index64, even if you need to coerce the index to an Int.

take :: Int -> s -> s Source #

take64 :: Int64 -> s -> s Source #

genericTake :: Integral i => i -> s -> s Source #

drop :: Int -> s -> s Source #

drop64 :: Int64 -> s -> s Source #

genericDrop :: Integral i => i -> s -> s Source #

length :: s -> Int Source #

length64 :: s -> Int64 Source #

genericLength :: Integral i => s -> i Source #

safeUncons :: s -> Maybe (StringCellChar s, s) Source #

safeUnsnoc :: s -> Maybe (s, StringCellChar s) Source #

safeAltUncons :: s -> Maybe (StringCellAltChar s, s) Source #

safeAltUnsnoc :: s -> Maybe (s, StringCellAltChar s) Source #

safeHead :: s -> Maybe (StringCellChar s) Source #

safeTail :: s -> Maybe s Source #

safeLast :: s -> Maybe (StringCellChar s) Source #

safeInit :: s -> Maybe s Source #

safeAltHead :: s -> Maybe (StringCellAltChar s) Source #

safeAltLast :: s -> Maybe (StringCellAltChar s) Source #

safeIndex :: s -> Int -> Maybe (StringCellChar s) Source #

safeIndex64 :: s -> Int64 -> Maybe (StringCellChar s) Source #

safeGenericIndex :: Integral i => s -> i -> Maybe (StringCellChar s) Source #

safeTake :: Int -> s -> Maybe s Source #

safeTake64 :: Int64 -> s -> Maybe s Source #

safeGenericTake :: Integral i => i -> s -> Maybe s Source #

safeDrop :: Int -> s -> Maybe s Source #

safeDrop64 :: Int64 -> s -> Maybe s Source #

safeGenericDrop :: Integral i => i -> s -> Maybe s Source #

safeUncons2 :: s -> Maybe (StringCellChar s, StringCellChar s, s) Source #

safeUncons3 :: s -> Maybe (StringCellChar s, StringCellChar s, StringCellChar s, s) Source #

safeUncons4 :: s -> Maybe (StringCellChar s, StringCellChar s, StringCellChar s, StringCellChar s, s) Source #

cons2 :: StringCellChar s -> StringCellChar s -> s -> s infixr 9 Source #

cons3 :: StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> s infixr 9 Source #

cons4 :: StringCellChar s -> StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> s infixr 9 Source #

uncons2 :: s -> (StringCellChar s, StringCellChar s, s) infixr 9 Source #

uncons3 :: s -> (StringCellChar s, StringCellChar s, StringCellChar s, s) infixr 9 Source #

uncons4 :: s -> (StringCellChar s, StringCellChar s, StringCellChar s, StringCellChar s, s) infixr 9 Source #

Instances

StringCells String Source # 

Associated Types

type StringCellChar String :: * Source #

type StringCellAltChar String :: * Source #

Methods

toStringCells :: StringCells s2 => String -> s2 Source #

fromStringCells :: StringCells s2 => s2 -> String Source #

cons :: StringCellChar String -> String -> String Source #

uncons :: String -> (StringCellChar String, String) Source #

snoc :: String -> StringCellChar String -> String Source #

unsnoc :: String -> (String, StringCellChar String) Source #

altCons :: StringCellAltChar String -> String -> String Source #

altUncons :: String -> (StringCellAltChar String, String) Source #

altSnoc :: String -> StringCellAltChar String -> String Source #

altUnsnoc :: String -> (String, StringCellAltChar String) Source #

toMainChar :: StringCell c => c -> Tagged * String (StringCellChar String) Source #

toAltChar :: StringCell c => c -> Tagged * String (StringCellAltChar String) Source #

append :: String -> String -> String Source #

concat :: [String] -> String Source #

empty :: String Source #

null :: String -> Bool Source #

head :: String -> StringCellChar String Source #

tail :: String -> String Source #

last :: String -> StringCellChar String Source #

init :: String -> String Source #

altHead :: String -> StringCellAltChar String Source #

altLast :: String -> StringCellAltChar String Source #

unfoldr :: (a -> Maybe (StringCellChar String, a)) -> a -> String Source #

altUnfoldr :: (a -> Maybe (StringCellAltChar String, a)) -> a -> String Source #

unfoldrN :: Int -> (a -> Maybe (StringCellChar String, a)) -> a -> String Source #

altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar String, a)) -> a -> String Source #

unfoldrN64 :: Int64 -> (a -> Maybe (StringCellChar String, a)) -> a -> String Source #

altUnfoldrN64 :: Int64 -> (a -> Maybe (StringCellAltChar String, a)) -> a -> String Source #

index :: String -> Int -> StringCellChar String Source #

index64 :: String -> Int64 -> StringCellChar String Source #

genericIndex :: Integral i => String -> i -> StringCellChar String Source #

take :: Int -> String -> String Source #

take64 :: Int64 -> String -> String Source #

genericTake :: Integral i => i -> String -> String Source #

drop :: Int -> String -> String Source #

drop64 :: Int64 -> String -> String Source #

genericDrop :: Integral i => i -> String -> String Source #

length :: String -> Int Source #

length64 :: String -> Int64 Source #

genericLength :: Integral i => String -> i Source #

safeUncons :: String -> Maybe (StringCellChar String, String) Source #

safeUnsnoc :: String -> Maybe (String, StringCellChar String) Source #

safeAltUncons :: String -> Maybe (StringCellAltChar String, String) Source #

safeAltUnsnoc :: String -> Maybe (String, StringCellAltChar String) Source #

safeHead :: String -> Maybe (StringCellChar String) Source #

safeTail :: String -> Maybe String Source #

safeLast :: String -> Maybe (StringCellChar String) Source #

safeInit :: String -> Maybe String Source #

safeAltHead :: String -> Maybe (StringCellAltChar String) Source #

safeAltLast :: String -> Maybe (StringCellAltChar String) Source #

safeIndex :: String -> Int -> Maybe (StringCellChar String) Source #

safeIndex64 :: String -> Int64 -> Maybe (StringCellChar String) Source #

safeGenericIndex :: Integral i => String -> i -> Maybe (StringCellChar String) Source #

safeTake :: Int -> String -> Maybe String Source #

safeTake64 :: Int64 -> String -> Maybe String Source #

safeGenericTake :: Integral i => i -> String -> Maybe String Source #

safeDrop :: Int -> String -> Maybe String Source #

safeDrop64 :: Int64 -> String -> Maybe String Source #

safeGenericDrop :: Integral i => i -> String -> Maybe String Source #

safeUncons2 :: String -> Maybe (StringCellChar String, StringCellChar String, String) Source #

safeUncons3 :: String -> Maybe (StringCellChar String, StringCellChar String, StringCellChar String, String) Source #

safeUncons4 :: String -> Maybe (StringCellChar String, StringCellChar String, StringCellChar String, StringCellChar String, String) Source #

cons2 :: StringCellChar String -> StringCellChar String -> String -> String Source #

cons3 :: StringCellChar String -> StringCellChar String -> StringCellChar String -> String -> String Source #

cons4 :: StringCellChar String -> StringCellChar String -> StringCellChar String -> StringCellChar String -> String -> String Source #

uncons2 :: String -> (StringCellChar String, StringCellChar String, String) Source #

uncons3 :: String -> (StringCellChar String, StringCellChar String, StringCellChar String, String) Source #

uncons4 :: String -> (StringCellChar String, StringCellChar String, StringCellChar String, StringCellChar String, String) Source #

StringCells ByteString Source # 

Methods

toStringCells :: StringCells s2 => ByteString -> s2 Source #

fromStringCells :: StringCells s2 => s2 -> ByteString Source #

cons :: StringCellChar ByteString -> ByteString -> ByteString Source #

uncons :: ByteString -> (StringCellChar ByteString, ByteString) Source #

snoc :: ByteString -> StringCellChar ByteString -> ByteString Source #

unsnoc :: ByteString -> (ByteString, StringCellChar ByteString) Source #

altCons :: StringCellAltChar ByteString -> ByteString -> ByteString Source #

altUncons :: ByteString -> (StringCellAltChar ByteString, ByteString) Source #

altSnoc :: ByteString -> StringCellAltChar ByteString -> ByteString Source #

altUnsnoc :: ByteString -> (ByteString, StringCellAltChar ByteString) Source #

toMainChar :: StringCell c => c -> Tagged * ByteString (StringCellChar ByteString) Source #

toAltChar :: StringCell c => c -> Tagged * ByteString (StringCellAltChar ByteString) Source #

append :: ByteString -> ByteString -> ByteString Source #

concat :: [ByteString] -> ByteString Source #

empty :: ByteString Source #

null :: ByteString -> Bool Source #

head :: ByteString -> StringCellChar ByteString Source #

tail :: ByteString -> ByteString Source #

last :: ByteString -> StringCellChar ByteString Source #

init :: ByteString -> ByteString Source #

altHead :: ByteString -> StringCellAltChar ByteString Source #

altLast :: ByteString -> StringCellAltChar ByteString Source #

unfoldr :: (a -> Maybe (StringCellChar ByteString, a)) -> a -> ByteString Source #

altUnfoldr :: (a -> Maybe (StringCellAltChar ByteString, a)) -> a -> ByteString Source #

unfoldrN :: Int -> (a -> Maybe (StringCellChar ByteString, a)) -> a -> ByteString Source #

altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar ByteString, a)) -> a -> ByteString Source #

unfoldrN64 :: Int64 -> (a -> Maybe (StringCellChar ByteString, a)) -> a -> ByteString Source #

altUnfoldrN64 :: Int64 -> (a -> Maybe (StringCellAltChar ByteString, a)) -> a -> ByteString Source #

index :: ByteString -> Int -> StringCellChar ByteString Source #

index64 :: ByteString -> Int64 -> StringCellChar ByteString Source #

genericIndex :: Integral i => ByteString -> i -> StringCellChar ByteString Source #

take :: Int -> ByteString -> ByteString Source #

take64 :: Int64 -> ByteString -> ByteString Source #

genericTake :: Integral i => i -> ByteString -> ByteString Source #

drop :: Int -> ByteString -> ByteString Source #

drop64 :: Int64 -> ByteString -> ByteString Source #

genericDrop :: Integral i => i -> ByteString -> ByteString Source #

length :: ByteString -> Int Source #

length64 :: ByteString -> Int64 Source #

genericLength :: Integral i => ByteString -> i Source #

safeUncons :: ByteString -> Maybe (StringCellChar ByteString, ByteString) Source #

safeUnsnoc :: ByteString -> Maybe (ByteString, StringCellChar ByteString) Source #

safeAltUncons :: ByteString -> Maybe (StringCellAltChar ByteString, ByteString) Source #

safeAltUnsnoc :: ByteString -> Maybe (ByteString, StringCellAltChar ByteString) Source #

safeHead :: ByteString -> Maybe (StringCellChar ByteString) Source #

safeTail :: ByteString -> Maybe ByteString Source #

safeLast :: ByteString -> Maybe (StringCellChar ByteString) Source #

safeInit :: ByteString -> Maybe ByteString Source #

safeAltHead :: ByteString -> Maybe (StringCellAltChar ByteString) Source #

safeAltLast :: ByteString -> Maybe (StringCellAltChar ByteString) Source #

safeIndex :: ByteString -> Int -> Maybe (StringCellChar ByteString) Source #

safeIndex64 :: ByteString -> Int64 -> Maybe (StringCellChar ByteString) Source #

safeGenericIndex :: Integral i => ByteString -> i -> Maybe (StringCellChar ByteString) Source #

safeTake :: Int -> ByteString -> Maybe ByteString Source #

safeTake64 :: Int64 -> ByteString -> Maybe ByteString Source #

safeGenericTake :: Integral i => i -> ByteString -> Maybe ByteString Source #

safeDrop :: Int -> ByteString -> Maybe ByteString Source #

safeDrop64 :: Int64 -> ByteString -> Maybe ByteString Source #

safeGenericDrop :: Integral i => i -> ByteString -> Maybe ByteString Source #

safeUncons2 :: ByteString -> Maybe (StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

safeUncons3 :: ByteString -> Maybe (StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

safeUncons4 :: ByteString -> Maybe (StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

cons2 :: StringCellChar ByteString -> StringCellChar ByteString -> ByteString -> ByteString Source #

cons3 :: StringCellChar ByteString -> StringCellChar ByteString -> StringCellChar ByteString -> ByteString -> ByteString Source #

cons4 :: StringCellChar ByteString -> StringCellChar ByteString -> StringCellChar ByteString -> StringCellChar ByteString -> ByteString -> ByteString Source #

uncons2 :: ByteString -> (StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

uncons3 :: ByteString -> (StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

uncons4 :: ByteString -> (StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

StringCells ByteString Source # 

Methods

toStringCells :: StringCells s2 => ByteString -> s2 Source #

fromStringCells :: StringCells s2 => s2 -> ByteString Source #

cons :: StringCellChar ByteString -> ByteString -> ByteString Source #

uncons :: ByteString -> (StringCellChar ByteString, ByteString) Source #

snoc :: ByteString -> StringCellChar ByteString -> ByteString Source #

unsnoc :: ByteString -> (ByteString, StringCellChar ByteString) Source #

altCons :: StringCellAltChar ByteString -> ByteString -> ByteString Source #

altUncons :: ByteString -> (StringCellAltChar ByteString, ByteString) Source #

altSnoc :: ByteString -> StringCellAltChar ByteString -> ByteString Source #

altUnsnoc :: ByteString -> (ByteString, StringCellAltChar ByteString) Source #

toMainChar :: StringCell c => c -> Tagged * ByteString (StringCellChar ByteString) Source #

toAltChar :: StringCell c => c -> Tagged * ByteString (StringCellAltChar ByteString) Source #

append :: ByteString -> ByteString -> ByteString Source #

concat :: [ByteString] -> ByteString Source #

empty :: ByteString Source #

null :: ByteString -> Bool Source #

head :: ByteString -> StringCellChar ByteString Source #

tail :: ByteString -> ByteString Source #

last :: ByteString -> StringCellChar ByteString Source #

init :: ByteString -> ByteString Source #

altHead :: ByteString -> StringCellAltChar ByteString Source #

altLast :: ByteString -> StringCellAltChar ByteString Source #

unfoldr :: (a -> Maybe (StringCellChar ByteString, a)) -> a -> ByteString Source #

altUnfoldr :: (a -> Maybe (StringCellAltChar ByteString, a)) -> a -> ByteString Source #

unfoldrN :: Int -> (a -> Maybe (StringCellChar ByteString, a)) -> a -> ByteString Source #

altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar ByteString, a)) -> a -> ByteString Source #

unfoldrN64 :: Int64 -> (a -> Maybe (StringCellChar ByteString, a)) -> a -> ByteString Source #

altUnfoldrN64 :: Int64 -> (a -> Maybe (StringCellAltChar ByteString, a)) -> a -> ByteString Source #

index :: ByteString -> Int -> StringCellChar ByteString Source #

index64 :: ByteString -> Int64 -> StringCellChar ByteString Source #

genericIndex :: Integral i => ByteString -> i -> StringCellChar ByteString Source #

take :: Int -> ByteString -> ByteString Source #

take64 :: Int64 -> ByteString -> ByteString Source #

genericTake :: Integral i => i -> ByteString -> ByteString Source #

drop :: Int -> ByteString -> ByteString Source #

drop64 :: Int64 -> ByteString -> ByteString Source #

genericDrop :: Integral i => i -> ByteString -> ByteString Source #

length :: ByteString -> Int Source #

length64 :: ByteString -> Int64 Source #

genericLength :: Integral i => ByteString -> i Source #

safeUncons :: ByteString -> Maybe (StringCellChar ByteString, ByteString) Source #

safeUnsnoc :: ByteString -> Maybe (ByteString, StringCellChar ByteString) Source #

safeAltUncons :: ByteString -> Maybe (StringCellAltChar ByteString, ByteString) Source #

safeAltUnsnoc :: ByteString -> Maybe (ByteString, StringCellAltChar ByteString) Source #

safeHead :: ByteString -> Maybe (StringCellChar ByteString) Source #

safeTail :: ByteString -> Maybe ByteString Source #

safeLast :: ByteString -> Maybe (StringCellChar ByteString) Source #

safeInit :: ByteString -> Maybe ByteString Source #

safeAltHead :: ByteString -> Maybe (StringCellAltChar ByteString) Source #

safeAltLast :: ByteString -> Maybe (StringCellAltChar ByteString) Source #

safeIndex :: ByteString -> Int -> Maybe (StringCellChar ByteString) Source #

safeIndex64 :: ByteString -> Int64 -> Maybe (StringCellChar ByteString) Source #

safeGenericIndex :: Integral i => ByteString -> i -> Maybe (StringCellChar ByteString) Source #

safeTake :: Int -> ByteString -> Maybe ByteString Source #

safeTake64 :: Int64 -> ByteString -> Maybe ByteString Source #

safeGenericTake :: Integral i => i -> ByteString -> Maybe ByteString Source #

safeDrop :: Int -> ByteString -> Maybe ByteString Source #

safeDrop64 :: Int64 -> ByteString -> Maybe ByteString Source #

safeGenericDrop :: Integral i => i -> ByteString -> Maybe ByteString Source #

safeUncons2 :: ByteString -> Maybe (StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

safeUncons3 :: ByteString -> Maybe (StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

safeUncons4 :: ByteString -> Maybe (StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

cons2 :: StringCellChar ByteString -> StringCellChar ByteString -> ByteString -> ByteString Source #

cons3 :: StringCellChar ByteString -> StringCellChar ByteString -> StringCellChar ByteString -> ByteString -> ByteString Source #

cons4 :: StringCellChar ByteString -> StringCellChar ByteString -> StringCellChar ByteString -> StringCellChar ByteString -> ByteString -> ByteString Source #

uncons2 :: ByteString -> (StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

uncons3 :: ByteString -> (StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

uncons4 :: ByteString -> (StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, StringCellChar ByteString, ByteString) Source #

StringCells Text Source # 

Associated Types

type StringCellChar Text :: * Source #

type StringCellAltChar Text :: * Source #

Methods

toStringCells :: StringCells s2 => Text -> s2 Source #

fromStringCells :: StringCells s2 => s2 -> Text Source #

cons :: StringCellChar Text -> Text -> Text Source #

uncons :: Text -> (StringCellChar Text, Text) Source #

snoc :: Text -> StringCellChar Text -> Text Source #

unsnoc :: Text -> (Text, StringCellChar Text) Source #

altCons :: StringCellAltChar Text -> Text -> Text Source #

altUncons :: Text -> (StringCellAltChar Text, Text) Source #

altSnoc :: Text -> StringCellAltChar Text -> Text Source #

altUnsnoc :: Text -> (Text, StringCellAltChar Text) Source #

toMainChar :: StringCell c => c -> Tagged * Text (StringCellChar Text) Source #

toAltChar :: StringCell c => c -> Tagged * Text (StringCellAltChar Text) Source #

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

concat :: [Text] -> Text Source #

empty :: Text Source #

null :: Text -> Bool Source #

head :: Text -> StringCellChar Text Source #

tail :: Text -> Text Source #

last :: Text -> StringCellChar Text Source #

init :: Text -> Text Source #

altHead :: Text -> StringCellAltChar Text Source #

altLast :: Text -> StringCellAltChar Text Source #

unfoldr :: (a -> Maybe (StringCellChar Text, a)) -> a -> Text Source #

altUnfoldr :: (a -> Maybe (StringCellAltChar Text, a)) -> a -> Text Source #

unfoldrN :: Int -> (a -> Maybe (StringCellChar Text, a)) -> a -> Text Source #

altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar Text, a)) -> a -> Text Source #

unfoldrN64 :: Int64 -> (a -> Maybe (StringCellChar Text, a)) -> a -> Text Source #

altUnfoldrN64 :: Int64 -> (a -> Maybe (StringCellAltChar Text, a)) -> a -> Text Source #

index :: Text -> Int -> StringCellChar Text Source #

index64 :: Text -> Int64 -> StringCellChar Text Source #

genericIndex :: Integral i => Text -> i -> StringCellChar Text Source #

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

take64 :: Int64 -> Text -> Text Source #

genericTake :: Integral i => i -> Text -> Text Source #

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

drop64 :: Int64 -> Text -> Text Source #

genericDrop :: Integral i => i -> Text -> Text Source #

length :: Text -> Int Source #

length64 :: Text -> Int64 Source #

genericLength :: Integral i => Text -> i Source #

safeUncons :: Text -> Maybe (StringCellChar Text, Text) Source #

safeUnsnoc :: Text -> Maybe (Text, StringCellChar Text) Source #

safeAltUncons :: Text -> Maybe (StringCellAltChar Text, Text) Source #

safeAltUnsnoc :: Text -> Maybe (Text, StringCellAltChar Text) Source #

safeHead :: Text -> Maybe (StringCellChar Text) Source #

safeTail :: Text -> Maybe Text Source #

safeLast :: Text -> Maybe (StringCellChar Text) Source #

safeInit :: Text -> Maybe Text Source #

safeAltHead :: Text -> Maybe (StringCellAltChar Text) Source #

safeAltLast :: Text -> Maybe (StringCellAltChar Text) Source #

safeIndex :: Text -> Int -> Maybe (StringCellChar Text) Source #

safeIndex64 :: Text -> Int64 -> Maybe (StringCellChar Text) Source #

safeGenericIndex :: Integral i => Text -> i -> Maybe (StringCellChar Text) Source #

safeTake :: Int -> Text -> Maybe Text Source #

safeTake64 :: Int64 -> Text -> Maybe Text Source #

safeGenericTake :: Integral i => i -> Text -> Maybe Text Source #

safeDrop :: Int -> Text -> Maybe Text Source #

safeDrop64 :: Int64 -> Text -> Maybe Text Source #

safeGenericDrop :: Integral i => i -> Text -> Maybe Text Source #

safeUncons2 :: Text -> Maybe (StringCellChar Text, StringCellChar Text, Text) Source #

safeUncons3 :: Text -> Maybe (StringCellChar Text, StringCellChar Text, StringCellChar Text, Text) Source #

safeUncons4 :: Text -> Maybe (StringCellChar Text, StringCellChar Text, StringCellChar Text, StringCellChar Text, Text) Source #

cons2 :: StringCellChar Text -> StringCellChar Text -> Text -> Text Source #

cons3 :: StringCellChar Text -> StringCellChar Text -> StringCellChar Text -> Text -> Text Source #

cons4 :: StringCellChar Text -> StringCellChar Text -> StringCellChar Text -> StringCellChar Text -> Text -> Text Source #

uncons2 :: Text -> (StringCellChar Text, StringCellChar Text, Text) Source #

uncons3 :: Text -> (StringCellChar Text, StringCellChar Text, StringCellChar Text, Text) Source #

uncons4 :: Text -> (StringCellChar Text, StringCellChar Text, StringCellChar Text, StringCellChar Text, Text) Source #

StringCells Text Source # 

Associated Types

type StringCellChar Text :: * Source #

type StringCellAltChar Text :: * Source #

Methods

toStringCells :: StringCells s2 => Text -> s2 Source #

fromStringCells :: StringCells s2 => s2 -> Text Source #

cons :: StringCellChar Text -> Text -> Text Source #

uncons :: Text -> (StringCellChar Text, Text) Source #

snoc :: Text -> StringCellChar Text -> Text Source #

unsnoc :: Text -> (Text, StringCellChar Text) Source #

altCons :: StringCellAltChar Text -> Text -> Text Source #

altUncons :: Text -> (StringCellAltChar Text, Text) Source #

altSnoc :: Text -> StringCellAltChar Text -> Text Source #

altUnsnoc :: Text -> (Text, StringCellAltChar Text) Source #

toMainChar :: StringCell c => c -> Tagged * Text (StringCellChar Text) Source #

toAltChar :: StringCell c => c -> Tagged * Text (StringCellAltChar Text) Source #

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

concat :: [Text] -> Text Source #

empty :: Text Source #

null :: Text -> Bool Source #

head :: Text -> StringCellChar Text Source #

tail :: Text -> Text Source #

last :: Text -> StringCellChar Text Source #

init :: Text -> Text Source #

altHead :: Text -> StringCellAltChar Text Source #

altLast :: Text -> StringCellAltChar Text Source #

unfoldr :: (a -> Maybe (StringCellChar Text, a)) -> a -> Text Source #

altUnfoldr :: (a -> Maybe (StringCellAltChar Text, a)) -> a -> Text Source #

unfoldrN :: Int -> (a -> Maybe (StringCellChar Text, a)) -> a -> Text Source #

altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar Text, a)) -> a -> Text Source #

unfoldrN64 :: Int64 -> (a -> Maybe (StringCellChar Text, a)) -> a -> Text Source #

altUnfoldrN64 :: Int64 -> (a -> Maybe (StringCellAltChar Text, a)) -> a -> Text Source #

index :: Text -> Int -> StringCellChar Text Source #

index64 :: Text -> Int64 -> StringCellChar Text Source #

genericIndex :: Integral i => Text -> i -> StringCellChar Text Source #

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

take64 :: Int64 -> Text -> Text Source #

genericTake :: Integral i => i -> Text -> Text Source #

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

drop64 :: Int64 -> Text -> Text Source #

genericDrop :: Integral i => i -> Text -> Text Source #

length :: Text -> Int Source #

length64 :: Text -> Int64 Source #

genericLength :: Integral i => Text -> i Source #

safeUncons :: Text -> Maybe (StringCellChar Text, Text) Source #

safeUnsnoc :: Text -> Maybe (Text, StringCellChar Text) Source #

safeAltUncons :: Text -> Maybe (StringCellAltChar Text, Text) Source #

safeAltUnsnoc :: Text -> Maybe (Text, StringCellAltChar Text) Source #

safeHead :: Text -> Maybe (StringCellChar Text) Source #

safeTail :: Text -> Maybe Text Source #

safeLast :: Text -> Maybe (StringCellChar Text) Source #

safeInit :: Text -> Maybe Text Source #

safeAltHead :: Text -> Maybe (StringCellAltChar Text) Source #

safeAltLast :: Text -> Maybe (StringCellAltChar Text) Source #

safeIndex :: Text -> Int -> Maybe (StringCellChar Text) Source #

safeIndex64 :: Text -> Int64 -> Maybe (StringCellChar Text) Source #

safeGenericIndex :: Integral i => Text -> i -> Maybe (StringCellChar Text) Source #

safeTake :: Int -> Text -> Maybe Text Source #

safeTake64 :: Int64 -> Text -> Maybe Text Source #

safeGenericTake :: Integral i => i -> Text -> Maybe Text Source #

safeDrop :: Int -> Text -> Maybe Text Source #

safeDrop64 :: Int64 -> Text -> Maybe Text Source #

safeGenericDrop :: Integral i => i -> Text -> Maybe Text Source #

safeUncons2 :: Text -> Maybe (StringCellChar Text, StringCellChar Text, Text) Source #

safeUncons3 :: Text -> Maybe (StringCellChar Text, StringCellChar Text, StringCellChar Text, Text) Source #

safeUncons4 :: Text -> Maybe (StringCellChar Text, StringCellChar Text, StringCellChar Text, StringCellChar Text, Text) Source #

cons2 :: StringCellChar Text -> StringCellChar Text -> Text -> Text Source #

cons3 :: StringCellChar Text -> StringCellChar Text -> StringCellChar Text -> Text -> Text Source #

cons4 :: StringCellChar Text -> StringCellChar Text -> StringCellChar Text -> StringCellChar Text -> Text -> Text Source #

uncons2 :: Text -> (StringCellChar Text, StringCellChar Text, Text) Source #

uncons3 :: Text -> (StringCellChar Text, StringCellChar Text, StringCellChar Text, Text) Source #

uncons4 :: Text -> (StringCellChar Text, StringCellChar Text, StringCellChar Text, StringCellChar Text, Text) Source #

StringCells GenString Source # 

Methods

toStringCells :: StringCells s2 => GenString -> s2 Source #

fromStringCells :: StringCells s2 => s2 -> GenString Source #

cons :: StringCellChar GenString -> GenString -> GenString Source #

uncons :: GenString -> (StringCellChar GenString, GenString) Source #

snoc :: GenString -> StringCellChar GenString -> GenString Source #

unsnoc :: GenString -> (GenString, StringCellChar GenString) Source #

altCons :: StringCellAltChar GenString -> GenString -> GenString Source #

altUncons :: GenString -> (StringCellAltChar GenString, GenString) Source #

altSnoc :: GenString -> StringCellAltChar GenString -> GenString Source #

altUnsnoc :: GenString -> (GenString, StringCellAltChar GenString) Source #

toMainChar :: StringCell c => c -> Tagged * GenString (StringCellChar GenString) Source #

toAltChar :: StringCell c => c -> Tagged * GenString (StringCellAltChar GenString) Source #

append :: GenString -> GenString -> GenString Source #

concat :: [GenString] -> GenString Source #

empty :: GenString Source #

null :: GenString -> Bool Source #

head :: GenString -> StringCellChar GenString Source #

tail :: GenString -> GenString Source #

last :: GenString -> StringCellChar GenString Source #

init :: GenString -> GenString Source #

altHead :: GenString -> StringCellAltChar GenString Source #

altLast :: GenString -> StringCellAltChar GenString Source #

unfoldr :: (a -> Maybe (StringCellChar GenString, a)) -> a -> GenString Source #

altUnfoldr :: (a -> Maybe (StringCellAltChar GenString, a)) -> a -> GenString Source #

unfoldrN :: Int -> (a -> Maybe (StringCellChar GenString, a)) -> a -> GenString Source #

altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar GenString, a)) -> a -> GenString Source #

unfoldrN64 :: Int64 -> (a -> Maybe (StringCellChar GenString, a)) -> a -> GenString Source #

altUnfoldrN64 :: Int64 -> (a -> Maybe (StringCellAltChar GenString, a)) -> a -> GenString Source #

index :: GenString -> Int -> StringCellChar GenString Source #

index64 :: GenString -> Int64 -> StringCellChar GenString Source #

genericIndex :: Integral i => GenString -> i -> StringCellChar GenString Source #

take :: Int -> GenString -> GenString Source #

take64 :: Int64 -> GenString -> GenString Source #

genericTake :: Integral i => i -> GenString -> GenString Source #

drop :: Int -> GenString -> GenString Source #

drop64 :: Int64 -> GenString -> GenString Source #

genericDrop :: Integral i => i -> GenString -> GenString Source #

length :: GenString -> Int Source #

length64 :: GenString -> Int64 Source #

genericLength :: Integral i => GenString -> i Source #

safeUncons :: GenString -> Maybe (StringCellChar GenString, GenString) Source #

safeUnsnoc :: GenString -> Maybe (GenString, StringCellChar GenString) Source #

safeAltUncons :: GenString -> Maybe (StringCellAltChar GenString, GenString) Source #

safeAltUnsnoc :: GenString -> Maybe (GenString, StringCellAltChar GenString) Source #

safeHead :: GenString -> Maybe (StringCellChar GenString) Source #

safeTail :: GenString -> Maybe GenString Source #

safeLast :: GenString -> Maybe (StringCellChar GenString) Source #

safeInit :: GenString -> Maybe GenString Source #

safeAltHead :: GenString -> Maybe (StringCellAltChar GenString) Source #

safeAltLast :: GenString -> Maybe (StringCellAltChar GenString) Source #

safeIndex :: GenString -> Int -> Maybe (StringCellChar GenString) Source #

safeIndex64 :: GenString -> Int64 -> Maybe (StringCellChar GenString) Source #

safeGenericIndex :: Integral i => GenString -> i -> Maybe (StringCellChar GenString) Source #

safeTake :: Int -> GenString -> Maybe GenString Source #

safeTake64 :: Int64 -> GenString -> Maybe GenString Source #

safeGenericTake :: Integral i => i -> GenString -> Maybe GenString Source #

safeDrop :: Int -> GenString -> Maybe GenString Source #

safeDrop64 :: Int64 -> GenString -> Maybe GenString Source #

safeGenericDrop :: Integral i => i -> GenString -> Maybe GenString Source #

safeUncons2 :: GenString -> Maybe (StringCellChar GenString, StringCellChar GenString, GenString) Source #

safeUncons3 :: GenString -> Maybe (StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, GenString) Source #

safeUncons4 :: GenString -> Maybe (StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, GenString) Source #

cons2 :: StringCellChar GenString -> StringCellChar GenString -> GenString -> GenString Source #

cons3 :: StringCellChar GenString -> StringCellChar GenString -> StringCellChar GenString -> GenString -> GenString Source #

cons4 :: StringCellChar GenString -> StringCellChar GenString -> StringCellChar GenString -> StringCellChar GenString -> GenString -> GenString Source #

uncons2 :: GenString -> (StringCellChar GenString, StringCellChar GenString, GenString) Source #

uncons3 :: GenString -> (StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, GenString) Source #

uncons4 :: GenString -> (StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, GenString) Source #

class StringCell c where Source #

Instances

StringCell Char Source # 
StringCell Word8 Source # 
StringCell Word16 Source # 
StringCell Word32 Source # 
StringCell Word64 Source # 

class StringRWIO s where Source #

Minimal complete definition: hGetContents, hGetLine, hPutStr, and hPutStrLn

Minimal complete definition

hGetContents, hGetLine, hPutStr, hPutStrLn

Methods

hGetContents :: Handle -> IO s Source #

Read n bytes *or* characters, depending on the implementation into a ByteString, directly from the specified Handle

Whether or not this function is lazy depends on the instance; laziness is preferred.

hGetLine :: Handle -> IO s Source #

Read a single line from a handle

hPutStr :: Handle -> s -> IO () Source #

Write a string to a handle

hPutStrLn :: Handle -> s -> IO () Source #

Write a string to a handle, followed by a newline

N.B.: implementations might not define this atomically. If the state of being atomic is necessary, one possible solution is to convert a string to an efficient type for which hPutStrLn is atomic.

interact :: (s -> s) -> IO () Source #

Take a function of type Text -> Text as its argument

The entire input from the standard input device is passed to this function as its argument, and the resulting string is output on the standard output device.

getContents :: IO s Source #

Read all user input on stdin as a single string

getLine :: IO s Source #

Read a single line of user input from stdin

putStr :: s -> IO () Source #

Write a string to stdout

putStrLn :: s -> IO () Source #

Write a string to stdout, followed by a newline

readFile :: FilePath -> IO s Source #

Read a file and returns the contents of the file as a string

Depending on the instance, this function might expect the file to be non-binary. The default definition uses openFile to open the file.

writeFile :: FilePath -> s -> IO () Source #

Write a string to a file

The file is truncated to zero length before writing begins. The default definition uses withFile to open the file.

appendFile :: FilePath -> s -> IO () Source #

Write a string to the end of a file

The default definition uses withFile to open the file.

Instances

StringRWIO String Source #

See 'System.IO for documentation of behaviour.

StringRWIO ByteString Source #

See Lazy for documentation of behaviour.

hGetLine and getLine are defined in terms of toStringCells and the equivalent methods of ByteString. hPutStrLn is defined non-atomically: it is defined as an action that puts the string and then separately puts a newline character string.

StringRWIO ByteString Source #

See ByteString for documentation of behaviour.

StringRWIO Text Source #

See IO for documentation of behaviour.

StringRWIO Text Source #

See IO for documentation of behaviour.

StringRWIO GenString Source #

This is minimally defined with GenStringDefault.

data GenString Source #

Polymorphic container of a string

When operations take place on multiple GenStrings, they are first converted to the type GenStringDefault, which are lazy bytestrings, whenever absolutely necessary (which includes testing for equality, appending strings, concatenating lists of strings, empty strings with empty, and unfolding), making them the most efficient type for this polymorphic container.

Constructors

Stringy s => GenString 

Fields

Instances

Eq GenString Source # 
IsString GenString Source # 
Semigroup GenString Source # 
Monoid GenString Source # 
StringRWIO GenString Source #

This is minimally defined with GenStringDefault.

ConvText GenString Source # 
ConvLazyByteString GenString Source # 
ConvStrictByteString GenString Source # 
ConvString GenString Source # 
ConvGenString GenString Source # 
StringCells GenString Source # 

Methods

toStringCells :: StringCells s2 => GenString -> s2 Source #

fromStringCells :: StringCells s2 => s2 -> GenString Source #

cons :: StringCellChar GenString -> GenString -> GenString Source #

uncons :: GenString -> (StringCellChar GenString, GenString) Source #

snoc :: GenString -> StringCellChar GenString -> GenString Source #

unsnoc :: GenString -> (GenString, StringCellChar GenString) Source #

altCons :: StringCellAltChar GenString -> GenString -> GenString Source #

altUncons :: GenString -> (StringCellAltChar GenString, GenString) Source #

altSnoc :: GenString -> StringCellAltChar GenString -> GenString Source #

altUnsnoc :: GenString -> (GenString, StringCellAltChar GenString) Source #

toMainChar :: StringCell c => c -> Tagged * GenString (StringCellChar GenString) Source #

toAltChar :: StringCell c => c -> Tagged * GenString (StringCellAltChar GenString) Source #

append :: GenString -> GenString -> GenString Source #

concat :: [GenString] -> GenString Source #

empty :: GenString Source #

null :: GenString -> Bool Source #

head :: GenString -> StringCellChar GenString Source #

tail :: GenString -> GenString Source #

last :: GenString -> StringCellChar GenString Source #

init :: GenString -> GenString Source #

altHead :: GenString -> StringCellAltChar GenString Source #

altLast :: GenString -> StringCellAltChar GenString Source #

unfoldr :: (a -> Maybe (StringCellChar GenString, a)) -> a -> GenString Source #

altUnfoldr :: (a -> Maybe (StringCellAltChar GenString, a)) -> a -> GenString Source #

unfoldrN :: Int -> (a -> Maybe (StringCellChar GenString, a)) -> a -> GenString Source #

altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar GenString, a)) -> a -> GenString Source #

unfoldrN64 :: Int64 -> (a -> Maybe (StringCellChar GenString, a)) -> a -> GenString Source #

altUnfoldrN64 :: Int64 -> (a -> Maybe (StringCellAltChar GenString, a)) -> a -> GenString Source #

index :: GenString -> Int -> StringCellChar GenString Source #

index64 :: GenString -> Int64 -> StringCellChar GenString Source #

genericIndex :: Integral i => GenString -> i -> StringCellChar GenString Source #

take :: Int -> GenString -> GenString Source #

take64 :: Int64 -> GenString -> GenString Source #

genericTake :: Integral i => i -> GenString -> GenString Source #

drop :: Int -> GenString -> GenString Source #

drop64 :: Int64 -> GenString -> GenString Source #

genericDrop :: Integral i => i -> GenString -> GenString Source #

length :: GenString -> Int Source #

length64 :: GenString -> Int64 Source #

genericLength :: Integral i => GenString -> i Source #

safeUncons :: GenString -> Maybe (StringCellChar GenString, GenString) Source #

safeUnsnoc :: GenString -> Maybe (GenString, StringCellChar GenString) Source #

safeAltUncons :: GenString -> Maybe (StringCellAltChar GenString, GenString) Source #

safeAltUnsnoc :: GenString -> Maybe (GenString, StringCellAltChar GenString) Source #

safeHead :: GenString -> Maybe (StringCellChar GenString) Source #

safeTail :: GenString -> Maybe GenString Source #

safeLast :: GenString -> Maybe (StringCellChar GenString) Source #

safeInit :: GenString -> Maybe GenString Source #

safeAltHead :: GenString -> Maybe (StringCellAltChar GenString) Source #

safeAltLast :: GenString -> Maybe (StringCellAltChar GenString) Source #

safeIndex :: GenString -> Int -> Maybe (StringCellChar GenString) Source #

safeIndex64 :: GenString -> Int64 -> Maybe (StringCellChar GenString) Source #

safeGenericIndex :: Integral i => GenString -> i -> Maybe (StringCellChar GenString) Source #

safeTake :: Int -> GenString -> Maybe GenString Source #

safeTake64 :: Int64 -> GenString -> Maybe GenString Source #

safeGenericTake :: Integral i => i -> GenString -> Maybe GenString Source #

safeDrop :: Int -> GenString -> Maybe GenString Source #

safeDrop64 :: Int64 -> GenString -> Maybe GenString Source #

safeGenericDrop :: Integral i => i -> GenString -> Maybe GenString Source #

safeUncons2 :: GenString -> Maybe (StringCellChar GenString, StringCellChar GenString, GenString) Source #

safeUncons3 :: GenString -> Maybe (StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, GenString) Source #

safeUncons4 :: GenString -> Maybe (StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, GenString) Source #

cons2 :: StringCellChar GenString -> StringCellChar GenString -> GenString -> GenString Source #

cons3 :: StringCellChar GenString -> StringCellChar GenString -> StringCellChar GenString -> GenString -> GenString Source #

cons4 :: StringCellChar GenString -> StringCellChar GenString -> StringCellChar GenString -> StringCellChar GenString -> GenString -> GenString Source #

uncons2 :: GenString -> (StringCellChar GenString, StringCellChar GenString, GenString) Source #

uncons3 :: GenString -> (StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, GenString) Source #

uncons4 :: GenString -> (StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, StringCellChar GenString, GenString) Source #

type StringCellChar GenString Source # 
type StringCellAltChar GenString Source # 

type GenStringDefault = ByteString Source #

This type is used by GenString when a concrete string type is needed