os-string-compat-1.0.0: Compatibility layer for os-string
Safe HaskellNone
LanguageHaskell2010

System.OsString.Posix.Compat

Synopsis

Types

data PosixString #

Instances

Instances details
Monoid PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Semigroup PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

(<>) :: PosixString -> PosixString -> PosixString

sconcat :: NonEmpty PosixString -> PosixString

stimes :: Integral b => b -> PosixString -> PosixString

Generic PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixString = D1 ('MetaData "PosixString" "System.OsString.Internal.Types.Hidden" "filepath-1.4.301.0-c27c" 'True) (C1 ('MetaCons "PosixString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))

Methods

from :: PosixString -> Rep PosixString x

to :: Rep PosixString x -> PosixString

Show PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

showsPrec :: Int -> PosixString -> ShowS

show :: PosixString -> String

showList :: [PosixString] -> ShowS

NFData PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnf :: PosixString -> ()

Eq PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

(==) :: PosixString -> PosixString -> Bool

(/=) :: PosixString -> PosixString -> Bool

Ord PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Lift PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

lift :: Quote m => PosixString -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => PosixString -> Code m PosixString

type Rep PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixString = D1 ('MetaData "PosixString" "System.OsString.Internal.Types.Hidden" "filepath-1.4.301.0-c27c" 'True) (C1 ('MetaCons "PosixString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))

data PosixChar #

Instances

Instances details
Generic PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixChar = D1 ('MetaData "PosixChar" "System.OsString.Internal.Types.Hidden" "filepath-1.4.301.0-c27c" 'True) (C1 ('MetaCons "PosixChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))

Methods

from :: PosixChar -> Rep PosixChar x

to :: Rep PosixChar x -> PosixChar

Show PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

showsPrec :: Int -> PosixChar -> ShowS

show :: PosixChar -> String

showList :: [PosixChar] -> ShowS

NFData PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnf :: PosixChar -> ()

Eq PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

(==) :: PosixChar -> PosixChar -> Bool

(/=) :: PosixChar -> PosixChar -> Bool

Ord PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

compare :: PosixChar -> PosixChar -> Ordering

(<) :: PosixChar -> PosixChar -> Bool

(<=) :: PosixChar -> PosixChar -> Bool

(>) :: PosixChar -> PosixChar -> Bool

(>=) :: PosixChar -> PosixChar -> Bool

max :: PosixChar -> PosixChar -> PosixChar

min :: PosixChar -> PosixChar -> PosixChar

type Rep PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixChar = D1 ('MetaData "PosixChar" "System.OsString.Internal.Types.Hidden" "filepath-1.4.301.0-c27c" 'True) (C1 ('MetaCons "PosixChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))

String construction

encodeUtf :: MonadThrow m => String -> m PosixString Source #

Partial unicode friendly encoding.

This encodes as UTF8 (strictly), which is a good guess.

Throws an EncodingException if encoding fails. If the input does not contain surrogate chars, you can use unsafeEncodeUtf.

unsafeEncodeUtf :: HasCallStack => String -> PosixString Source #

Unsafe unicode friendly encoding.

Like encodeUtf, except it crashes when the input contains surrogate chars. For sanitized input, this can be useful.

encodeWith :: TextEncoding -> String -> Either EncodingException PosixString #

encodeFS :: String -> IO PosixString Source #

Deprecated: Use System.OsPath.Posix.encodeFS from filepath

This mimics the behavior of the base library when doing filesystem operations (usually filepaths), which uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck).

Looking up the locale requires IO. If you're not worried about calls to setFileSystemEncoding, then unsafePerformIO may be feasible (make sure to deeply evaluate the result to catch exceptions).

encodeLE :: String -> IO PosixString Source #

This mimics the behavior of the base library when doing string operations, which uses getLocaleEncoding.

Looking up the locale requires IO. If you're not worried about calls to setFileSystemEncoding, then unsafePerformIO may be feasible (make sure to deeply evaluate the result to catch exceptions).

fromBytes :: MonadThrow m => ByteString -> m PosixString Source #

Constructs a platform string from a ByteString.

This is a no-op.

fromShortBytes :: MonadThrow m => ShortByteString -> m PosixString Source #

Constructs a platform string from a ShortByteString.

This is a no-op.

Since: 2.0.8

fromBytestring :: ByteString -> PosixString Source #

Like fromBytes, but not in IO.

fromBytes was designed to have a symmetric type signature on unix and windows, but morally the function has no IO effects on unix, so we provide this variant without breaking existing API.

This function does not exist on windows.

Since: 2.0.6

fromShortBytestring :: ShortByteString -> PosixString Source #

Like fromShortBytes, but not in IO, similarly to fromBytestring

Since: 2.0.8

pstr :: QuasiQuoter #

pack :: [PosixChar] -> PosixString Source #

Pack a list of platform words to a platform string.

Note that using this in conjunction with unsafeFromChar to convert from [Char] to platform string is probably not what you want, because it will truncate unicode code points.

String deconstruction

decodeUtf :: MonadThrow m => PosixString -> m String Source #

Partial unicode friendly decoding.

This decodes as UTF8 (strictly), which is a good guess. Note that filenames on unix are encoding agnostic char arrays.

Throws a EncodingException if decoding fails.

decodeWith :: TextEncoding -> PosixString -> Either EncodingException String #

decodeFS :: PosixString -> IO String Source #

Deprecated: Use System.OsPath.Posix.decodeFS from filepath

This mimics the behavior of the base library when doing filesystem operations (usually filepaths), which uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck).

Looking up the locale requires IO. If you're not worried about calls to setFileSystemEncoding, then unsafePerformIO may be feasible (make sure to deeply evaluate the result to catch exceptions).

decodeLE :: PosixString -> IO String Source #

This mimics the behavior of the base library when doing filesystem operations, which uses getLocaleEncoding.

Looking up the locale requires IO. If you're not worried about calls to setFileSystemEncoding, then unsafePerformIO may be feasible (make sure to deeply evaluate the result to catch exceptions).

unpack :: PosixString -> [PosixChar] Source #

Unpack a platform string to a list of platform words.

Word construction

unsafeFromChar :: Char -> PosixChar Source #

Truncates to 1 octet.

Word deconstruction

toChar :: PosixChar -> Char Source #

Converts back to a unicode codepoint (total).

Basic interface

snoc :: PosixString -> PosixChar -> PosixString Source #

O(n) Append a byte to the end of a PosixString

cons :: PosixChar -> PosixString -> PosixString Source #

O(n) cons is analogous to (:) for lists.

last :: HasCallStack => PosixString -> PosixChar Source #

O(1) Extract the last element of a PosixString, which must be finite and non-empty. An exception will be thrown in the case of an empty PosixString.

This is a partial function, consider using unsnoc instead.

tail :: HasCallStack => PosixString -> PosixString Source #

O(n) Extract the elements after the head of a PosixString, which must be non-empty. An exception will be thrown in the case of an empty PosixString.

This is a partial function, consider using uncons instead.

uncons :: PosixString -> Maybe (PosixChar, PosixString) Source #

O(n) Extract the head and tail of a PosixString, returning Nothing if it is empty.

head :: HasCallStack => PosixString -> PosixChar Source #

O(1) Extract the first element of a PosixString, which must be non-empty. An exception will be thrown in the case of an empty PosixString.

This is a partial function, consider using uncons instead.

init :: HasCallStack => PosixString -> PosixString Source #

O(n) Return all the elements of a PosixString except the last one. An exception will be thrown in the case of an empty PosixString.

This is a partial function, consider using unsnoc instead.

unsnoc :: PosixString -> Maybe (PosixString, PosixChar) Source #

O(n) Extract the init and last of a PosixString, returning Nothing if it is empty.

null :: PosixString -> Bool Source #

O(1). The empty PosixString.

length :: PosixString -> Int Source #

O(1) The length of a PosixString.

This returns the number of code units (Word8 on unix and Word16 on windows), not bytes.

>>> length "abc"
3

Note: older versions of os-string return the length in bytes, rather than the length in code units. This will return the length in code units, regardless of the version of os-string. For checking the length in Bytes, use lengthBytes.

lengthBytes :: PosixString -> Int Source #

O(1) The length in bytes of a PosixString.

If you want the number of code units, just use length instead.

Transforming PosixStrings

map :: (PosixChar -> PosixChar) -> PosixString -> PosixString Source #

O(n) map f xs is the PosixString obtained by applying f to each element of xs.

reverse :: PosixString -> PosixString Source #

O(n) reverse xs efficiently returns the elements of xs in reverse order.

intercalate :: PosixString -> [PosixString] -> PosixString Source #

O(n) The intercalate function takes a PosixString and a list of PosixStrings and concatenates the list after interspersing the first argument between each element of the list.

Reducing PosixStrings (folds)

foldl :: (a -> PosixChar -> a) -> a -> PosixString -> a Source #

foldl, applied to a binary operator, a starting value (typically the left-identity of the operator), and a PosixString, reduces the PosixString using the binary operator, from left to right.

foldl' :: (a -> PosixChar -> a) -> a -> PosixString -> a Source #

foldl' is like foldl, but strict in the accumulator.

foldl1 :: (PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar Source #

foldl1 is a variant of foldl that has no starting value argument, and thus must be applied to non-empty PosixStrings. An exception will be thrown in the case of an empty PosixString.

foldl1' :: (PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar Source #

foldl1' is like foldl1, but strict in the accumulator. An exception will be thrown in the case of an empty PosixString.

foldr :: (PosixChar -> a -> a) -> a -> PosixString -> a Source #

foldr, applied to a binary operator, a starting value (typically the right-identity of the operator), and a PosixString, reduces the PosixString using the binary operator, from right to left.

foldr' :: (PosixChar -> a -> a) -> a -> PosixString -> a Source #

foldr' is like foldr, but strict in the accumulator.

foldr1 :: (PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar Source #

foldr1 is a variant of foldr that has no starting value argument, and thus must be applied to non-empty PosixStrings An exception will be thrown in the case of an empty PosixString.

foldr1' :: (PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar Source #

foldr1' is a variant of foldr1, but is strict in the accumulator.

Special folds

all :: (PosixChar -> Bool) -> PosixString -> Bool Source #

O(n) Applied to a predicate and a PLATFString, all determines if all elements of the PosixString satisfy the predicate.

any :: (PosixChar -> Bool) -> PosixString -> Bool Source #

O(n) Applied to a predicate and a PosixString, any determines if any element of the PosixString satisfies the predicate.

Generating and unfolding PosixStrings

replicate :: Int -> PosixChar -> PosixString Source #

O(n) replicate n x is a PosixString of length n with x the value of every element. The following holds:

replicate w c = unfoldr w (\u -> Just (u,u)) c

unfoldr :: (a -> Maybe (PosixChar, a)) -> a -> PosixString Source #

O(n), where n is the length of the result. The unfoldr function is analogous to the List 'unfoldr'. unfoldr builds a PosixString from a seed value. The function takes the element and returns Nothing if it is done producing the PosixString or returns Just (a,b), in which case, a is the next byte in the string, and b is the seed value for further production.

This function is not efficient/safe. It will build a list of [Word8] and run the generator until it returns Nothing, otherwise recurse infinitely, then finally create a PosixString.

If you know the maximum length, consider using unfoldrN.

Examples:

   unfoldr (\x -> if x <= 5 then Just (x, x + 1) else Nothing) 0
== pack [0, 1, 2, 3, 4, 5]

unfoldrN :: Int -> (a -> Maybe (PosixChar, a)) -> a -> (PosixString, Maybe a) Source #

O(n) Like unfoldr, unfoldrN builds a PosixString from a seed value. However, the length of the result is limited by the first argument to unfoldrN. This function is more efficient than unfoldr when the maximum length of the result is known.

The following equation relates unfoldrN and unfoldr:

fst (unfoldrN n f s) == take n (unfoldr f s)

Substrings

Breaking strings

take :: Int -> PosixString -> PosixString Source #

O(n) take n, applied to a PosixString xs, returns the prefix of xs of length n, or xs itself if n > length xs.

takeEnd :: Int -> PosixString -> PosixString Source #

O(n) takeEnd n xs is equivalent to drop (length xs - n) xs. Takes n elements from end of bytestring.

>>> takeEnd 3 "abcdefg"
"efg"
>>> takeEnd 0 "abcdefg"
""
>>> takeEnd 4 "abc"
"abc"

takeWhileEnd :: (PosixChar -> Bool) -> PosixString -> PosixString Source #

Returns the longest (possibly empty) suffix of elements satisfying the predicate.

takeWhileEnd p is equivalent to reverse . takeWhile p . reverse.

takeWhile :: (PosixChar -> Bool) -> PosixString -> PosixString Source #

Similar to takeWhile, returns the longest (possibly empty) prefix of elements satisfying the predicate.

drop :: Int -> PosixString -> PosixString Source #

O(n) drop n xs returns the suffix of xs after the first n elements, or empty if n > length xs.

dropEnd :: Int -> PosixString -> PosixString Source #

O(n) dropEnd n xs is equivalent to take (length xs - n) xs. Drops n elements from end of bytestring.

>>> dropEnd 3 "abcdefg"
"abcd"
>>> dropEnd 0 "abcdefg"
"abcdefg"
>>> dropEnd 4 "abc"
""

dropWhileEnd :: (PosixChar -> Bool) -> PosixString -> PosixString Source #

Similar to dropWhileEnd, drops the longest (possibly empty) suffix of elements satisfying the predicate and returns the remainder.

dropWhileEnd p is equivalent to reverse . dropWhile p . reverse.

dropWhile :: (PosixChar -> Bool) -> PosixString -> PosixString Source #

Similar to dropWhile, drops the longest (possibly empty) prefix of elements satisfying the predicate and returns the remainder.

break :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString) Source #

Similar to break, returns the longest (possibly empty) prefix of elements which do not satisfy the predicate and the remainder of the string.

break p is equivalent to span (not . p) and to (takeWhile (not . p) &&& dropWhile (not . p)).

breakEnd :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString) Source #

Returns the longest (possibly empty) suffix of elements which do not satisfy the predicate and the remainder of the string.

breakEnd p is equivalent to spanEnd (not . p) and to (takeWhileEnd (not . p) &&& dropWhileEnd (not . p)).

span :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString) Source #

Similar to span, returns the longest (possibly empty) prefix of elements satisfying the predicate and the remainder of the string.

span p is equivalent to break (not . p) and to (takeWhile p &&& dropWhile p).

spanEnd :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString) Source #

Returns the longest (possibly empty) suffix of elements satisfying the predicate and the remainder of the string.

spanEnd p is equivalent to breakEnd (not . p) and to (takeWhileEnd p &&& dropWhileEnd p).

We have

spanEnd (not . isSpace) "x y z" == ("x y ", "z")

and

spanEnd (not . isSpace) sbs
   ==
let (x, y) = span (not . isSpace) (reverse sbs) in (reverse y, reverse x)

splitAt :: Int -> PosixString -> (PosixString, PosixString) Source #

O(n) splitAt n sbs is equivalent to (take n sbs, drop n sbs).

split :: PosixChar -> PosixString -> [PosixString] Source #

O(n) Break a PosixString into pieces separated by the byte argument, consuming the delimiter. I.e.

split 10  "a\nb\nd\ne" == ["a","b","d","e"]   -- fromEnum '\n' == 10
split 97  "aXaXaXa"    == ["","X","X","X",""] -- fromEnum 'a' == 97
split 120 "x"          == ["",""]             -- fromEnum 'x' == 120
split undefined ""     == []                  -- and not [""]

and

intercalate [c] . split c == id
split == splitWith . (==)

splitWith :: (PosixChar -> Bool) -> PosixString -> [PosixString] Source #

O(n) Splits a PosixString into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output. eg.

splitWith (==97) "aabbaca" == ["","","bb","c",""] -- fromEnum 'a' == 97
splitWith undefined ""     == []                  -- and not [""]

stripSuffix :: PosixString -> PosixString -> Maybe PosixString Source #

O(n) The stripSuffix function takes two OsStrings and returns Just the remainder of the second iff the first is its suffix, and otherwise Nothing.

stripPrefix :: PosixString -> PosixString -> Maybe PosixString Source #

O(n) The stripPrefix function takes two OsStrings and returns Just the remainder of the second iff the first is its prefix, and otherwise Nothing.

Predicates

isInfixOf :: PosixString -> PosixString -> Bool Source #

Check whether one string is a substring of another.

isPrefixOf :: PosixString -> PosixString -> Bool Source #

O(n) The isPrefixOf function takes two OsStrings and returns True

isSuffixOf :: PosixString -> PosixString -> Bool Source #

O(n) The isSuffixOf function takes two OsStrings and returns True iff the first is a suffix of the second.

The following holds:

isSuffixOf x y == reverse x `isPrefixOf` reverse y

Search for arbitrary susbstrings

breakSubstring :: PosixString -> PosixString -> (PosixString, PosixString) Source #

Break a string on a substring, returning a pair of the part of the string prior to the match, and the rest of the string.

The following relationships hold:

break (== c) l == breakSubstring (singleton c) l

For example, to tokenise a string, dropping delimiters:

tokenise x y = h : if null t then [] else tokenise x (drop (length x) t)
    where (h,t) = breakSubstring x y

To skip to the first occurrence of a string:

snd (breakSubstring x y)

To take the parts of a string before a delimiter:

fst (breakSubstring x y)

Note that calling `breakSubstring x` does some preprocessing work, so you should avoid unnecessarily duplicating breakSubstring calls with the same pattern.

Searching PosixStrings

Searching by equality

elem :: PosixChar -> PosixString -> Bool Source #

O(n) elem is the PosixString membership predicate.

find :: (PosixChar -> Bool) -> PosixString -> Maybe PosixChar Source #

O(n) The find function takes a predicate and a PosixString, and returns the first element in matching the predicate, or Nothing if there is no such element.

find f p = case findIndex f p of Just n -> Just (p ! n) ; _ -> Nothing

filter :: (PosixChar -> Bool) -> PosixString -> PosixString Source #

O(n) filter, applied to a predicate and a PosixString, returns a PosixString containing those characters that satisfy the predicate.

partition :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString) Source #

O(n) The partition function takes a predicate a PosixString and returns the pair of OsStrings with elements which do and do not satisfy the predicate, respectively; i.e.,

partition p bs == (filter p sbs, filter (not . p) sbs)

Indexing PosixStrings

index :: HasCallStack => PosixString -> Int -> PosixChar Source #

O(1) PosixString index (subscript) operator, starting from 0.

indexMaybe :: PosixString -> Int -> Maybe PosixChar Source #

O(1) PosixString index, starting from 0, that returns Just if:

0 <= n < length bs

(!?) :: PosixString -> Int -> Maybe PosixChar Source #

O(1) PosixString index, starting from 0, that returns Just if:

0 <= n < length bs

elemIndex :: PosixChar -> PosixString -> Maybe Int Source #

O(n) The elemIndex function returns the index of the first element in the given PosixString which is equal to the query element, or Nothing if there is no such element.

elemIndices :: PosixChar -> PosixString -> [Int] Source #

O(n) The elemIndices function extends elemIndex, by returning the indices of all elements equal to the query element, in ascending order.

count :: PosixChar -> PosixString -> Int Source #

count returns the number of times its argument appears in the PosixString

findIndex :: (PosixChar -> Bool) -> PosixString -> Maybe Int Source #

O(n) The findIndex function takes a predicate and a PosixString and returns the index of the first element in the PosixString satisfying the predicate.

findIndices :: (PosixChar -> Bool) -> PosixString -> [Int] Source #

O(n) The findIndices function extends findIndex, by returning the indices of all elements satisfying the predicate, in ascending order.