ghcup-0.1.18.0: ghc toolchain installer
Copyright(c) Julian Ospald 2020
LicenseLGPL-3.0
Maintainerhasufell@hasufell.de
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

GHCup.Prelude.Internal

Description

Stuff that doesn't need GHCup modules, so we can avoid recursive imports.

Synopsis

Documentation

>>> import Data.ByteString.Internal (c2w, w2c)
>>> import Test.QuickCheck
>>> import Data.Word8
>>> import qualified Data.Text as T
>>> import qualified Data.Char as C
>>> import Data.List
>>> instance Arbitrary T.Text where arbitrary = T.pack <$> arbitrary

fS :: IsString a => String -> a Source #

fSM :: Maybe a -> Maybe a Source #

tSM :: Maybe a -> Maybe a Source #

iE :: String -> IO a Source #

showT :: Show a => a -> Text Source #

whenM :: Monad m => m Bool -> m () -> m () Source #

Like when, but where the test can be monadic.

unlessM :: Monad m => m Bool -> m () -> m () Source #

Like unless, but where the test can be monadic.

ifM :: Monad m => m Bool -> m a -> m a -> m a Source #

Like if, but where the test can be monadic.

whileM :: Monad m => m a -> (a -> m Bool) -> m a Source #

whileM_ :: Monad m => m a -> (a -> m Bool) -> m () Source #

guardM :: (Monad m, Alternative m) => m Bool -> m () Source #

handleIO' :: (MonadIO m, MonadCatch m) => IOErrorType -> (IOException -> m a) -> m a -> m a Source #

(??) :: forall e es a m. (Monad m, e :< es) => Maybe a -> e -> Excepts es m a Source #

(!?) :: forall e es a m. (Monad m, e :< es) => m (Maybe a) -> e -> Excepts es m a Source #

lE :: forall e es a m. (Monad m, e :< es) => Either e a -> Excepts es m a Source #

lE' :: forall e' e es a m. (Monad m, e :< es) => (e' -> e) -> Either e' a -> Excepts es m a Source #

lEM :: forall e es a m. (Monad m, e :< es) => m (Either e a) -> Excepts es m a Source #

lEM' :: forall e' e es a m. (Monad m, e :< es) => (e' -> e) -> m (Either e' a) -> Excepts es m a Source #

fromEither :: Either a b -> VEither '[a] b Source #

liftIOException' :: (MonadCatch m, MonadIO m, Monad m, e :< es', LiftVariant es es') => IOErrorType -> e -> Excepts es m a -> Excepts es' m a Source #

liftIOException :: (MonadCatch m, MonadIO m, Monad m, e :< es') => IOErrorType -> e -> m a -> Excepts es' m a Source #

hideError :: (MonadIO m, MonadCatch m) => IOErrorType -> m () -> m () Source #

Uses safe-exceptions.

hideErrorDef :: (MonadIO m, MonadCatch m) => [IOErrorType] -> a -> m a -> m a Source #

hideErrorDefM :: (MonadIO m, MonadCatch m) => [IOErrorType] -> m a -> m a -> m a Source #

hideExcept :: forall e es es' a m. (Monad m, e :< es, LiftVariant (Remove e es) es') => e -> a -> Excepts es m a -> Excepts es' m a Source #

hideExcept' :: forall e es es' m. (Monad m, e :< es, LiftVariant (Remove e es) es') => e -> Excepts es m () -> Excepts es' m () Source #

reThrowAll :: forall e es es' a m. (Monad m, e :< es') => (V es -> e) -> Excepts es m a -> Excepts es' m a Source #

reThrowAllIO :: forall e es es' a m. (MonadCatch m, Monad m, MonadIO m, e :< es') => (V es -> e) -> (IOException -> e) -> Excepts es m a -> Excepts es' m a Source #

throwEither :: (Exception a, MonadThrow m) => Either a b -> m b Source #

throwEither' :: (Exception a, MonadThrow m) => a -> Either x b -> m b Source #

throwMaybe :: (Exception a, MonadThrow m) => a -> Maybe b -> m b Source #

throwMaybeM :: (Exception a, MonadThrow m) => a -> m (Maybe b) -> m b Source #

decUTF8Safe :: ByteString -> Text Source #

Safe decodeUtf8With. Replaces an invalid input byte with the Unicode replacement character U+FFFD.

escapeVerRex :: Version -> ByteString Source #

Escape a version for use in regex

recover :: (MonadIO m, MonadMask m) => m a -> m a Source #

traverseFold :: (Foldable t, Applicative m, Monoid b) => (a -> m b) -> t a -> m b Source #

Gathering monoidal values

>>> traverseFold (pure . (:["0"])) ["1","2"]
["1","0","2","0"]
>>> traverseFold Just ["1","2","3","4","5"]
Just "12345"
\t -> traverseFold Just t === Just (mconcat t)

forFold :: (Foldable t, Applicative m, Monoid b) => t a -> (a -> m b) -> m b Source #

