os-string-compat-1.0.0: Compatibility layer for os-string
Copyright(c) 2021 Julian Ospald 2025 David Wilson
LicenseBSD-3-Clause (see the LICENSE file)
Safe HaskellNone
LanguageHaskell2010

System.OsString.Compat

Description

Compatibility layer for versions of filepath that don't import os-string. For versions that do, it just re-exports the corresponding functions from System.OsString.

Note: All documentation is taken from the os-string documentation, except for a few functions/types that are found in the older versions of "filepath".

For more information on OsStrings in general, look at the package os-string.

Synopsis

String types

data OsString #

Instances

Instances details
Monoid OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Semigroup OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

(<>) :: OsString -> OsString -> OsString

sconcat :: NonEmpty OsString -> OsString

stimes :: Integral b => b -> OsString -> OsString

Generic OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

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

Methods

from :: OsString -> Rep OsString x

to :: Rep OsString x -> OsString

Show OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

showsPrec :: Int -> OsString -> ShowS

show :: OsString -> String

showList :: [OsString] -> ShowS

NFData OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnf :: OsString -> ()

Eq OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

(==) :: OsString -> OsString -> Bool

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

Ord OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

compare :: OsString -> OsString -> Ordering

(<) :: OsString -> OsString -> Bool

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

(>) :: OsString -> OsString -> Bool

(>=) :: OsString -> OsString -> Bool

max :: OsString -> OsString -> OsString

min :: OsString -> OsString -> OsString

Lift OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

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

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

type Rep OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

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

OsString construction

encodeUtf :: MonadThrow m => String -> m OsString #

unsafeEncodeUtf :: HasCallStack => String -> OsString 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 -> TextEncoding -> String -> Either EncodingException OsString #

encodeFS :: String -> IO OsString Source #

Like encodeUtf, except this mimics the behavior of the base library when doing filesystem operations (usually filepaths), which is:

  1. on unix, uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck)
  2. on windows does permissive UTF-16 encoding, where coding errors generate Chars in the surrogate range

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

osstr :: QuasiQuoter #

OsString deconstruction

decodeUtf :: MonadThrow m => OsString -> m String #

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

decodeFS :: OsString -> IO String #

Word types

data OsChar #

Instances

Instances details
Generic OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

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

Methods

from :: OsChar -> Rep OsChar x

to :: Rep OsChar x -> OsChar

Show OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

showsPrec :: Int -> OsChar -> ShowS

show :: OsChar -> String

showList :: [OsChar] -> ShowS

NFData OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnf :: OsChar -> ()

Eq OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

(==) :: OsChar -> OsChar -> Bool

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

Ord OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

compare :: OsChar -> OsChar -> Ordering

(<) :: OsChar -> OsChar -> Bool

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

(>) :: OsChar -> OsChar -> Bool

(>=) :: OsChar -> OsChar -> Bool

max :: OsChar -> OsChar -> OsChar

min :: OsChar -> OsChar -> OsChar

type Rep OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

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

Word construction

Word deconstruction

toChar :: OsChar -> Char Source #

Converts back to a unicode codepoint (total).

Note that this uses the version from os-string, not filepath

Basic interface

snoc :: OsString -> OsChar -> OsString Source #

O(n) Append a byte/word to the end of an OsString

cons :: OsChar -> OsString -> OsString Source #

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

last :: HasCallStack => OsString -> OsChar Source #

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

This is a partial function, consider using unsnoc instead.

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

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

This is a partial function, consider using uncons instead.

uncons :: OsString -> Maybe (OsChar, OsString) Source #

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

head :: HasCallStack => OsString -> OsChar Source #

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

This is a partial function, consider using uncons instead.

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

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

This is a partial function, consider using unsnoc instead.

unsnoc :: OsString -> Maybe (OsString, OsChar) Source #

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

null :: OsString -> Bool Source #

O(1) Test whether an OsString is empty.

length :: OsString -> Int Source #

O(1) The length of an OsString.

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

lengthBytes :: OsString -> Int Source #

O(1) The length in bytes of an OsString.

This always returns the number of bytes, regardless of which platform you're on.

Transforming OsString

map :: (OsChar -> OsChar) -> OsString -> OsString Source #

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

reverse :: OsString -> OsString Source #

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

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

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

Reducing OsStrings (folds)

foldl :: (a -> OsChar -> a) -> a -> OsString -> a Source #

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

foldl' :: (a -> OsChar -> a) -> a -> OsString -> a Source #

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

