{-# LANGUAGE CPP #-}{-# LANGUAGE RankNTypes #-}{-# LANGUAGE UnliftedFFITypes #-}{-# LANGUAGE ScopedTypeVariables #-}{-# LANGUAGE TypeApplications #-}{-# LANGUAGE TemplateHaskellQuotes #-}{-# LANGUAGE ViewPatterns #-}-- needed to quote a view patternmoduleSystem.OsString.InternalwhereimportSystem.OsString.Internal.Types importControl.Monad.Catch(MonadThrow)importData.ByteString(ByteString)importData.CharimportLanguage.Haskell.TH.Quote(QuasiQuoter(..))importLanguage.Haskell.TH.Syntax(Lift(..),lift)importSystem.IO(TextEncoding)importSystem.OsString.Encoding (EncodingException (..))importGHC.IO.Encoding.Failure(CodingFailureMode(..))
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
importGHC.IO.Encoding.UTF16(mkUTF16le)importSystem.OsString.Encoding(encodeWithBaseWindows,decodeWithBaseWindows)importqualifiedSystem.OsString.WindowsasPF
#else
importGHC.IO.Encoding.UTF8(mkUTF8)importSystem.OsString.Encoding (encodeWithBasePosix ,decodeWithBasePosix )importqualifiedSystem.OsString.Posix asPF
#endif
importGHC.Stack(HasCallStack)importData.Coerce(coerce)importData.Type.Coercion(coerceWith)-- | Partial unicode friendly encoding.---- On windows this encodes as UTF16-LE (strictly), which is a pretty good guess.-- On unix 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'.encodeUtf ::MonadThrowm =>String->m OsString encodeUtf :: forall (m :: * -> *). MonadThrow m => String -> m OsString
encodeUtf =(PosixString -> OsString) -> m PosixString -> m OsString
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmapPosixString -> OsString
OsString (m PosixString -> m OsString)
-> (String -> m PosixString) -> String -> m OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.String -> m PosixString
forall (m :: * -> *). MonadThrow m => String -> m PosixString
PF.encodeUtf -- | Unsafe unicode friendly encoding.---- Like 'encodeUtf', except it crashes when the input contains-- surrogate chars. For sanitized input, this can be useful.unsafeEncodeUtf ::HasCallStack=>String->OsString unsafeEncodeUtf :: HasCallStack => String -> OsString
unsafeEncodeUtf =PosixString -> OsString
OsString (PosixString -> OsString)
-> (String -> PosixString) -> String -> OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.HasCallStack => String -> PosixString
String -> PosixString
PF.unsafeEncodeUtf -- | Encode a 'FilePath' with the specified encoding.---- Note: on windows, we expect a "wide char" encoding (e.g. UCS-2 or UTF-16). Anything-- that works with @Word16@ boundaries. Picking an incompatible encoding may crash-- filepath operations.encodeWith ::TextEncoding-- ^ unix text encoding->TextEncoding-- ^ windows text encoding (wide char)->String->EitherEncodingException OsString 
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
encodeWith_winEncstr=OsString<$>PF.encodeWithwinEncstr
#else
encodeWith :: TextEncoding
-> TextEncoding -> String -> Either EncodingException OsString
encodeWith TextEncoding
unixEnc TextEncoding
_String
str =PosixString -> OsString
OsString (PosixString -> OsString)
-> Either EncodingException PosixString
-> Either EncodingException OsString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>TextEncoding -> String -> Either EncodingException PosixString
PF.encodeWith TextEncoding
unixEnc String
str 
#endif
-- | 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).encodeFS ::String->IOOsString 
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
encodeFS=fmap(OsString.WindowsString).encodeWithBaseWindows
#else
encodeFS :: String -> IO OsString
encodeFS =(ShortByteString -> OsString) -> IO ShortByteString -> IO OsString
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap(PosixString -> OsString
OsString (PosixString -> OsString)
-> (ShortByteString -> PosixString) -> ShortByteString -> OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ShortByteString -> PosixString
PosixString )(IO ShortByteString -> IO OsString)
-> (String -> IO ShortByteString) -> String -> IO OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.String -> IO ShortByteString
encodeWithBasePosix 
#endif
-- | Like 'encodeUtf', except this mimics the behavior of the base library when doing string-- operations, which is:---- 1. on unix this uses 'getLocaleEncoding'-- 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).encodeLE ::String->IOOsString encodeLE :: String -> IO OsString
encodeLE =(PosixString -> OsString) -> IO PosixString -> IO OsString
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmapPosixString -> OsString
OsString (IO PosixString -> IO OsString)
-> (String -> IO PosixString) -> String -> IO OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.String -> IO PosixString
PF.encodeLE -- | Partial unicode friendly decoding.---- On windows this decodes as UTF16-LE (strictly), which is a pretty good guess.-- On unix 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.decodeUtf ::MonadThrowm =>OsString ->m StringdecodeUtf :: forall (m :: * -> *). MonadThrow m => OsString -> m String
decodeUtf (OsString PosixString
x )=PosixString -> m String
forall (m :: * -> *). MonadThrow m => PosixString -> m String
PF.decodeUtf PosixString
x -- | Decode an 'OsString' with the specified encoding.---- The String is forced into memory to catch all exceptions.decodeWith ::TextEncoding-- ^ unix text encoding->TextEncoding-- ^ windows text encoding->OsString ->EitherEncodingException String
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
decodeWith_winEnc(OsStringx)=PF.decodeWithwinEncx
#else
decodeWith :: TextEncoding
-> TextEncoding -> OsString -> Either EncodingException String
decodeWith TextEncoding
unixEnc TextEncoding
_(OsString PosixString
x )=TextEncoding -> PosixString -> Either EncodingException String
PF.decodeWith TextEncoding
unixEnc PosixString
x 
#endif
-- | Like 'decodeUtf', 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).decodeFS ::OsString ->IOString
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
decodeFS(OsString(WindowsStringx))=decodeWithBaseWindowsx
#else
decodeFS :: OsString -> IO String
decodeFS (OsString (PosixString ShortByteString
x ))=ShortByteString -> IO String
decodeWithBasePosix ShortByteString
x 
#endif
-- | Like 'decodeUtf', except this mimics the behavior of the base library when doing string operations,-- which is:---- 1. on unix this uses 'getLocaleEncoding'-- 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).decodeLE ::OsString ->IOStringdecodeLE :: OsString -> IO String
decodeLE (OsString PosixString
x )=PosixString -> IO String
PF.decodeLE PosixString
x -- | Constructs an @OsString@ from a ByteString.---- On windows, this ensures valid UCS-2LE, on unix it is passed unchanged/unchecked.---- Throws 'EncodingException' on invalid UCS-2LE on windows (although unlikely).fromBytes ::MonadThrowm =>ByteString->m OsString fromBytes :: forall (m :: * -> *). MonadThrow m => ByteString -> m OsString
fromBytes =(PosixString -> OsString) -> m PosixString -> m OsString
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmapPosixString -> OsString
OsString (m PosixString -> m OsString)
-> (ByteString -> m PosixString) -> ByteString -> m OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ByteString -> m PosixString
forall (m :: * -> *). MonadThrow m => ByteString -> m PosixString
PF.fromBytes -- | QuasiQuote an 'OsString'. This accepts Unicode characters-- and encodes as UTF-8 on unix and UTF-16 on windows.-- If used as pattern, requires turning on the @ViewPatterns@ extension.osstr ::QuasiQuoterosstr :: QuasiQuoter
osstr =QuasiQuoter
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
{quoteExp=\s->doosp<-either(fail.show)(pure.OsString).PF.encodeWith(mkUTF16leErrorOnCodingFailure)$sliftosp,quotePat=\s->doosp'<-either(fail.show)(pure.OsString).PF.encodeWith(mkUTF16leErrorOnCodingFailure)$s[p|((==)osp'->True)|],quoteType=\_->fail"illegal QuasiQuote (allowed as expression or pattern only, used as a type)",quoteDec=\_->fail"illegal QuasiQuote (allowed as expression or pattern only, used as a declaration)"}
#else
{quoteExp :: String -> Q Exp
quoteExp=\String
s ->doOsString
osp <-(EncodingException -> Q OsString)
-> (PosixString -> Q OsString)
-> Either EncodingException PosixString
-> Q OsString
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either(String -> Q OsString
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail(String -> Q OsString)
-> (EncodingException -> String) -> EncodingException -> Q OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.EncodingException -> String
forall a. Show a => a -> String
show)(OsString -> Q OsString
forall a. a -> Q a
forall (f :: * -> *) a. Applicative f => a -> f a
pure(OsString -> Q OsString)
-> (PosixString -> OsString) -> PosixString -> Q OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.PosixString -> OsString
OsString )(Either EncodingException PosixString -> Q OsString)
-> (String -> Either EncodingException PosixString)
-> String
-> Q OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.TextEncoding -> String -> Either EncodingException PosixString
PF.encodeWith (CodingFailureMode -> TextEncoding
mkUTF8CodingFailureMode
ErrorOnCodingFailure)(String -> Q OsString) -> String -> Q OsString
forall a b. (a -> b) -> a -> b
$String
s OsString -> Q Exp
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
forall (m :: * -> *). Quote m => OsString -> m Exp
liftOsString
osp ,quotePat :: String -> Q Pat
quotePat=\String
s ->doOsString
osp' <-(EncodingException -> Q OsString)
-> (PosixString -> Q OsString)
-> Either EncodingException PosixString
-> Q OsString
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either(String -> Q OsString
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail(String -> Q OsString)
-> (EncodingException -> String) -> EncodingException -> Q OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.EncodingException -> String
forall a. Show a => a -> String
show)(OsString -> Q OsString
forall a. a -> Q a
forall (f :: * -> *) a. Applicative f => a -> f a
pure(OsString -> Q OsString)
-> (PosixString -> OsString) -> PosixString -> Q OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.PosixString -> OsString
OsString )(Either EncodingException PosixString -> Q OsString)
-> (String -> Either EncodingException PosixString)
-> String
-> Q OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.TextEncoding -> String -> Either EncodingException PosixString
PF.encodeWith (CodingFailureMode -> TextEncoding
mkUTF8CodingFailureMode
ErrorOnCodingFailure)(String -> Q OsString) -> String -> Q OsString
forall a b. (a -> b) -> a -> b
$String
s [p|((==)osp'->True)|],quoteType :: String -> Q Type
quoteType=\String
_->String -> Q Type
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
failString
"illegal QuasiQuote (allowed as expression or pattern only, used as a type)",quoteDec :: String -> Q [Dec]
quoteDec=\String
_->String -> Q [Dec]
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
failString
"illegal QuasiQuote (allowed as expression or pattern only, used as a declaration)"}
#endif
-- | Unpack an 'OsString' to a list of 'OsChar'.unpack ::OsString ->[OsChar ]unpack :: OsString -> [OsChar]
unpack =(PosixString -> [PosixChar]) -> OsString -> [OsChar]
forall a b. Coercible a b => a -> b
coercePosixString -> [PosixChar]
PF.unpack -- | Pack a list of 'OsChar' to an 'OsString'---- Note that using this in conjunction with 'unsafeFromChar' to-- convert from @[Char]@ to 'OsString' is probably not what-- you want, because it will truncate unicode code points.pack ::[OsChar ]->OsString pack :: [OsChar] -> OsString
pack =([PosixChar] -> PosixString) -> [OsChar] -> OsString
forall a b. Coercible a b => a -> b
coerce[PosixChar] -> PosixString
PF.pack empty ::OsString empty :: OsString
empty =OsString
forall a. Monoid a => a
memptysingleton ::OsChar ->OsString singleton :: OsChar -> OsString
singleton =(PosixChar -> PosixString) -> OsChar -> OsString
forall a b. Coercible a b => a -> b
coercePosixChar -> PosixString
PF.singleton -- | Truncates on unix to 1 and on Windows to 2 octets.unsafeFromChar ::Char->OsChar unsafeFromChar :: Char -> OsChar
unsafeFromChar =(Char -> PosixChar) -> Char -> OsChar
forall a b. Coercible a b => a -> b
coerceChar -> PosixChar
PF.unsafeFromChar -- | Converts back to a unicode codepoint (total).toChar ::OsChar ->ChartoChar :: OsChar -> Char
toChar =caseEither
 (Coercion OsChar WindowsChar, Coercion OsString WindowsString)
 (Coercion OsChar PosixChar, Coercion OsString PosixString)
coercionToPlatformTypes ofLeft(Coercion OsChar WindowsChar
co ,Coercion OsString WindowsString
_)->Int -> Char
chr(Int -> Char) -> (OsChar -> Int) -> OsChar -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Word16 -> Int) -> (OsChar -> Word16) -> OsChar -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.WindowsChar -> Word16
getWindowsChar (WindowsChar -> Word16)
-> (OsChar -> WindowsChar) -> OsChar -> Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Coercion OsChar WindowsChar -> OsChar -> WindowsChar
forall a b. Coercion a b -> a -> b
coerceWithCoercion OsChar WindowsChar
co Right(Coercion OsChar PosixChar
co ,Coercion OsString PosixString
_)->Int -> Char
chr(Int -> Char) -> (OsChar -> Int) -> OsChar -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Word8 -> Int) -> (OsChar -> Word8) -> OsChar -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.PosixChar -> Word8
getPosixChar (PosixChar -> Word8) -> (OsChar -> PosixChar) -> OsChar -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Coercion OsChar PosixChar -> OsChar -> PosixChar
forall a b. Coercion a b -> a -> b
coerceWithCoercion OsChar PosixChar
co -- | /O(n)/ Append a byte to the end of a 'OsString'---- @since 1.4.200.0snoc ::OsString ->OsChar ->OsString snoc :: OsString -> OsChar -> OsString
snoc =(PosixString -> PosixChar -> PosixString)
-> OsString -> OsChar -> OsString
forall a b. Coercible a b => a -> b
coercePosixString -> PosixChar -> PosixString
PF.snoc -- | /O(n)/ 'cons' is analogous to (:) for lists.---- @since 1.4.200.0cons ::OsChar ->OsString ->OsString cons :: OsChar -> OsString -> OsString
cons =(PosixChar -> PosixString -> PosixString)
-> OsChar -> OsString -> OsString
forall a b. Coercible a b => a -> b
coercePosixChar -> PosixString -> PosixString
PF.cons -- | /O(1)/ Extract the last element of a 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.---- @since 1.4.200.0last ::HasCallStack=>OsString ->OsChar last :: HasCallStack => OsString -> OsChar
last =(PosixString -> PosixChar) -> OsString -> OsChar
forall a b. Coercible a b => a -> b
coerceHasCallStack => PosixString -> PosixChar
PosixString -> PosixChar
PF.last -- | /O(n)/ Extract the elements after the head of a 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.---- @since 1.4.200.0tail ::HasCallStack=>OsString ->OsString tail :: HasCallStack => OsString -> OsString
tail =(PosixString -> PosixString) -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerceHasCallStack => PosixString -> PosixString
PosixString -> PosixString
PF.tail -- | /O(n)/ Extract the 'head' and 'tail' of a OsString, returning 'Nothing'-- if it is empty.---- @since 1.4.200.0uncons ::OsString ->Maybe(OsChar ,OsString )uncons :: OsString -> Maybe (OsChar, OsString)
uncons =(PosixString -> Maybe (PosixChar, PosixString))
-> OsString -> Maybe (OsChar, OsString)
forall a b. Coercible a b => a -> b
coercePosixString -> Maybe (PosixChar, PosixString)
PF.uncons -- | /O(1)/ Extract the first element of a 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.---- @since 1.4.200.0head ::HasCallStack=>OsString ->OsChar head :: HasCallStack => OsString -> OsChar
head =(PosixString -> PosixChar) -> OsString -> OsChar
forall a b. Coercible a b => a -> b
coerceHasCallStack => PosixString -> PosixChar
PosixString -> PosixChar
PF.head -- | /O(n)/ Return all the elements of a '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.---- @since 1.4.200.0init ::HasCallStack=>OsString ->OsString init :: HasCallStack => OsString -> OsString
init =(PosixString -> PosixString) -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerceHasCallStack => PosixString -> PosixString
PosixString -> PosixString
PF.init -- | /O(n)/ Extract the 'init' and 'last' of a OsString, returning 'Nothing'-- if it is empty.---- @since 1.4.200.0unsnoc ::OsString ->Maybe(OsString ,OsChar )unsnoc :: OsString -> Maybe (OsString, OsChar)
unsnoc =(PosixString -> Maybe (PosixString, PosixChar))
-> OsString -> Maybe (OsString, OsChar)
forall a b. Coercible a b => a -> b
coercePosixString -> Maybe (PosixString, PosixChar)
PF.unsnoc -- | /O(1)/ Test whether a 'OsString' is empty.---- @since 1.4.200.0null ::OsString ->Boolnull :: OsString -> Bool
null =(PosixString -> Bool) -> OsString -> Bool
forall a b. Coercible a b => a -> b
coercePosixString -> Bool
PF.null -- | /O(1)/ The length of a 'OsString'.---- @since 1.4.200.0length ::OsString ->Intlength :: OsString -> Int
length =(PosixString -> Int) -> OsString -> Int
forall a b. Coercible a b => a -> b
coercePosixString -> Int
PF.length -- | /O(n)/ 'map' @f xs@ is the OsString obtained by applying @f@ to each-- element of @xs@.---- @since 1.4.200.0map ::(OsChar ->OsChar )->OsString ->OsString map :: (OsChar -> OsChar) -> OsString -> OsString
map =((PosixChar -> PosixChar) -> PosixString -> PosixString)
-> (OsChar -> OsChar) -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerce(PosixChar -> PosixChar) -> PosixString -> PosixString
PF.map -- | /O(n)/ 'reverse' @xs@ efficiently returns the elements of @xs@ in reverse order.---- @since 1.4.200.0reverse ::OsString ->OsString reverse :: OsString -> OsString
reverse =(PosixString -> PosixString) -> OsString -> OsString
forall a b. Coercible a b => a -> b
coercePosixString -> PosixString
PF.reverse -- | /O(n)/ The 'intercalate' function takes a 'OsString' and a list of-- 'OsString's and concatenates the list after interspersing the first-- argument between each element of the list.---- @since 1.4.200.0intercalate ::OsString ->[OsString ]->OsString intercalate :: OsString -> [OsString] -> OsString
intercalate =(PosixString -> [PosixString] -> PosixString)
-> OsString -> [OsString] -> OsString
forall a b. Coercible a b => a -> b
coercePosixString -> [PosixString] -> PosixString
PF.intercalate -- | 'foldl', applied to a binary operator, a starting value (typically-- the left-identity of the operator), and a OsString, reduces the-- OsString using the binary operator, from left to right.---- @since 1.4.200.0foldl ::foralla .(a ->OsChar ->a )->a ->OsString ->a foldl :: forall a. (a -> OsChar -> a) -> a -> OsString -> a
foldl =((a -> PosixChar -> a) -> a -> PosixString -> a)
-> (a -> OsChar -> a) -> a -> OsString -> a
forall a b. Coercible a b => a -> b
coerce(forall a. (a -> PosixChar -> a) -> a -> PosixString -> a
PF.foldl @a )-- | 'foldl'' is like 'foldl', but strict in the accumulator.---- @since 1.4.200.0foldl' ::foralla .(a ->OsChar ->a )->a ->OsString ->a foldl' :: forall a. (a -> OsChar -> a) -> a -> OsString -> a
foldl' =((a -> PosixChar -> a) -> a -> PosixString -> a)
-> (a -> OsChar -> a) -> a -> OsString -> a
forall a b. Coercible a b => a -> b
coerce(forall a. (a -> PosixChar -> a) -> a -> PosixString -> a
PF.foldl' @a )-- | 'foldl1' is a variant of 'foldl' that has no starting value-- argument, and thus must be applied to non-empty 'OsString's.-- An exception will be thrown in the case of an empty OsString.---- @since 1.4.200.0foldl1 ::(OsChar ->OsChar ->OsChar )->OsString ->OsChar foldl1 :: (OsChar -> OsChar -> OsChar) -> OsString -> OsChar
foldl1 =((PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar)
-> (OsChar -> OsChar -> OsChar) -> OsString -> OsChar
forall a b. Coercible a b => a -> b
coerce(PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar
PF.foldl1 -- | 'foldl1'' is like 'foldl1', but strict in the accumulator.-- An exception will be thrown in the case of an empty OsString.---- @since 1.4.200.0foldl1' ::(OsChar ->OsChar ->OsChar )->OsString ->OsChar foldl1' :: (OsChar -> OsChar -> OsChar) -> OsString -> OsChar
foldl1' =((PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar)
-> (OsChar -> OsChar -> OsChar) -> OsString -> OsChar
forall a b. Coercible a b => a -> b
coerce(PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar
PF.foldl1' -- | 'foldr', applied to a binary operator, a starting value-- (typically the right-identity of the operator), and a OsString,-- reduces the OsString using the binary operator, from right to left.---- @since 1.4.200.0foldr ::foralla .(OsChar ->a ->a )->a ->OsString ->a foldr :: forall a. (OsChar -> a -> a) -> a -> OsString -> a
foldr =((PosixChar -> a -> a) -> a -> PosixString -> a)
-> (OsChar -> a -> a) -> a -> OsString -> a
forall a b. Coercible a b => a -> b
coerce(forall a. (PosixChar -> a -> a) -> a -> PosixString -> a
PF.foldr @a )-- | 'foldr'' is like 'foldr', but strict in the accumulator.---- @since 1.4.200.0foldr' ::foralla .(OsChar ->a ->a )->a ->OsString ->a foldr' :: forall a. (OsChar -> a -> a) -> a -> OsString -> a
foldr' =((PosixChar -> a -> a) -> a -> PosixString -> a)
-> (OsChar -> a -> a) -> a -> OsString -> a
forall a b. Coercible a b => a -> b
coerce(forall a. (PosixChar -> a -> a) -> a -> PosixString -> a
PF.foldr' @a )-- | 'foldr1' is a variant of 'foldr' that has no starting value argument,-- and thus must be applied to non-empty 'OsString's-- An exception will be thrown in the case of an empty OsString.---- @since 1.4.200.0foldr1 ::(OsChar ->OsChar ->OsChar )->OsString ->OsChar foldr1 :: (OsChar -> OsChar -> OsChar) -> OsString -> OsChar
foldr1 =((PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar)
-> (OsChar -> OsChar -> OsChar) -> OsString -> OsChar
forall a b. Coercible a b => a -> b
coerce(PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar
PF.foldr1 -- | 'foldr1'' is a variant of 'foldr1', but is strict in the-- accumulator.---- @since 1.4.200.0foldr1' ::(OsChar ->OsChar ->OsChar )->OsString ->OsChar foldr1' :: (OsChar -> OsChar -> OsChar) -> OsString -> OsChar
foldr1' =((PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar)
-> (OsChar -> OsChar -> OsChar) -> OsString -> OsChar
forall a b. Coercible a b => a -> b
coerce(PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar
PF.foldr1' -- | /O(n)/ Applied to a predicate and a 'OsString', 'all' determines-- if all elements of the 'OsString' satisfy the predicate.---- @since 1.4.200.0all ::(OsChar ->Bool)->OsString ->Boolall :: (OsChar -> Bool) -> OsString -> Bool
all =((PosixChar -> Bool) -> PosixString -> Bool)
-> (OsChar -> Bool) -> OsString -> Bool
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> Bool
PF.all -- | /O(n)/ Applied to a predicate and a 'OsString', 'any' determines if-- any element of the 'OsString' satisfies the predicate.---- @since 1.4.200.0any ::(OsChar ->Bool)->OsString ->Boolany :: (OsChar -> Bool) -> OsString -> Bool
any =((PosixChar -> Bool) -> PosixString -> Bool)
-> (OsChar -> Bool) -> OsString -> Bool
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> Bool
PF.any -- /O(n)/ Concatenate a list of OsStrings.---- @since 1.4.200.0concat ::[OsString ]->OsString concat :: [OsString] -> OsString
concat =[OsString] -> OsString
forall a. Monoid a => [a] -> a
mconcat-- | /O(n)/ 'replicate' @n x@ is a OsString of length @n@ with @x@-- the value of every element. The following holds:---- > replicate w c = unfoldr w (\u -> Just (u,u)) c---- @since 1.4.200.0replicate ::Int->OsChar ->OsString replicate :: Int -> OsChar -> OsString
replicate =(Int -> PosixChar -> PosixString) -> Int -> OsChar -> OsString
forall a b. Coercible a b => a -> b
coerceInt -> PosixChar -> PosixString
PF.replicate -- | /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 a '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]---- @since 1.4.200.0unfoldr ::foralla .(a ->Maybe(OsChar ,a ))->a ->OsString unfoldr :: forall a. (a -> Maybe (OsChar, a)) -> a -> OsString
unfoldr =((a -> Maybe (PosixChar, a)) -> a -> PosixString)
-> (a -> Maybe (OsChar, a)) -> a -> OsString
forall a b. Coercible a b => a -> b
coerce(forall a. (a -> Maybe (PosixChar, a)) -> a -> PosixString
PF.unfoldr @a )-- | /O(n)/ Like 'unfoldr', 'unfoldrN' builds a 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)---- @since 1.4.200.0unfoldrN ::foralla .Int->(a ->Maybe(OsChar ,a ))->a ->(OsString ,Maybea )unfoldrN :: forall a.
Int -> (a -> Maybe (OsChar, a)) -> a -> (OsString, Maybe a)
unfoldrN =(Int -> (a -> Maybe (PosixChar, a)) -> a -> (PosixString, Maybe a))
-> Int -> (a -> Maybe (OsChar, a)) -> a -> (OsString, Maybe a)
forall a b. Coercible a b => a -> b
coerce(forall a.
Int -> (a -> Maybe (PosixChar, a)) -> a -> (PosixString, Maybe a)
PF.unfoldrN @a )-- | /O(n)/ 'take' @n@, applied to a OsString @xs@, returns the prefix-- of @xs@ of length @n@, or @xs@ itself if @n > 'length' xs@.---- @since 1.4.200.0take ::Int->OsString ->OsString take :: Int -> OsString -> OsString
take =(Int -> PosixString -> PosixString) -> Int -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerceInt -> PosixString -> PosixString
PF.take -- | /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"---- @since 1.4.200.0takeEnd ::Int->OsString ->OsString takeEnd :: Int -> OsString -> OsString
takeEnd =(Int -> PosixString -> PosixString) -> Int -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerceInt -> PosixString -> PosixString
PF.takeEnd -- | Returns the longest (possibly empty) suffix of elements-- satisfying the predicate.---- @'takeWhileEnd' p@ is equivalent to @'reverse' . 'takeWhile' p . 'reverse'@.---- @since 1.4.200.0takeWhileEnd ::(OsChar ->Bool)->OsString ->OsString takeWhileEnd :: (OsChar -> Bool) -> OsString -> OsString
takeWhileEnd =((PosixChar -> Bool) -> PosixString -> PosixString)
-> (OsChar -> Bool) -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> PosixString
PF.takeWhileEnd -- | Similar to 'Prelude.takeWhile',-- returns the longest (possibly empty) prefix of elements-- satisfying the predicate.---- @since 1.4.200.0takeWhile ::(OsChar ->Bool)->OsString ->OsString takeWhile :: (OsChar -> Bool) -> OsString -> OsString
takeWhile =((PosixChar -> Bool) -> PosixString -> PosixString)
-> (OsChar -> Bool) -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> PosixString
PF.takeWhile -- | /O(n)/ 'drop' @n@ @xs@ returns the suffix of @xs@ after the first n elements, or 'empty' if @n > 'length' xs@.---- @since 1.4.200.0drop ::Int->OsString ->OsString drop :: Int -> OsString -> OsString
drop =(Int -> PosixString -> PosixString) -> Int -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerceInt -> PosixString -> PosixString
PF.drop -- | /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"-- ""---- @since 1.4.200.0dropEnd ::Int->OsString ->OsString dropEnd :: Int -> OsString -> OsString
dropEnd =(Int -> PosixString -> PosixString) -> Int -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerceInt -> PosixString -> PosixString
PF.dropEnd -- | Similar to 'Prelude.dropWhile',-- drops the longest (possibly empty) prefix of elements-- satisfying the predicate and returns the remainder.---- @since 1.4.200.0dropWhile ::(OsChar ->Bool)->OsString ->OsString dropWhile :: (OsChar -> Bool) -> OsString -> OsString
dropWhile =((PosixChar -> Bool) -> PosixString -> PosixString)
-> (OsChar -> Bool) -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> PosixString
PF.dropWhile -- | Similar to 'Prelude.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'@.---- @since 1.4.200.0dropWhileEnd ::(OsChar ->Bool)->OsString ->OsString dropWhileEnd :: (OsChar -> Bool) -> OsString -> OsString
dropWhileEnd =((PosixChar -> Bool) -> PosixString -> PosixString)
-> (OsChar -> Bool) -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> PosixString
PF.dropWhileEnd -- | 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))@.---- @since 1.4.200.0breakEnd ::(OsChar ->Bool)->OsString ->(OsString ,OsString )breakEnd :: (OsChar -> Bool) -> OsString -> (OsString, OsString)
breakEnd =((PosixChar -> Bool) -> PosixString -> (PosixString, PosixString))
-> (OsChar -> Bool) -> OsString -> (OsString, OsString)
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
PF.breakEnd -- | Similar to 'Prelude.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))@.---- @since 1.4.200.0break ::(OsChar ->Bool)->OsString ->(OsString ,OsString )break :: (OsChar -> Bool) -> OsString -> (OsString, OsString)
break =((PosixChar -> Bool) -> PosixString -> (PosixString, PosixString))
-> (OsChar -> Bool) -> OsString -> (OsString, OsString)
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
PF.break -- | Similar to 'Prelude.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)@.---- @since 1.4.200.0span ::(OsChar ->Bool)->OsString ->(OsString ,OsString )span :: (OsChar -> Bool) -> OsString -> (OsString, OsString)
span =((PosixChar -> Bool) -> PosixString -> (PosixString, PosixString))
-> (OsChar -> Bool) -> OsString -> (OsString, OsString)
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
PF.span -- | 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)---- @since 1.4.200.0spanEnd ::(OsChar ->Bool)->OsString ->(OsString ,OsString )spanEnd :: (OsChar -> Bool) -> OsString -> (OsString, OsString)
spanEnd =((PosixChar -> Bool) -> PosixString -> (PosixString, PosixString))
-> (OsChar -> Bool) -> OsString -> (OsString, OsString)
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
PF.spanEnd -- | /O(n)/ 'splitAt' @n sbs@ is equivalent to @('take' n sbs, 'drop' n sbs)@.---- @since 1.4.200.0splitAt ::Int->OsString ->(OsString ,OsString )splitAt :: Int -> OsString -> (OsString, OsString)
splitAt =(Int -> PosixString -> (PosixString, PosixString))
-> Int -> OsString -> (OsString, OsString)
forall a b. Coercible a b => a -> b
coerceInt -> PosixString -> (PosixString, PosixString)
PF.splitAt -- | /O(n)/ Break a '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 . (==)---- @since 1.4.200.0split ::OsChar ->OsString ->[OsString ]split :: OsChar -> OsString -> [OsString]
split =(PosixChar -> PosixString -> [PosixString])
-> OsChar -> OsString -> [OsString]
forall a b. Coercible a b => a -> b
coercePosixChar -> PosixString -> [PosixString]
PF.split -- | /O(n)/ Splits a '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 [""]---- @since 1.4.200.0splitWith ::(OsChar ->Bool)->OsString ->[OsString ]splitWith :: (OsChar -> Bool) -> OsString -> [OsString]
splitWith =((PosixChar -> Bool) -> PosixString -> [PosixString])
-> (OsChar -> Bool) -> OsString -> [OsString]
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> [PosixString]
PF.splitWith -- | /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'.---- @since 1.4.200.0stripSuffix ::OsString ->OsString ->MaybeOsString stripSuffix :: OsString -> OsString -> Maybe OsString
stripSuffix =(PosixString -> PosixString -> Maybe PosixString)
-> OsString -> OsString -> Maybe OsString
forall a b. Coercible a b => a -> b
coercePosixString -> PosixString -> Maybe PosixString
PF.stripSuffix -- | /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'.---- @since 1.4.200.0stripPrefix ::OsString ->OsString ->MaybeOsString stripPrefix :: OsString -> OsString -> Maybe OsString
stripPrefix =(PosixString -> PosixString -> Maybe PosixString)
-> OsString -> OsString -> Maybe OsString
forall a b. Coercible a b => a -> b
coercePosixString -> PosixString -> Maybe PosixString
PF.stripPrefix -- | Check whether one string is a substring of another.---- @since 1.4.200.0isInfixOf ::OsString ->OsString ->BoolisInfixOf :: OsString -> OsString -> Bool
isInfixOf =(PosixString -> PosixString -> Bool)
-> OsString -> OsString -> Bool
forall a b. Coercible a b => a -> b
coercePosixString -> PosixString -> Bool
PF.isInfixOf -- |/O(n)/ The 'isPrefixOf' function takes two OsStrings and returns 'True'---- @since 1.4.200.0isPrefixOf ::OsString ->OsString ->BoolisPrefixOf :: OsString -> OsString -> Bool
isPrefixOf =(PosixString -> PosixString -> Bool)
-> OsString -> OsString -> Bool
forall a b. Coercible a b => a -> b
coercePosixString -> PosixString -> Bool
PF.isPrefixOf -- | /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---- @since 1.4.200.0isSuffixOf ::OsString ->OsString ->BoolisSuffixOf :: OsString -> OsString -> Bool
isSuffixOf =(PosixString -> PosixString -> Bool)
-> OsString -> OsString -> Bool
forall a b. Coercible a b => a -> b
coercePosixString -> PosixString -> Bool
PF.isSuffixOf -- | 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.---- @since 1.4.200.0breakSubstring ::OsString ->OsString ->(OsString ,OsString )breakSubstring :: OsString -> OsString -> (OsString, OsString)
breakSubstring =(PosixString -> PosixString -> (PosixString, PosixString))
-> OsString -> OsString -> (OsString, OsString)
forall a b. Coercible a b => a -> b
coercePosixString -> PosixString -> (PosixString, PosixString)
PF.breakSubstring -- | /O(n)/ 'elem' is the 'OsString' membership predicate.---- @since 1.4.200.0elem ::OsChar ->OsString ->Boolelem :: OsChar -> OsString -> Bool
elem =(PosixChar -> PosixString -> Bool) -> OsChar -> OsString -> Bool
forall a b. Coercible a b => a -> b
coercePosixChar -> PosixString -> Bool
PF.elem -- | /O(n)/ The 'find' function takes a predicate and a 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---- @since 1.4.200.0find ::(OsChar ->Bool)->OsString ->MaybeOsChar find :: (OsChar -> Bool) -> OsString -> Maybe OsChar
find =((PosixChar -> Bool) -> PosixString -> Maybe PosixChar)
-> (OsChar -> Bool) -> OsString -> Maybe OsChar
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> Maybe PosixChar
PF.find -- | /O(n)/ 'filter', applied to a predicate and a OsString,-- returns a OsString containing those characters that satisfy the-- predicate.---- @since 1.4.200.0filter ::(OsChar ->Bool)->OsString ->OsString filter :: (OsChar -> Bool) -> OsString -> OsString
filter =((PosixChar -> Bool) -> PosixString -> PosixString)
-> (OsChar -> Bool) -> OsString -> OsString
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> PosixString
PF.filter -- | /O(n)/ The 'partition' function takes a predicate a 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)---- @since 1.4.200.0partition ::(OsChar ->Bool)->OsString ->(OsString ,OsString )partition :: (OsChar -> Bool) -> OsString -> (OsString, OsString)
partition =((PosixChar -> Bool) -> PosixString -> (PosixString, PosixString))
-> (OsChar -> Bool) -> OsString -> (OsString, OsString)
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
PF.partition -- | /O(1)/ 'OsString' index (subscript) operator, starting from 0.---- @since 1.4.200.0index ::HasCallStack=>OsString ->Int->OsChar index :: HasCallStack => OsString -> Int -> OsChar
index =(PosixString -> Int -> PosixChar) -> OsString -> Int -> OsChar
forall a b. Coercible a b => a -> b
coerceHasCallStack => PosixString -> Int -> PosixChar
PosixString -> Int -> PosixChar
PF.index -- | /O(1)/ 'OsString' index, starting from 0, that returns 'Just' if:---- > 0 <= n < length bs---- @since 1.4.200.0indexMaybe ::OsString ->Int->MaybeOsChar indexMaybe :: OsString -> Int -> Maybe OsChar
indexMaybe =(PosixString -> Int -> Maybe PosixChar)
-> OsString -> Int -> Maybe OsChar
forall a b. Coercible a b => a -> b
coercePosixString -> Int -> Maybe PosixChar
PF.indexMaybe -- | /O(1)/ 'OsString' index, starting from 0, that returns 'Just' if:---- > 0 <= n < length bs---- @since 1.4.200.0(!?) ::OsString ->Int->MaybeOsChar !? :: OsString -> Int -> Maybe OsChar
(!?) =OsString -> Int -> Maybe OsChar
indexMaybe -- | /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.---- @since 1.4.200.0elemIndex ::OsChar ->OsString ->MaybeIntelemIndex :: OsChar -> OsString -> Maybe Int
elemIndex =(PosixChar -> PosixString -> Maybe Int)
-> OsChar -> OsString -> Maybe Int
forall a b. Coercible a b => a -> b
coercePosixChar -> PosixString -> Maybe Int
PF.elemIndex -- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning-- the indices of all elements equal to the query element, in ascending order.---- @since 1.4.200.0elemIndices ::OsChar ->OsString ->[Int]elemIndices :: OsChar -> OsString -> [Int]
elemIndices =(PosixChar -> PosixString -> [Int]) -> OsChar -> OsString -> [Int]
forall a b. Coercible a b => a -> b
coercePosixChar -> PosixString -> [Int]
PF.elemIndices -- | count returns the number of times its argument appears in the OsString---- @since 1.4.200.0count ::OsChar ->OsString ->Intcount :: OsChar -> OsString -> Int
count =(PosixChar -> PosixString -> Int) -> OsChar -> OsString -> Int
forall a b. Coercible a b => a -> b
coercePosixChar -> PosixString -> Int
PF.count -- | /O(n)/ The 'findIndex' function takes a predicate and a 'OsString' and-- returns the index of the first element in the OsString-- satisfying the predicate.---- @since 1.4.200.0findIndex ::(OsChar ->Bool)->OsString ->MaybeIntfindIndex :: (OsChar -> Bool) -> OsString -> Maybe Int
findIndex =((PosixChar -> Bool) -> PosixString -> Maybe Int)
-> (OsChar -> Bool) -> OsString -> Maybe Int
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> Maybe Int
PF.findIndex -- | /O(n)/ The 'findIndices' function extends 'findIndex', by returning the-- indices of all elements satisfying the predicate, in ascending order.---- @since 1.4.200.0findIndices ::(OsChar ->Bool)->OsString ->[Int]findIndices :: (OsChar -> Bool) -> OsString -> [Int]
findIndices =((PosixChar -> Bool) -> PosixString -> [Int])
-> (OsChar -> Bool) -> OsString -> [Int]
forall a b. Coercible a b => a -> b
coerce(PosixChar -> Bool) -> PosixString -> [Int]
PF.findIndices 

AltStyle によって変換されたページ (->オリジナル) /