Gathering monoidal values

stripNewline :: String -> String Source #

Strip \r and \n from Strings

>>> stripNewline "foo\n\n\n"
"foo"
>>> stripNewline "foo\n\n\nfoo"
"foofoo"
>>> stripNewline "foo\r"
"foo"
>>> stripNewline "foo"
"foo"
\t -> stripNewline (t <> "\n") === stripNewline t
\t -> not (any (isNewLine . c2w) t) ==> stripNewline t == t

stripNewlineEnd :: String -> String Source #

Strip \r and \n from end of String.

>>> stripNewlineEnd "foo\n\n\n"
"foo"
>>> stripNewlineEnd "foo\n\n\nfoo"
"foo\n\n\nfoo"
>>> stripNewlineEnd "foo\r"
"foo"
>>> stripNewlineEnd "foo"
"foo"
\t -> stripNewlineEnd (t <> "\n") === stripNewlineEnd t
\t -> not (any (isNewLine . c2w) t) ==> stripNewlineEnd t == t

stripNewline' :: Text -> Text Source #

Strip \r and \n from Texts

>>> stripNewline' "foo\n\n\n"
"foo"
>>> stripNewline' "foo\n\n\nfoo"
"foofoo"
>>> stripNewline' "foo\r"
"foo"
>>> stripNewline' "foo"
"foo"
\t -> stripNewline' (t <> "\n") === stripNewline' t
\t -> not (T.any (isNewLine . c2w) t) ==> stripNewline' t == t

isNewLine :: Word8 -> Bool Source #

Is the word8 a newline?

>>> isNewLine (c2w '\n')
True
>>> isNewLine (c2w '\r')
True
\w -> w /= _lf && w /= _cr ==> not (isNewLine w)

splitOnPVP :: String -> String -> (String, String) Source #

Split on a PVP suffix.

>>> splitOnPVP "-" "ghc-iserv-dyn-9.3.20210706"
("ghc-iserv-dyn","9.3.20210706")
>>> splitOnPVP "-" "ghc-iserv-dyn"
("ghc-iserv-dyn","")

findM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a) Source #

Like find, but where the test can be monadic.

>>> findM (Just . C.isUpper) "teST"
Just (Just 'S')
>>> findM (Just . C.isUpper) "test"
Just Nothing
>>> findM (Just . const True) ["x",undefined]
Just (Just "x")

dropSuffix :: Eq a => [a] -> [a] -> [a] Source #

Drops the given suffix from a list. It returns the original sequence if the sequence doesn't end with the given suffix.

>>> dropSuffix "!" "Hello World!"
"Hello World"
>>> dropSuffix "!" "Hello World!!"
"Hello World!"
>>> dropSuffix "!" "Hello World."
"Hello World."

stripSuffix :: Eq a => [a] -> [a] -> Maybe [a] Source #

Return the prefix of the second list if its suffix matches the entire first list.

>>> stripSuffix "bar" "foobar"
Just "foo"
>>> stripSuffix ""    "baz"
Just "baz"
>>> stripSuffix "foo" "quux"
Nothing

dropPrefix :: Eq a => [a] -> [a] -> [a] Source #

Drops the given prefix from a list. It returns the original sequence if the sequence doesn't start with the given prefix.

>>> dropPrefix "Mr. " "Mr. Men"
"Men"
>>> dropPrefix "Mr. " "Dr. Men"
"Dr. Men"

splitOn :: Eq a => [a] -> [a] -> [[a]] Source #

Break a list into pieces separated by the first list argument, consuming the delimiter. An empty delimiter is invalid, and will cause an error to be raised.

>>> splitOn "\r\n" "a\r\nb\r\nd\r\ne"
["a","b","d","e"]
>>> splitOn "aaa"  "aaaXaaaXaaaXaaa"
["","X","X","X",""]
>>> splitOn "x"    "x"
["",""]
>>> splitOn "x"    ""
[""]
\s x -> s /= "" ==> intercalate s (splitOn s x) == x
\c x -> splitOn [c] x                           == split (==c) x

split :: (a -> Bool) -> [a] -> [[a]] Source #

Splits a list 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.

>>> split (== 'a') "aabbaca"
["","","bb","c",""]
>>> split (== 'a') ""
[""]
>>> split (== ':') "::xyz:abc::123::"
["","","xyz","abc","","123","",""]
>>> split (== ',') "my,list,here"
["my","list","here"]

breakOn :: Eq a => [a] -> [a] -> ([a], [a]) Source #

Find the first instance of needle in haystack. The first element of the returned tuple is the prefix of haystack before needle is matched. The second is the remainder of haystack, starting with the match. If you want the remainder without the match, use stripInfix.

>>> breakOn "::" "a::b::c"
("a","::b::c")
>>> breakOn "/" "foobar"
("foobar","")
\needle haystack -> let (prefix,match) = breakOn needle haystack in prefix ++ match == haystack