foldl1 :: (OsChar -> OsChar -> OsChar) -> OsString -> OsChar Source #

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

foldl1' :: (OsChar -> OsChar -> OsChar) -> OsString -> OsChar Source #

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

foldr :: (OsChar -> a -> a) -> a -> OsString -> a Source #

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

foldr' :: (OsChar -> a -> a) -> a -> OsString -> a Source #

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

foldr1 :: (OsChar -> OsChar -> OsChar) -> OsString -> OsChar Source #

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

foldr1' :: (OsChar -> OsChar -> OsChar) -> OsString -> OsChar Source #

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

Special folds

all :: (OsChar -> Bool) -> OsString -> Bool Source #

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

any :: (OsChar -> Bool) -> OsString -> Bool Source #

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

Generating and unfolding OsStrings

replicate :: Int -> OsChar -> OsString Source #

O(n) replicate n x is an OsString 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 (OsChar, a)) -> a -> OsString Source #

O(n), where n is the length of the result. The unfoldr function is analogous to the List 'unfoldr'. unfoldr builds a OsString from a seed value. The function takes the element and returns Nothing if it is done producing the OsString 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 an OsString.

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 (OsChar, a)) -> a -> (OsString, Maybe a) Source #

O(n) Like unfoldr, unfoldrN builds an OsString 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 -> OsString -> OsString Source #

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

takeEnd :: Int -> OsString -> OsString 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 :: (OsChar -> Bool) -> OsString -> OsString Source #

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

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

takeWhile :: (OsChar -> Bool) -> OsString -> OsString Source #

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

drop :: Int -> OsString -> OsString Source #

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

dropEnd :: Int -> OsString -> OsString 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 :: (OsChar -> Bool) -> OsString -> OsString 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 :: (OsChar -> Bool) -> OsString -> OsString Source #

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

break :: (OsChar -> Bool) -> OsString -> (OsString, OsString) 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 :: (OsChar -> Bool) -> OsString -> (OsString, OsString) 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 :: (OsChar -> Bool) -> OsString -> (OsString, OsString) 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 :: (OsChar -> Bool) -> OsString -> (OsString, OsString) 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 -> OsString -> (OsString, OsString) Source #

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

split :: OsChar -> OsString -> [OsString] Source #

O(n) Break an OsString 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 :: (OsChar -> Bool) -> OsString -> [OsString] Source #

O(n) Splits an OsString 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 :: OsString -> OsString -> Maybe OsString 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 :: OsString -> OsString -> Maybe OsString 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 :: OsString -> OsString -> Bool Source #

Check whether one string is a substring of another.

isPrefixOf :: OsString -> OsString -> Bool Source #

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

isSuffixOf :: OsString -> OsString -> 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 :: OsString -> OsString -> (OsString, OsString) 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 OsStrings

Searching by equality

elem :: OsChar -> OsString -> Bool Source #

O(n) elem is the OsString membership predicate.

find :: (OsChar -> Bool) -> OsString -> Maybe OsChar Source #

O(n) The find function takes a predicate and an OsString, 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 :: (OsChar -> Bool) -> OsString -> OsString Source #

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

partition :: (OsChar -> Bool) -> OsString -> (OsString, OsString) Source #

O(n) The partition function takes a predicate an OsString 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 OsStrings

index :: HasCallStack => OsString -> Int -> OsChar Source #

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

indexMaybe :: OsString -> Int -> Maybe OsChar Source #

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

0 <= n < length bs

(!?) :: OsString -> Int -> Maybe OsChar Source #

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

0 <= n < length bs

elemIndex :: OsChar -> OsString -> Maybe Int Source #

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

elemIndices :: OsChar -> OsString -> [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 :: OsChar -> OsString -> Int Source #

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

findIndex :: (OsChar -> Bool) -> OsString -> Maybe Int Source #

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

findIndices :: (OsChar -> Bool) -> OsString -> [Int] Source #

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

Coercions

coercionToPlatformTypes :: Either (Coercion OsChar WindowsChar, Coercion OsString WindowsString) (Coercion OsChar PosixChar, Coercion OsString PosixString) Source #

This is a type-level evidence that OsChar is a newtype wrapper over WindowsChar or PosixChar and OsString is a newtype wrapper over WindowsString or PosixString. If you pattern match on coercionToPlatformTypes, GHC will know that relevant types are coercible to each other. This helps to avoid CPP in certain scenarios.

Note: normally, this requires os-string >= 2.0.2, but since it's required in the test suite, I've defined it here for os-string-2.0.1 and for older versions of filepath.