(original) (raw)
{-# LANGUAGE Unsafe #-} {-# LANGUAGE CPP , NoImplicitPrelude , BangPatterns , ExplicitForAll , MagicHash , UnboxedTuples , ExistentialQuantification , RankNTypes , KindSignatures , PolyKinds , DataKinds #-}
{-# OPTIONS_GHC -Wno-orphans #-} {-# OPTIONS_HADDOCK hide #-}
#include "MachDeps.h"
module GHC.Base ( module GHC.Base, module GHC.Classes, module GHC.CString, module GHC.Magic, module GHC.Types, module GHC.Prim,
module [GHC.Err](GHC.Err.html),
module [GHC.Maybe](GHC.Maybe.html)
) where
import GHC.Types import GHC.Classes import GHC.CString import GHC.Magic import GHC.Prim import GHC.Err import GHC.Maybe import {-# SOURCE #-} GHC.IO (failIO,mplusIO)
import GHC.Tuple ()
import GHC.Integer ()
import GHC.Natural ()
import {-# SOURCE #-} GHC.Real (Integral) import {-# SOURCE #-} Data.Semigroup.Internal ( stimesDefault , stimesMaybe , stimesList , stimesIdempotentMonoid )
infixr 9 . infixr 5 ++ infixl 4 <$ infixl 1 >>, >>= infixr 1 =<< infixr 0 $, $!
default ()
#if 0
data Bool = False | True data Ordering = LT | EQ | GT data Char = C# Char# type String = [Char] data Int = I# Int# data () = () data [] a = MkNil
not True = False (&&) True True = True otherwise = True
build = errorWithoutStackTrace "urk" foldr = errorWithoutStackTrace "urk" #endif
infixr 6 <>
([<>](GHC.Base.html#%3C%3E)) :: [a](#local-6989586621679020016) -> [a](#local-6989586621679020016) -> [a](#local-6989586621679020016)
[sconcat](GHC.Base.html#sconcat) :: [NonEmpty](GHC.Base.html#NonEmpty) [a](#local-6989586621679020016) -> [a](#local-6989586621679020016)
[sconcat](GHC.Base.html#sconcat) ([a](#local-6989586621679020018) [:|](GHC.Base.html#%3A%7C) as) = [go](#local-6989586621679020020) [a](#local-6989586621679020018) as where
[go](#local-6989586621679020020) [b](#local-6989586621679020021) ([c](#local-6989586621679020022):[cs](#local-6989586621679020023)) = [b](#local-6989586621679020021) [<>](GHC.Base.html#%3C%3E) [go](#local-6989586621679020020) [c](#local-6989586621679020022) [cs](#local-6989586621679020023)
go [b](#local-6989586621679020024) [] = [b](#local-6989586621679020024)
[stimes](GHC.Base.html#stimes) :: [Integral](GHC.Real.html#Integral) [b](#local-6989586621679020017) => [b](#local-6989586621679020017) -> [a](#local-6989586621679020016) -> [a](#local-6989586621679020016)
[stimes](GHC.Base.html#stimes) = [stimesDefault](Data.Semigroup.Internal.html#stimesDefault)
class Semigroup a => Monoid a where
[mempty](GHC.Base.html#mempty) :: [a](#local-6989586621679020015)
[mappend](GHC.Base.html#mappend) :: [a](#local-6989586621679020015) -> [a](#local-6989586621679020015) -> [a](#local-6989586621679020015)
[mappend](GHC.Base.html#mappend) = ([<>](GHC.Base.html#%3C%3E))
{-# INLINE mappend #-}
[mconcat](GHC.Base.html#mconcat) :: [[a](#local-6989586621679020015)] -> [a](#local-6989586621679020015)
[mconcat](GHC.Base.html#mconcat) = [foldr](GHC.Base.html#foldr) [mappend](GHC.Base.html#mappend) [mempty](GHC.Base.html#mempty)
instance Semigroup [a] where (<>) = (++) {-# INLINE (<>) #-}
[stimes](GHC.Base.html#stimes) = [stimesList](Data.Semigroup.Internal.html#stimesList)
instance Monoid [a] where {-# INLINE mempty #-} mempty = [] {-# INLINE mconcat #-} mconcat xss = [x | xs <- xss, x <- xs]
instance Semigroup (NonEmpty a) where (a :| as) <> ~(b :| bs) = a :| (as ++ b : bs)
instance Semigroup b => Semigroup (a -> b) where f <> g = [x](#local-6989586621679020198) -> f x <> g x stimes n f e = stimes n (f e)
instance Monoid b => Monoid (a -> b) where mempty _ = mempty
instance Semigroup () where _ <> _ = () sconcat _ = () stimes _ _ = ()
instance Monoid () where
[mempty](GHC.Base.html#mempty) = ()
[mconcat](GHC.Base.html#mconcat) _ = ()
instance (Semigroup a, Semigroup b) => Semigroup (a, b) where (a,b) <> (a',b') = (a<>a',b<>b') stimes n (a,b) = (stimes n a, stimes n b)
instance (Monoid a, Monoid b) => Monoid (a,b) where mempty = (mempty, mempty)
instance (Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) where (a,b,c) <> (a',b',c') = (a<>a',b<>b',c<>c') stimes n (a,b,c) = (stimes n a, stimes n b, stimes n c)
instance (Monoid a, Monoid b, Monoid c) => Monoid (a,b,c) where mempty = (mempty, mempty, mempty)
instance (Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) where (a,b,c,d) <> (a',b',c',d') = (a<>a',b<>b',c<>c',d<>d') stimes n (a,b,c,d) = (stimes n a, stimes n b, stimes n c, stimes n d)
instance (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a,b,c,d) where mempty = (mempty, mempty, mempty, mempty)
instance (Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) where (a,b,c,d,e) <> (a',b',c',d',e') = (a<>a',b<>b',c<>c',d<>d',e<>e') stimes n (a,b,c,d,e) = (stimes n a, stimes n b, stimes n c, stimes n d, stimes n e)
instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a,b,c,d,e) where mempty = (mempty, mempty, mempty, mempty, mempty)
instance Semigroup Ordering where LT <> _ = LT EQ <> y = y GT <> _ = GT
[stimes](GHC.Base.html#stimes) = [stimesIdempotentMonoid](Data.Semigroup.Internal.html#stimesIdempotentMonoid)
instance Monoid Ordering where mempty = EQ
instance Semigroup a => Semigroup (Maybe a) where Nothing <> b = b a <> Nothing = a Just a <> Just b = Just (a <> b)
[stimes](GHC.Base.html#stimes) = [stimesMaybe](Data.Semigroup.Internal.html#stimesMaybe)
instance Semigroup a => Monoid (Maybe a) where mempty = Nothing
instance Monoid a => Applicative ((,) a) where pure x = (mempty, x) (u, f) <*> (v, x) = (u <> v, f x) liftA2 f (u, x) (v, y) = (u <> v, f x y)
instance Monoid a => Monad ((,) a) where (u, a) >>= k = case k a of (v, b) -> (u <> v, b)
instance Semigroup a => Semigroup (IO a) where (<>) = liftA2 (<>)
instance Monoid a => Monoid (IO a) where mempty = pure mempty
class Functor f where fmap :: (a -> b) -> f a -> f b
([<$](GHC.Base.html#%3C%24)) :: [a](#local-6989586621679020013) -> [f](#local-6989586621679020010) [b](#local-6989586621679020014) -> [f](#local-6989586621679020010) [a](#local-6989586621679020013)
([<$](GHC.Base.html#%3C%24)) = [fmap](GHC.Base.html#fmap) [.](GHC.Base.html#.) [const](GHC.Base.html#const)
class Functor f => Applicative f where {-# MINIMAL pure, ((<*>) | liftA2) #-}
[pure](GHC.Base.html#pure) :: [a](#local-6989586621679019996) -> [f](#local-6989586621679019995) [a](#local-6989586621679019996)
([<*>](GHC.Base.html#%3C%2A%3E)) :: [f](#local-6989586621679019995) ([a](#local-6989586621679019997) -> [b](#local-6989586621679019998)) -> [f](#local-6989586621679019995) [a](#local-6989586621679019997) -> [f](#local-6989586621679019995) [b](#local-6989586621679019998)
([<*>](GHC.Base.html#%3C%2A%3E)) = [liftA2](GHC.Base.html#liftA2) [id](GHC.Base.html#id)
[liftA2](GHC.Base.html#liftA2) :: ([a](#local-6989586621679019999) -> [b](#local-6989586621679020000) -> [c](#local-6989586621679020001)) -> [f](#local-6989586621679019995) [a](#local-6989586621679019999) -> [f](#local-6989586621679019995) [b](#local-6989586621679020000) -> [f](#local-6989586621679019995) [c](#local-6989586621679020001)
[liftA2](GHC.Base.html#liftA2) [f](#local-6989586621679020006) [x](#local-6989586621679020007) = ([<*>](GHC.Base.html#%3C%2A%3E)) ([fmap](GHC.Base.html#fmap) [f](#local-6989586621679020006) [x](#local-6989586621679020007))
([*>](GHC.Base.html#%2A%3E)) :: [f](#local-6989586621679019995) [a](#local-6989586621679020002) -> [f](#local-6989586621679019995) [b](#local-6989586621679020003) -> [f](#local-6989586621679019995) [b](#local-6989586621679020003)
[a1](#local-6989586621679020008) [*>](GHC.Base.html#%2A%3E) [a2](#local-6989586621679020009) = ([id](GHC.Base.html#id) [<$](GHC.Base.html#%3C%24) [a1](#local-6989586621679020008)) [<*>](GHC.Base.html#%3C%2A%3E) [a2](#local-6989586621679020009)
([<*](GHC.Base.html#%3C%2A)) :: [f](#local-6989586621679019995) [a](#local-6989586621679020004) -> [f](#local-6989586621679019995) [b](#local-6989586621679020005) -> [f](#local-6989586621679019995) [a](#local-6989586621679020004)
([<*](GHC.Base.html#%3C%2A)) = [liftA2](GHC.Base.html#liftA2) [const](GHC.Base.html#const)
(<**>) :: Applicative f => f a -> f (a -> b) -> f b (<**>) = liftA2 ([a](#local-6989586621679020359) f -> f a)
liftA :: Applicative f => (a -> b) -> f a -> f b liftA f a = pure f <*> a
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d liftA3 f a b c = liftA2 f a b <*> c
{-# INLINABLE liftA #-} {-# SPECIALISE liftA :: (a1->r) -> IO a1 -> IO r #-} {-# SPECIALISE liftA :: (a1->r) -> Maybe a1 -> Maybe r #-} {-# INLINABLE liftA3 #-} {-# SPECIALISE liftA3 :: (a1->a2->a3->r) -> IO a1 -> IO a2 -> IO a3 -> IO r #-} {-# SPECIALISE liftA3 :: (a1->a2->a3->r) -> Maybe a1 -> Maybe a2 -> Maybe a3 -> Maybe r #-}
join :: (Monad m) => m (m a) -> m a join x = x >>= id
class Applicative m => Monad m where
([>>=](GHC.Base.html#%3E%3E%3D)) :: forall [a](#local-6989586621679019986) [b](#local-6989586621679019987). [m](#local-6989586621679019985) [a](#local-6989586621679019986) -> ([a](#local-6989586621679019986) -> [m](#local-6989586621679019985) [b](#local-6989586621679019987)) -> [m](#local-6989586621679019985) [b](#local-6989586621679019987)
([>>](GHC.Base.html#%3E%3E)) :: forall [a](#local-6989586621679019988) [b](#local-6989586621679019989). [m](#local-6989586621679019985) [a](#local-6989586621679019988) -> [m](#local-6989586621679019985) [b](#local-6989586621679019989) -> [m](#local-6989586621679019985) [b](#local-6989586621679019989)
[m](#local-6989586621679019992) [>>](GHC.Base.html#%3E%3E) [k](#local-6989586621679019993) = [m](#local-6989586621679019992) [>>=](GHC.Base.html#%3E%3E%3D) \_ -> [k](#local-6989586621679019993)
{-# INLINE (>>) #-}
[return](GHC.Base.html#return) :: [a](#local-6989586621679019990) -> [m](#local-6989586621679019985) [a](#local-6989586621679019990)
[return](GHC.Base.html#return) = [pure](GHC.Base.html#pure)
[fail](GHC.Base.html#fail) :: [String](GHC.Base.html#String) -> [m](#local-6989586621679019985) [a](#local-6989586621679019991)
[fail](GHC.Base.html#fail) [s](#local-6989586621679019994) = [errorWithoutStackTrace](GHC.Err.html#errorWithoutStackTrace) [s](#local-6989586621679019994)
{-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-} (=<<) :: Monad m => (a -> m b) -> m a -> m b f =<< x = x >>= f
when :: (Applicative f) => Bool -> f () -> f () {-# INLINABLE when #-} {-# SPECIALISE when :: Bool -> IO () -> IO () #-} {-# SPECIALISE when :: Bool -> Maybe () -> Maybe () #-} when p s = if p then s else pure ()
sequence :: Monad m => [m a] -> m [a] {-# INLINE sequence #-} sequence = mapM id
mapM :: Monad m => (a -> m b) -> [a] -> m [b] {-# INLINE mapM #-} mapM f as = foldr k (return []) as where k a r = do { x <- f a; xs <- r; return (x:xs) }
liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r liftM f m1 = do { x1 <- m1; return (f x1) }
liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) }
liftM3 :: (Monad m) => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r liftM3 f m1 m2 m3 = do { x1 <- m1; x2 <- m2; x3 <- m3; return (f x1 x2 x3) }
liftM4 :: (Monad m) => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r liftM4 f m1 m2 m3 m4 = do { x1 <- m1; x2 <- m2; x3 <- m3; x4 <- m4; return (f x1 x2 x3 x4) }
liftM5 :: (Monad m) => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r liftM5 f m1 m2 m3 m4 m5 = do { x1 <- m1; x2 <- m2; x3 <- m3; x4 <- m4; x5 <- m5; return (f x1 x2 x3 x4 x5) }
{-# INLINABLE liftM #-} {-# SPECIALISE liftM :: (a1->r) -> IO a1 -> IO r #-} {-# SPECIALISE liftM :: (a1->r) -> Maybe a1 -> Maybe r #-} {-# INLINABLE liftM2 #-} {-# SPECIALISE liftM2 :: (a1->a2->r) -> IO a1 -> IO a2 -> IO r #-} {-# SPECIALISE liftM2 :: (a1->a2->r) -> Maybe a1 -> Maybe a2 -> Maybe r #-} {-# INLINABLE liftM3 #-} {-# SPECIALISE liftM3 :: (a1->a2->a3->r) -> IO a1 -> IO a2 -> IO a3 -> IO r #-} {-# SPECIALISE liftM3 :: (a1->a2->a3->r) -> Maybe a1 -> Maybe a2 -> Maybe a3 -> Maybe r #-} {-# INLINABLE liftM4 #-} {-# SPECIALISE liftM4 :: (a1->a2->a3->a4->r) -> IO a1 -> IO a2 -> IO a3 -> IO a4 -> IO r #-} {-# SPECIALISE liftM4 :: (a1->a2->a3->a4->r) -> Maybe a1 -> Maybe a2 -> Maybe a3 -> Maybe a4 -> Maybe r #-} {-# INLINABLE liftM5 #-} {-# SPECIALISE liftM5 :: (a1->a2->a3->a4->a5->r) -> IO a1 -> IO a2 -> IO a3 -> IO a4 -> IO a5 -> IO r #-} {-# SPECIALISE liftM5 :: (a1->a2->a3->a4->a5->r) -> Maybe a1 -> Maybe a2 -> Maybe a3 -> Maybe a4 -> Maybe a5 -> Maybe r #-}
ap :: (Monad m) => m (a -> b) -> m a -> m b ap m1 m2 = do { x1 <- m1; x2 <- m2; return (x1 x2) }
{-# INLINABLE ap #-} {-# SPECIALISE ap :: IO (a -> b) -> IO a -> IO b #-} {-# SPECIALISE ap :: Maybe (a -> b) -> Maybe a -> Maybe b #-}
instance Functor ((->) r) where fmap = (.)
instance Applicative ((->) a) where pure = const (<*>) f g x = f x (g x) liftA2 q f g x = q (f x) (g x)
instance Monad ((->) r) where f >>= k = \ r -> k (f r) r
instance Functor ((,) a) where fmap f (x,y) = (x, f y)
instance Functor Maybe where fmap _ Nothing = Nothing fmap f (Just a) = Just (f a)
instance Applicative Maybe where pure = Just
[Just](GHC.Maybe.html#Just) [f](#local-6989586621679020064) [<*>](GHC.Base.html#%3C%2A%3E) [m](#local-6989586621679020065) = [fmap](GHC.Base.html#fmap) [f](#local-6989586621679020064) [m](#local-6989586621679020065)
[Nothing](GHC.Maybe.html#Nothing) <*> [_m](#local-6989586621679020066) = [Nothing](GHC.Maybe.html#Nothing)
[liftA2](GHC.Base.html#liftA2) [f](#local-6989586621679020067) ([Just](GHC.Maybe.html#Just) [x](#local-6989586621679020068)) ([Just](GHC.Maybe.html#Just) [y](#local-6989586621679020069)) = [Just](GHC.Maybe.html#Just) ([f](#local-6989586621679020067) [x](#local-6989586621679020068) [y](#local-6989586621679020069))
liftA2 _ _ _ = [Nothing](GHC.Maybe.html#Nothing)
[Just](GHC.Maybe.html#Just) [_m1](#local-6989586621679020070) [*>](GHC.Base.html#%2A%3E) [m2](#local-6989586621679020071) = [m2](#local-6989586621679020071)
[Nothing](GHC.Maybe.html#Nothing) *> [_m2](#local-6989586621679020072) = [Nothing](GHC.Maybe.html#Nothing)
instance Monad Maybe where (Just x) >>= k = k x Nothing >>= _ = Nothing
([>>](GHC.Base.html#%3E%3E)) = ([*>](GHC.Base.html#%2A%3E))
[fail](GHC.Base.html#fail) _ = [Nothing](GHC.Maybe.html#Nothing)
infixl 3 <|>
class Applicative f => Alternative f where
[empty](GHC.Base.html#empty) :: [f](#local-6989586621679019974) [a](#local-6989586621679019975)
([<|>](GHC.Base.html#%3C%7C%3E)) :: [f](#local-6989586621679019974) [a](#local-6989586621679019976) -> [f](#local-6989586621679019974) [a](#local-6989586621679019976) -> [f](#local-6989586621679019974) [a](#local-6989586621679019976)
[some](GHC.Base.html#some) :: [f](#local-6989586621679019974) [a](#local-6989586621679019977) -> [f](#local-6989586621679019974) [[a](#local-6989586621679019977)]
[some](GHC.Base.html#some) [v](#local-6989586621679019979) = [some_v](#local-6989586621679019981)
where
[many_v](#local-6989586621679019980) = [some_v](#local-6989586621679019981) [<|>](GHC.Base.html#%3C%7C%3E) [pure](GHC.Base.html#pure) []
[some_v](#local-6989586621679019981) = [liftA2](GHC.Base.html#liftA2) (:) [v](#local-6989586621679019979) [many_v](#local-6989586621679019980)
[many](GHC.Base.html#many) :: [f](#local-6989586621679019974) [a](#local-6989586621679019978) -> [f](#local-6989586621679019974) [[a](#local-6989586621679019978)]
[many](GHC.Base.html#many) [v](#local-6989586621679019982) = [many_v](#local-6989586621679019983)
where
[many_v](#local-6989586621679019983) = [some_v](#local-6989586621679019984) [<|>](GHC.Base.html#%3C%7C%3E) [pure](GHC.Base.html#pure) []
[some_v](#local-6989586621679019984) = [liftA2](GHC.Base.html#liftA2) (:) [v](#local-6989586621679019982) [many_v](#local-6989586621679019983)
instance Alternative Maybe where empty = Nothing Nothing <|> r = r l <|> _ = l
class (Alternative m, Monad m) => MonadPlus m where
mplus :: m a -> m a -> m a mplus = (<|>)
infixr 5 :|
data NonEmpty a = a :| [a]
deriving ( Eq
, Ord
)
instance Functor NonEmpty where fmap f ~(a :| as) = f a :| fmap f as b <$ ~(_ :| as) = b :| (b <$ as)
instance Applicative NonEmpty where pure a = a :| [] (<*>) = ap liftA2 = liftM2
instance Monad NonEmpty where ~(a :| as) >>= f = b :| (bs ++ bs') where b :| bs = f a bs' = as >>= toList . f toList ~(c :| cs) = c : cs
instance Functor [] where {-# INLINE fmap #-} fmap = map
instance Applicative [] where {-# INLINE pure #-} pure x = [x] {-# INLINE (<*>) #-} fs <*> xs = [f x | f <- fs, x <- xs] {-# INLINE liftA2 #-} liftA2 f xs ys = [f x y | x <- xs, y <- ys] {-# INLINE (*>) #-} xs *> ys = [y | _ <- xs, y <- ys]
instance Monad [] where {-# INLINE (>>=) #-} xs >>= f = [y | x <- xs, y <- f x] {-# INLINE (>>) #-} (>>) = (*>) {-# INLINE fail #-} fail _ = []
instance Alternative [] where empty = [] (<|>) = (++)
instance MonadPlus []
foldr :: (a -> b -> b) -> b -> [a] -> b
{-# INLINE [0] foldr #-}
foldr k z = go
where
go [] = z
go (y:ys) = y [k](#local-6989586621679020418)
go ys
build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] {-# INLINE [1] build #-}
augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a] {-# INLINE [1] augment #-} augment g xs = g (:) xs
{-# RULES "fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) . foldr k z (build g) = g k z
"foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . foldr k z (augment g xs) = g k (foldr k z xs)
"foldr/id" foldr (:) [] = \x -> x "foldr/app" [1] forall ys. foldr (:) ys = \xs -> xs ++ ys -- Only activate this from phase 1, because that's -- when we disable the rule that expands (++) into foldr
-- The foldr/cons rule looks nice, but it can give disastrously -- bloated code when commpiling -- array (a,b) [(1,2), (2,2), (3,2), ...very long list... ] -- i.e. when there are very very long literal lists -- So I've disabled it for now. We could have special cases -- for short lists, I suppose. -- "foldr/cons" forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs)
"foldr/single" forall k z x. foldr k z [x] = k x z "foldr/nil" forall k z. foldr k z [] = z
"foldr/cons/build" forall k z x (g::forall b. (a->b->b) -> b -> b) . foldr k z (x:build g) = k x (g k z)
"augment/build" forall (g::forall b. (a->b->b) -> b -> b) (h::forall b. (a->b->b) -> b -> b) . augment g (build h) = build (\c n -> g c (h c n)) "augment/nil" forall (g::forall b. (a->b->b) -> b -> b) . augment g [] = build g #-}
map :: (a -> b) -> [a] -> [b] {-# NOINLINE [0] map #-}
map _ [] = [] map f (x:xs) = f x : map f xs
mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst {-# INLINE [0] mapFB #-} mapFB c f = [x](#local-6989586621679020431) ys -> c (f x) ys
{-# RULES "map" [~1] forall f xs. map f xs = build (\c n -> foldr (mapFB c f) n xs) "mapList" [1] forall f. foldr (mapFB (:) f) [] = map f "mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g) "mapFB/id" forall c. mapFB c (\x -> x) = c #-}
{-# RULES "map/coerce" [1] map coerce = coerce #-}
(++) :: [a] -> [a] -> [a] {-# NOINLINE [1] (++) #-}
(++) [] ys = ys (++) (x:xs) ys = x : xs ++ ys
{-# RULES "++" [~1] forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys #-}
otherwise :: Bool otherwise = True
type String = [Char]
unsafeChr :: Int -> Char unsafeChr (I# i#) = C# (chr# i#)
ord :: Char -> Int ord (C# c#) = I# (ord# c#)
eqString :: String -> String -> Bool
eqString [] [] = True
eqString (c1:cs1) (c2:cs2) = c1 == c2 && cs1 [eqString](GHC.Base.html#eqString)
cs2
eqString _ _ = False
{-# RULES "eqString" (==) = eqString #-}
maxInt, minInt :: Int
#if WORD_SIZE_IN_BITS == 31 minInt = I# (-0x40000000#) maxInt = I# 0x3FFFFFFF# #elif WORD_SIZE_IN_BITS == 32 minInt = I# (-0x80000000#) maxInt = I# 0x7FFFFFFF# #else minInt = I# (-0x8000000000000000#) maxInt = I# 0x7FFFFFFFFFFFFFFF# #endif
assert :: Bool -> a -> a assert _pred r = r
breakpoint :: a -> a breakpoint r = r
breakpointCond :: Bool -> a -> a breakpointCond _ r = r
const :: a -> b -> a const x _ = x
{-# INLINE (.) #-}
(.) :: (b -> c) -> (a -> b) -> a -> c (.) f g = [x](#local-6989586621679020451) -> f (g x)
flip :: (a -> b -> c) -> b -> a -> c flip f x y = f y x
{-# INLINE ($) #-} ($) :: forall r a (b :: TYPE r). (a -> b) -> a -> b f $ x = f x
($!) :: forall r a (b :: TYPE r). (a -> b) -> a -> b f $! x = let = x in f vx
until :: (a -> Bool) -> (a -> a) -> a -> a until p f = go where go x | p x = x | otherwise = go (f x)
asTypeOf :: a -> a -> a asTypeOf = const
instance Functor IO where fmap f x = x >>= (pure . f)
instance Applicative IO where {-# INLINE pure #-} {-# INLINE (*>) #-} {-# INLINE liftA2 #-} pure = returnIO (*>) = thenIO (<*>) = ap liftA2 = liftM2
instance Monad IO where {-# INLINE (>>) #-} {-# INLINE (>>=) #-} (>>) = (*>) (>>=) = bindIO fail s = failIO s
instance Alternative IO where empty = failIO "mzero" (<|>) = mplusIO
instance MonadPlus IO
returnIO :: a -> IO a returnIO x = IO (\ s -> (# s, x #))
bindIO :: IO a -> (a -> IO b) -> IO b bindIO (IO m) k = IO (\ s -> case m s of (# new_s, a #) -> unIO (k a) new_s)
thenIO :: IO a -> IO b -> IO b thenIO (IO m) k = IO (\ s -> case m s of (# new_s, _ #) -> unIO k new_s)
unIO :: IO a -> (State# RealWorld -> (# State# RealWorld, a #)) unIO (IO a) = a
{-# INLINE getTag #-} getTag :: a -> Int# getTag = dataToTag# x
{-# INLINE quotInt #-} {-# INLINE remInt #-}
quotInt, remInt, divInt, modInt :: Int -> Int -> Int
(I# x) [quotInt](GHC.Base.html#quotInt)
(I# y) = I# (x quotInt#
y)
(I# x) [remInt](GHC.Base.html#remInt)
(I# y) = I# (x remInt#
y)
(I# x) [divInt](GHC.Base.html#divInt)
(I# y) = I# (x divInt#
y)
(I# x) [modInt](GHC.Base.html#modInt)
(I# y) = I# (x modInt#
y)
quotRemInt :: Int -> Int -> (Int, Int)
(I# x) [quotRemInt](GHC.Base.html#quotRemInt)
(I# y) = case x quotRemInt#
y of
(# q, r #) ->
(I# q, I# r)
divModInt :: Int -> Int -> (Int, Int)
(I# x) [divModInt](GHC.Base.html#divModInt)
(I# y) = case x [divModInt#](GHC.Base.html#divModInt%23)
y of
(# q, r #) -> (I# q, I# r)
divModInt# :: Int# -> Int# -> (# Int#, Int# #)
x# [divModInt#](GHC.Base.html#divModInt%23)
y#
| isTrue# (x# ># 0#) && isTrue# (y# <# 0#) =
case (x# -# 1#) quotRemInt#
y# of
(# q, r #) -> (# q -# 1#, r +# y# +# 1# #)
| isTrue# (x# <# 0#) && isTrue# (y# ># 0#) =
case (x# +# 1#) quotRemInt#
y# of
(# q, r #) -> (# q -# 1#, r +# y# -# 1# #)
| otherwise =
x# quotRemInt#
y#
shiftL# :: Word# -> Int# -> Word#
a [shiftL#](GHC.Base.html#shiftL%23)
b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0##
| otherwise = a uncheckedShiftL#
b
shiftRL# :: Word# -> Int# -> Word#
a [shiftRL#](GHC.Base.html#shiftRL%23)
b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0##
| otherwise = a uncheckedShiftRL#
b
iShiftL# :: Int# -> Int# -> Int#
a [iShiftL#](GHC.Base.html#iShiftL%23)
b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0#
| otherwise = a uncheckedIShiftL#
b
iShiftRA# :: Int# -> Int# -> Int#
a [iShiftRA#](GHC.Base.html#iShiftRA%23)
b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = if isTrue# (a <# 0#)
then (-1#)
else 0#
| otherwise = a uncheckedIShiftRA#
b
iShiftRL# :: Int# -> Int# -> Int#
a [iShiftRL#](GHC.Base.html#iShiftRL%23)
b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0#
| otherwise = a uncheckedIShiftRL#
b
{-# RULES "unpack" [~1] forall a . unpackCString# a = build (unpackFoldrCString# a) "unpack-list" [1] forall a . unpackFoldrCString# a (:) [] = unpackCString# a "unpack-append" forall a n . unpackFoldrCString# a (:) n = unpackAppendCString# a n
-- There's a built-in rule (in PrelRules.hs) for -- unpackFoldr "foo" c (unpackFoldr "baz" c n) = unpackFoldr "foobaz" c n
#-}