A RetroSearch Logo

Home - News ( United States | United Kingdom | Italy | Germany ) - Football scores

Search Query:

Showing content from http://hackage.haskell.org/package/ghc-internal-9.1201.0/docs/src/GHC.Internal.Base.html below:



{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE EmptyDataDeriving #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE Unsafe #-}



{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_HADDOCK not-home #-}















#include "MachDeps.h"

module GHC.Internal.Base
        (
        module GHC.Internal.Base,
        module GHC.Classes,
        module GHC.CString,
        module GHC.Magic,
        module GHC.Magic.Dict,
        module GHC.Types,
        module GHC.Prim,         
        module GHC.Prim.Ext,     
        module GHC.Prim.PtrEq,   
        module GHC.Internal.Err, 
        module GHC.Internal.Maybe
  )
        where

import GHC.Types hiding (
  Unit#,
  Solo#,
  Tuple0#,
  Tuple1#,
  Tuple2#,
  Tuple3#,
  Tuple4#,
  Tuple5#,
  Tuple6#,
  Tuple7#,
  Tuple8#,
  Tuple9#,
  Tuple10#,
  Tuple11#,
  Tuple12#,
  Tuple13#,
  Tuple14#,
  Tuple15#,
  Tuple16#,
  Tuple17#,
  Tuple18#,
  Tuple19#,
  Tuple20#,
  Tuple21#,
  Tuple22#,
  Tuple23#,
  Tuple24#,
  Tuple25#,
  Tuple26#,
  Tuple27#,
  Tuple28#,
  Tuple29#,
  Tuple30#,
  Tuple31#,
  Tuple32#,
  Tuple33#,
  Tuple34#,
  Tuple35#,
  Tuple36#,
  Tuple37#,
  Tuple38#,
  Tuple39#,
  Tuple40#,
  Tuple41#,
  Tuple42#,
  Tuple43#,
  Tuple44#,
  Tuple45#,
  Tuple46#,
  Tuple47#,
  Tuple48#,
  Tuple49#,
  Tuple50#,
  Tuple51#,
  Tuple52#,
  Tuple53#,
  Tuple54#,
  Tuple55#,
  Tuple56#,
  Tuple57#,
  Tuple58#,
  Tuple59#,
  Tuple60#,
  Tuple61#,
  Tuple62#,
  Tuple63#,
  Tuple64#,
  Sum2#,
  Sum3#,
  Sum4#,
  Sum5#,
  Sum6#,
  Sum7#,
  Sum8#,
  Sum9#,
  Sum10#,
  Sum11#,
  Sum12#,
  Sum13#,
  Sum14#,
  Sum15#,
  Sum16#,
  Sum17#,
  Sum18#,
  Sum19#,
  Sum20#,
  Sum21#,
  Sum22#,
  Sum23#,
  Sum24#,
  Sum25#,
  Sum26#,
  Sum27#,
  Sum28#,
  Sum29#,
  Sum30#,
  Sum31#,
  Sum32#,
  Sum33#,
  Sum34#,
  Sum35#,
  Sum36#,
  Sum37#,
  Sum38#,
  Sum39#,
  Sum40#,
  Sum41#,
  Sum42#,
  Sum43#,
  Sum44#,
  Sum45#,
  Sum46#,
  Sum47#,
  Sum48#,
  Sum49#,
  Sum50#,
  Sum51#,
  Sum52#,
  Sum53#,
  Sum54#,
  Sum55#,
  Sum56#,
  Sum57#,
  Sum58#,
  Sum59#,
  Sum60#,
  Sum61#,
  Sum62#,
  Sum63#,
  )
import GHC.Classes hiding (
  CUnit,
  CSolo,
  CTuple0,
  CTuple1,
  CTuple2,
  CTuple3,
  CTuple4,
  CTuple5,
  CTuple6,
  CTuple7,
  CTuple8,
  CTuple9,
  CTuple10,
  CTuple11,
  CTuple12,
  CTuple13,
  CTuple14,
  CTuple15,
  CTuple16,
  CTuple17,
  CTuple18,
  CTuple19,
  CTuple20,
  CTuple21,
  CTuple22,
  CTuple23,
  CTuple24,
  CTuple25,
  CTuple26,
  CTuple27,
  CTuple28,
  CTuple29,
  CTuple30,
  CTuple31,
  CTuple32,
  CTuple33,
  CTuple34,
  CTuple35,
  CTuple36,
  CTuple37,
  CTuple38,
  CTuple39,
  CTuple40,
  CTuple41,
  CTuple42,
  CTuple43,
  CTuple44,
  CTuple45,
  CTuple46,
  CTuple47,
  CTuple48,
  CTuple49,
  CTuple50,
  CTuple51,
  CTuple52,
  CTuple53,
  CTuple54,
  CTuple55,
  CTuple56,
  CTuple57,
  CTuple58,
  CTuple59,
  CTuple60,
  CTuple61,
  CTuple62,
  CTuple63,
  CTuple64,
  )
import GHC.CString
import GHC.Magic
import GHC.Magic.Dict
import GHC.Prim hiding (dataToTagSmall#, dataToTagLarge#, whereFrom#)
  
  
  

import GHC.Prim.Ext
import GHC.Prim.PtrEq
import GHC.Internal.Err
import GHC.Internal.Maybe
import {-# SOURCE #-} GHC.Internal.IO (mkUserError, mplusIO)

import GHC.Tuple (Solo (MkSolo))


import {-# SOURCE #-} GHC.Internal.Num (Num (..))
import {-# SOURCE #-} GHC.Internal.Real (Integral (..))




infixr 9  .
infixr 5  ++
infixl 4  <$
infixl 1  >>, >>=
infixr 1  =<<
infixr 0  $, $!

infixl 4 <*>, <*, *>, <**>

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




data Void deriving
  ( Void -> Void -> Bool
(Void -> Void -> Bool) -> (Void -> Void -> Bool) -> Eq Void
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Void -> Void -> Bool
== :: Void -> Void -> Bool
$c/= :: Void -> Void -> Bool
/= :: Void -> Void -> Bool
Eq      
  , Eq Void Eq Void => (Void -> Void -> Ordering) -> (Void -> Void -> Bool) -> (Void -> Void -> Bool) -> (Void -> Void -> Bool) -> (Void -> Void -> Bool) -> (Void -> Void -> Void) -> (Void -> Void -> Void) -> Ord Void Void -> Void -> Bool Void -> Void -> Ordering Void -> Void -> Void forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a $ccompare :: Void -> Void -> Ordering compare :: Void -> Void -> Ordering $c< :: Void -> Void -> Bool < :: Void -> Void -> Bool $c<= :: Void -> Void -> Bool <= :: Void -> Void -> Bool $c> :: Void -> Void -> Bool > :: Void -> Void -> Bool $c>= :: Void -> Void -> Bool >= :: Void -> Void -> Bool $cmax :: Void -> Void -> Void max :: Void -> Void -> Void $cmin :: Void -> Void -> Void min :: Void -> Void -> Void Ord     
  )













absurd :: Void -> a
absurd :: forall a. Void -> a
absurd Void
a = case Void
a of {}






vacuous :: Functor f => f Void -> f a
vacuous :: forall (f :: * -> *) a. Functor f => f Void -> f a
vacuous = (Void -> a) -> f Void -> f a
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Void -> a
forall a. Void -> a
absurd

infixr 6 <>














class Semigroup a where
        
        
        
        
        
        
        
        
        
        
        
        
        (<>) :: a -> a -> a
        a
a <> a
b = NonEmpty a -> a
forall a. Semigroup a => NonEmpty a -> a
sconcat (a
a a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [ a
b ])

        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        sconcat :: NonEmpty a -> a
        sconcat (a
a :| [a]
as) = a -> [a] -> a
forall {t}. Semigroup t => t -> [t] -> t
go a
a [a]
as where
          go :: t -> [t] -> t
go t
b (t
c:[t]
cs) = t
b t -> t -> t
forall a. Semigroup a => a -> a -> a
<> t -> [t] -> t
go t
c [t]
cs
          go t
b []     = t
b

        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        stimes :: Integral b => b -> a -> a
        stimes b
y0 a
x0
          | b
y0 b -> b -> Bool
forall a. Ord a => a -> a -> Bool
<= b
0   = [Char] -> a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"stimes: positive multiplier expected"
          | Bool
otherwise = a -> b -> a
forall {a} {t}. (Integral a, Semigroup t) => t -> a -> t
f a
x0 b
y0
          where
            f :: t -> a -> t
f t
x a
y
              | a
y a -> a -> a
forall a. Integral a => a -> a -> a
`rem` a
2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 = t -> a -> t
f (t
x t -> t -> t
forall a. Semigroup a => a -> a -> a
<> t
x) (a
y a -> a -> a
forall a. Integral a => a -> a -> a
`quot` a
2)
              | a
y a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
1 = t
x
              | Bool
otherwise = t -> a -> t -> t
forall {a} {t}. (Integral a, Semigroup t) => t -> a -> t -> t
g (t
x t -> t -> t
forall a. Semigroup a => a -> a -> a
<> t
x) (a
y a -> a -> a
forall a. Integral a => a -> a -> a
`quot` a
2) t
x        
            g :: t -> a -> t -> t
g t
x a
y t
z
              | a
y a -> a -> a
forall a. Integral a => a -> a -> a
`rem` a
2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 = t -> a -> t -> t
g (t
x t -> t -> t
forall a. Semigroup a => a -> a -> a
<> t
x) (a
y a -> a -> a
forall a. Integral a => a -> a -> a
`quot` a
2) t
z
              | a
y a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
1 = t
x t -> t -> t
forall a. Semigroup a => a -> a -> a
<> t
z
              | Bool
otherwise = t -> a -> t -> t
g (t
x t -> t -> t
forall a. Semigroup a => a -> a -> a
<> t
x) (a
y a -> a -> a
forall a. Integral a => a -> a -> a
`quot` a
2) (t
x t -> t -> t
forall a. Semigroup a => a -> a -> a
<> t
z) 

        {-# MINIMAL (<>) | sconcat #-}



























class Semigroup a => Monoid a where
        
        
        
        
        
        
        
        
        mempty :: a
        mempty = [a] -> a
forall a. Monoid a => [a] -> a
mconcat []
        {-# INLINE mempty #-}

        
        
        
        
        
        
        
        mappend :: a -> a -> a
        mappend = a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>)
        {-# INLINE mappend #-}

        
        
        
        
        
        
        
        
        mconcat :: [a] -> a
        mconcat = (a -> a -> a) -> a -> [a] -> a
forall a b. (a -> b -> b) -> b -> [a] -> b
foldr a -> a -> a
forall a. Monoid a => a -> a -> a
mappend a
forall a. Monoid a => a
mempty
        {-# INLINE mconcat #-}
        

        {-# MINIMAL mempty | mconcat #-}


instance Semigroup [a] where
        <> :: [a] -> [a] -> [a]
(<>) = [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
(++)
        {-# INLINE (<>) #-}

        stimes :: forall b. Integral b => b -> [a] -> [a]
stimes b
n [a]
x
          | b
n b -> b -> Bool
forall a. Ord a => a -> a -> Bool
< b
0 = [Char] -> [a]
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"stimes: [], negative multiplier"
          | Bool
otherwise = b -> [a]
forall {t}. (Eq t, Num t) => t -> [a]
rep b
n
          where
            rep :: t -> [a]
rep t
0 = []
            rep t
i = [a]
x [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ t -> [a]
rep (t
i t -> t -> t
forall a. Num a => a -> a -> a
- t
1)


instance Monoid [a] where
        {-# INLINE mempty #-}
        mempty :: [a]
mempty  = []
        {-# INLINE mconcat #-}
        mconcat :: [[a]] -> [a]
mconcat [[a]]
xss = [a
x | [a]
xs <- [[a]]
xss, a
x <- [a]
xs]



instance Semigroup Void where
    Void
a <> :: Void -> Void -> Void
<> Void
_ = Void
a
    stimes :: forall b. Integral b => b -> Void -> Void
stimes b
_ Void
a = Void
a




instance Semigroup (NonEmpty a) where
        (a
a :| [a]
as) <> :: NonEmpty a -> NonEmpty a -> NonEmpty a
<> ~(a
b :| [a]
bs) = a
a a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| ([a]
as [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ a
b a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
bs)


instance Semigroup b => Semigroup (a -> b) where
        a -> b
f <> :: (a -> b) -> (a -> b) -> a -> b
<> a -> b
g = \a
x -> a -> b
f a
x b -> b -> b
forall a. Semigroup a => a -> a -> a
<> a -> b
g a
x
        stimes :: forall b. Integral b => b -> (a -> b) -> a -> b
stimes b
n a -> b
f a
e = b -> b -> b
forall b. Integral b => b -> b -> b
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n (a -> b
f a
e)


instance Monoid b => Monoid (a -> b) where
        mempty :: a -> b
mempty a
_ = b
forall a. Monoid a => a
mempty
        
        
        
        mconcat :: [a -> b] -> a -> b
mconcat = \[a -> b]
fs a
x -> [b] -> b
forall a. Monoid a => [a] -> a
mconcat ([b] -> b) -> [b] -> b
forall a b. (a -> b) -> a -> b
$ ((a -> b) -> b) -> [a -> b] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map (\a -> b
f -> a -> b
f a
x) [a -> b]
fs
        {-# INLINE mconcat #-}


instance Semigroup () where
        ()
_ <> :: () -> () -> ()
<> ()
_      = ()
        sconcat :: NonEmpty () -> ()
sconcat NonEmpty ()
_   = ()
        stimes :: forall b. Integral b => b -> () -> ()
stimes  b
_ ()
_ = ()


instance Monoid () where
        
        mempty :: ()
mempty        = ()
        mconcat :: [()] -> ()
mconcat [()]
_     = ()


instance Semigroup a => Semigroup (Solo a) where
  MkSolo a
a <> :: Solo a -> Solo a -> Solo a
<> MkSolo a
b = a -> Solo a
forall a. a -> Solo a
MkSolo (a
a a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
b)
  stimes :: forall b. Integral b => b -> Solo a -> Solo a
stimes b
n (MkSolo a
a) = a -> Solo a
forall a. a -> Solo a
MkSolo (b -> a -> a
forall b. Integral b => b -> a -> a
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n a
a)


instance Monoid a => Monoid (Solo a) where
  mempty :: Solo a
mempty = a -> Solo a
forall a. a -> Solo a
MkSolo a
forall a. Monoid a => a
mempty


instance (Semigroup a, Semigroup b) => Semigroup (a, b) where
        (a
a,b
b) <> :: (a, b) -> (a, b) -> (a, b)
<> (a
a',b
b') = (a
aa -> a -> a
forall a. Semigroup a => a -> a -> a
<>a
a',b
bb -> b -> b
forall a. Semigroup a => a -> a -> a
<>b
b')
        stimes :: forall b. Integral b => b -> (a, b) -> (a, b)
stimes b
n (a
a,b
b) = (b -> a -> a
forall b. Integral b => b -> a -> a
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n a
a, b -> b -> b
forall b. Integral b => b -> b -> b
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n b
b)


instance (Monoid a, Monoid b) => Monoid (a,b) where
        mempty :: (a, b)
mempty = (a
forall a. Monoid a => a
mempty, b
forall a. Monoid a => a
mempty)


instance (Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) where
        (a
a,b
b,c
c) <> :: (a, b, c) -> (a, b, c) -> (a, b, c)
<> (a
a',b
b',c
c') = (a
aa -> a -> a
forall a. Semigroup a => a -> a -> a
<>a
a',b
bb -> b -> b
forall a. Semigroup a => a -> a -> a
<>b
b',c
cc -> c -> c
forall a. Semigroup a => a -> a -> a
<>c
c')
        stimes :: forall b. Integral b => b -> (a, b, c) -> (a, b, c)
stimes b
n (a
a,b
b,c
c) = (b -> a -> a
forall b. Integral b => b -> a -> a
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n a
a, b -> b -> b
forall b. Integral b => b -> b -> b
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n b
b, b -> c -> c
forall b. Integral b => b -> c -> c
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n c
c)


instance (Monoid a, Monoid b, Monoid c) => Monoid (a,b,c) where
        mempty :: (a, b, c)
mempty = (a
forall a. Monoid a => a
mempty, b
forall a. Monoid a => a
mempty, c
forall a. Monoid a => a
mempty)


instance (Semigroup a, Semigroup b, Semigroup c, Semigroup d)  => Semigroup (a, b, c, d) where
        (a
a,b
b,c
c,d
d) <> :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d)
<> (a
a',b
b',c
c',d
d') = (a
aa -> a -> a
forall a. Semigroup a => a -> a -> a
<>a
a',b
bb -> b -> b
forall a. Semigroup a => a -> a -> a
<>b
b',c
cc -> c -> c
forall a. Semigroup a => a -> a -> a
<>c
c',d
dd -> d -> d
forall a. Semigroup a => a -> a -> a
<>d
d')
        stimes :: forall b. Integral b => b -> (a, b, c, d) -> (a, b, c, d)
stimes b
n (a
a,b
b,c
c,d
d) = (b -> a -> a
forall b. Integral b => b -> a -> a
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n a
a, b -> b -> b
forall b. Integral b => b -> b -> b
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n b
b, b -> c -> c
forall b. Integral b => b -> c -> c
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n c
c, b -> d -> d
forall b. Integral b => b -> d -> d
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n d
d)


instance (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a,b,c,d) where
        mempty :: (a, b, c, d)
mempty = (a
forall a. Monoid a => a
mempty, b
forall a. Monoid a => a
mempty, c
forall a. Monoid a => a
mempty, d
forall a. Monoid a => a
mempty)


instance (Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e)  => Semigroup (a, b, c, d, e) where
        (a
a,b
b,c
c,d
d,e
e) <> :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e)
<> (a
a',b
b',c
c',d
d',e
e') = (a
aa -> a -> a
forall a. Semigroup a => a -> a -> a
<>a
a',b
bb -> b -> b
forall a. Semigroup a => a -> a -> a
<>b
b',c
cc -> c -> c
forall a. Semigroup a => a -> a -> a
<>c
c',d
dd -> d -> d
forall a. Semigroup a => a -> a -> a
<>d
d',e
ee -> e -> e
forall a. Semigroup a => a -> a -> a
<>e
e')
        stimes :: forall b. Integral b => b -> (a, b, c, d, e) -> (a, b, c, d, e)
stimes b
n (a
a,b
b,c
c,d
d,e
e) =
            (b -> a -> a
forall b. Integral b => b -> a -> a
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n a
a, b -> b -> b
forall b. Integral b => b -> b -> b
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n b
b, b -> c -> c
forall b. Integral b => b -> c -> c
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n c
c, b -> d -> d
forall b. Integral b => b -> d -> d
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n d
d, b -> e -> e
forall b. Integral b => b -> e -> e
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n e
e)


instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) =>  Monoid (a,b,c,d,e) where
        mempty :: (a, b, c, d, e)
mempty = (a
forall a. Monoid a => a
mempty, b
forall a. Monoid a => a
mempty, c
forall a. Monoid a => a
mempty, d
forall a. Monoid a => a
mempty, e
forall a. Monoid a => a
mempty)



instance Semigroup Ordering where
    Ordering
LT <> :: Ordering -> Ordering -> Ordering
<> Ordering
_ = Ordering
LT
    Ordering
EQ <> Ordering
y = Ordering
y
    Ordering
GT <> Ordering
_ = Ordering
GT

    stimes :: forall b. Integral b => b -> Ordering -> Ordering
stimes b
n Ordering
x = case b -> b -> Ordering
forall a. Ord a => a -> a -> Ordering
compare b
n b
0 of
      Ordering
LT -> [Char] -> Ordering
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"stimes: Ordering, negative multiplier"
      Ordering
EQ -> Ordering
EQ
      Ordering
GT -> Ordering
x



instance Monoid Ordering where
    mempty :: Ordering
mempty             = Ordering
EQ


instance Semigroup a => Semigroup (Maybe a) where
    Maybe a
Nothing <> :: Maybe a -> Maybe a -> Maybe a
<> Maybe a
b       = Maybe a
b
    Maybe a
a       <> Maybe a
Nothing = Maybe a
a
    Just a
a  <> Just a
b  = a -> Maybe a
forall a. a -> Maybe a
Just (a
a a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
b)

    stimes :: forall b. Integral b => b -> Maybe a -> Maybe a
stimes b
_ Maybe a
Nothing = Maybe a
forall a. Maybe a
Nothing
    stimes b
n (Just a
a) = case b -> b -> Ordering
forall a. Ord a => a -> a -> Ordering
compare b
n b
0 of
      Ordering
LT -> [Char] -> Maybe a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"stimes: Maybe, negative multiplier"
      Ordering
EQ -> Maybe a
forall a. Maybe a
Nothing
      Ordering
GT -> a -> Maybe a
forall a. a -> Maybe a
Just (b -> a -> a
forall b. Integral b => b -> a -> a
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n a
a)










instance Semigroup a => Monoid (Maybe a) where
    mempty :: Maybe a
mempty = Maybe a
forall a. Maybe a
Nothing


instance Applicative Solo where
  pure :: forall a. a -> Solo a
pure = a -> Solo a
forall a. a -> Solo a
MkSolo

  
  
  
  
  
  
  
  MkSolo a -> b
f <*> :: forall a b. Solo (a -> b) -> Solo a -> Solo b
<*> MkSolo a
x = b -> Solo b
forall a. a -> Solo a
MkSolo (a -> b
f a
x)
  liftA2 :: forall a b c. (a -> b -> c) -> Solo a -> Solo b -> Solo c
liftA2 a -> b -> c
f (MkSolo a
x) (MkSolo b
y) = c -> Solo c
forall a. a -> Solo a
MkSolo (a -> b -> c
f a
x b
y)









instance Monoid a => Applicative ((,) a) where
    pure :: forall a. a -> (a, a)
pure a
x = (a
forall a. Monoid a => a
mempty, a
x)
    (a
u, a -> b
f) <*> :: forall a b. (a, a -> b) -> (a, a) -> (a, b)
<*> (a
v, a
x) = (a
u a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
v, a -> b
f a
x)
    liftA2 :: forall a b c. (a -> b -> c) -> (a, a) -> (a, b) -> (a, c)
liftA2 a -> b -> c
f (a
u, a
x) (a
v, b
y) = (a
u a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
v, a -> b -> c
f a
x b
y)


instance Monad Solo where
  MkSolo a
x >>= :: forall a b. Solo a -> (a -> Solo b) -> Solo b
>>= a -> Solo b
f = a -> Solo b
f a
x


instance Monoid a => Monad ((,) a) where
    (a
u, a
a) >>= :: forall a b. (a, a) -> (a -> (a, b)) -> (a, b)
>>= a -> (a, b)
k = case a -> (a, b)
k a
a of (a
v, b
b) -> (a
u a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
v, b
b)


instance Functor ((,,) a b) where
    fmap :: forall a b. (a -> b) -> (a, b, a) -> (a, b, b)
fmap a -> b
f (a
a, b
b, a
c) = (a
a, b
b, a -> b
f a
c)


instance (Monoid a, Monoid b) => Applicative ((,,) a b) where
    pure :: forall a. a -> (a, b, a)
pure a
x = (a
forall a. Monoid a => a
mempty, b
forall a. Monoid a => a
mempty, a
x)
    (a
a, b
b, a -> b
f) <*> :: forall a b. (a, b, a -> b) -> (a, b, a) -> (a, b, b)
<*> (a
a', b
b', a
x) = (a
a a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a', b
b b -> b -> b
forall a. Semigroup a => a -> a -> a
<> b
b', a -> b
f a
x)


instance (Monoid a, Monoid b) => Monad ((,,) a b) where
    (a
u, b
v, a
a) >>= :: forall a b. (a, b, a) -> (a -> (a, b, b)) -> (a, b, b)
>>= a -> (a, b, b)
k = case a -> (a, b, b)
k a
a of (a
u', b
v', b
b) -> (a
u a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
u', b
v b -> b -> b
forall a. Semigroup a => a -> a -> a
<> b
v', b
b)


instance Functor ((,,,) a b c) where
    fmap :: forall a b. (a -> b) -> (a, b, c, a) -> (a, b, c, b)
fmap a -> b
f (a
a, b
b, c
c, a
d) = (a
a, b
b, c
c, a -> b
f a
d)


instance (Monoid a, Monoid b, Monoid c) => Applicative ((,,,) a b c) where
    pure :: forall a. a -> (a, b, c, a)
pure a
x = (a
forall a. Monoid a => a
mempty, b
forall a. Monoid a => a
mempty, c
forall a. Monoid a => a
mempty, a
x)
    (a
a, b
b, c
c, a -> b
f) <*> :: forall a b. (a, b, c, a -> b) -> (a, b, c, a) -> (a, b, c, b)
<*> (a
a', b
b', c
c', a
x) = (a
a a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a', b
b b -> b -> b
forall a. Semigroup a => a -> a -> a
<> b
b', c
c c -> c -> c
forall a. Semigroup a => a -> a -> a
<> c
c', a -> b
f a
x)


instance (Monoid a, Monoid b, Monoid c) => Monad ((,,,) a b c) where
    (a
u, b
v, c
w, a
a) >>= :: forall a b. (a, b, c, a) -> (a -> (a, b, c, b)) -> (a, b, c, b)
>>= a -> (a, b, c, b)
k = case a -> (a, b, c, b)
k a
a of (a
u', b
v', c
w', b
b) -> (a
u a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
u', b
v b -> b -> b
forall a. Semigroup a => a -> a -> a
<> b
v', c
w c -> c -> c
forall a. Semigroup a => a -> a -> a
<> c
w', b
b)


instance Functor ((,,,,) a b c d) where
    fmap :: forall a b. (a -> b) -> (a, b, c, d, a) -> (a, b, c, d, b)
fmap a -> b
f (a
a, b
b, c
c, d
d, a
e) = (a
a, b
b, c
c, d
d, a -> b
f a
e)


instance Functor ((,,,,,) a b c d e) where
    fmap :: forall a b. (a -> b) -> (a, b, c, d, e, a) -> (a, b, c, d, e, b)
fmap a -> b
fun (a
a, b
b, c
c, d
d, e
e, a
f) = (a
a, b
b, c
c, d
d, e
e, a -> b
fun a
f)


instance Functor ((,,,,,,) a b c d e f) where
    fmap :: forall a b.
(a -> b) -> (a, b, c, d, e, f, a) -> (a, b, c, d, e, f, b)
fmap a -> b
fun (a
a, b
b, c
c, d
d, e
e, f
f, a
g) = (a
a, b
b, c
c, d
d, e
e, f
f, a -> b
fun a
g)


instance Semigroup a => Semigroup (IO a) where
    <> :: IO a -> IO a -> IO a
(<>) = (a -> a -> a) -> IO a -> IO a -> IO a
forall a b c. (a -> b -> c) -> IO a -> IO b -> IO c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>)


instance Monoid a => Monoid (IO a) where
    mempty :: IO a
mempty = a -> IO a
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty



class Functor f where
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    

    fmap        :: (a -> b) -> f a -> f b

    
    
    
    
    
    
    
    
    
    
    
    
    
    (<$)        :: a -> f b -> f a
    (<$)        =  (b -> a) -> f b -> f a
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((b -> a) -> f b -> f a) -> (a -> b -> a) -> a -> f b -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b -> a
forall a b. a -> b -> a
const

































































class Functor f => Applicative f where
    {-# MINIMAL pure, ((<*>) | liftA2) #-}
    
    
    
    
    
    
    
    
    
    
    
    
    pure :: a -> f a

    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    (<*>) :: f (a -> b) -> f a -> f b
    (<*>) = ((a -> b) -> a -> b) -> f (a -> b) -> f a -> f b
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (a -> b) -> a -> b
forall a. a -> a
id

    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    liftA2 :: (a -> b -> c) -> f a -> f b -> f c
    liftA2 a -> b -> c
f f a
x = f (b -> c) -> f b -> f c
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
(<*>) ((a -> b -> c) -> f a -> f (b -> c)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b -> c
f f a
x)

    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    

    (*>) :: f a -> f b -> f b
    f a
a1 *> f b
a2 = (b -> b
forall a. a -> a
id (b -> b) -> f a -> f (b -> b)
forall a b. a -> f b -> f a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ f a
a1) f (b -> b) -> f b -> f b
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f b
a2

    
    
    
    
    
    
    
    

    
    
    (<*) :: f a -> f b -> f a
    (<*) = (a -> b -> a) -> f a -> f b -> f a
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> b -> a
forall a b. a -> b -> a
const

















(<**>) :: Applicative f => f a -> f (a -> b) -> f b
<**> :: forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
(<**>) = (a -> (a -> b) -> b) -> f a -> f (a -> b) -> f b
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\a
a a -> b
f -> a -> b
f a
a)


















liftA :: Applicative f => (a -> b) -> f a -> f b
liftA :: forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA a -> b
f f a
a = (a -> b) -> f (a -> b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a -> b
f f (a -> b) -> f a -> f b
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f a
a





liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 :: forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 a -> b -> c -> d
f f a
a f b
b f c
c = (a -> b -> c -> d) -> f a -> f b -> f (c -> d)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> b -> c -> d
f f a
a f b
b f (c -> d) -> f c -> f d
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f c
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 :: forall (m :: * -> *) a. Monad m => m (m a) -> m a
join m (m a)
x            =  m (m a)
x m (m a) -> (m a -> m a) -> m a
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= m a -> m a
forall a. a -> a
id


class Applicative m => Monad m where
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    (>>=)       :: forall a b. m a -> (a -> m b) -> m b

    
    
    
    
    
    
    
    
    
    
    
    
    
    
    (>>)        :: forall a b. m a -> m b -> m b
    m a
m >> m b
k = m a
m m a -> (a -> m b) -> m b
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
_ -> m b
k 
    {-# INLINE (>>) #-}

    
    
    
    
    return      :: a -> m a
    return      = a -> m a
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure






{-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
(=<<)           :: Monad m => (a -> m b) -> m a -> m b
a -> m b
f =<< :: forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< m a
x         = m a
x m a -> (a -> m b) -> m b
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> m b
f












when      :: (Applicative f) => Bool -> f () -> f ()
{-# INLINABLE when #-}
{-# SPECIALISE when :: Bool -> IO () -> IO () #-}
{-# SPECIALISE when :: Bool -> Maybe () -> Maybe () #-}
when :: forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
p f ()
s  = if Bool
p then f ()
s else () -> f ()
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()



sequence :: Monad m => [m a] -> m [a]
{-# INLINE sequence #-}
sequence :: forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence = (m a -> m a) -> [m a] -> m [a]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM m a -> m a
forall a. a -> a
id



mapM :: Monad m => (a -> m b) -> [a] -> m [b]
{-# INLINE mapM #-}
mapM :: forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM a -> m b
f [a]
as = (a -> m [b] -> m [b]) -> m [b] -> [a] -> m [b]
forall a b. (a -> b -> b) -> b -> [a] -> b
foldr a -> m [b] -> m [b]
k ([b] -> m [b]
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return []) [a]
as
            where
              k :: a -> m [b] -> m [b]
k a
a m [b]
r = do { x <- a -> m b
f a
a; xs <- r; return (x:xs) }





liftM   :: (Monad m) => (a1 -> r) -> m a1 -> m r
liftM :: forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM a1 -> r
f m a1
m1              = do { x1 <- m a1
m1; return (f x1) }














liftM2  :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 :: forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 a1 -> a2 -> r
f m a1
m1 m a2
m2          = do { x1 <- m a1
m1; x2 <- m2; return (f x1 x2) }





liftM3 :: (Monad m) => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
liftM3 :: forall (m :: * -> *) a1 a2 a3 r.
Monad m =>
(a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
liftM3 a1 -> a2 -> a3 -> r
f m a1
m1 m a2
m2 m a3
m3       = do { x1 <- m a1
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 :: forall (m :: * -> *) a1 a2 a3 a4 r.
Monad m =>
(a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
liftM4 a1 -> a2 -> a3 -> a4 -> r
f m a1
m1 m a2
m2 m a3
m3 m a4
m4    = do { x1 <- m a1
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 :: forall (m :: * -> *) a1 a2 a3 a4 a5 r.
Monad m =>
(a1 -> a2 -> a3 -> a4 -> a5 -> r)
-> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
liftM5 a1 -> a2 -> a3 -> a4 -> a5 -> r
f m a1
m1 m a2
m2 m a3
m3 m a4
m4 m a5
m5 = do { x1 <- m a1
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 :: forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap m (a -> b)
m1 m a
m2          = do { x1 <- m (a -> b)
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 :: forall a b. (a -> b) -> (r -> a) -> r -> b
fmap = (a -> b) -> (r -> a) -> r -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)


instance Applicative ((->) r) where
    pure :: forall a. a -> r -> a
pure = a -> r -> a
forall a b. a -> b -> a
const
    <*> :: forall a b. (r -> (a -> b)) -> (r -> a) -> r -> b
(<*>) r -> (a -> b)
f r -> a
g r
x = r -> (a -> b)
f r
x (r -> a
g r
x)
    liftA2 :: forall a b c. (a -> b -> c) -> (r -> a) -> (r -> b) -> r -> c
liftA2 a -> b -> c
q r -> a
f r -> b
g r
x = a -> b -> c
q (r -> a
f r
x) (r -> b
g r
x)


instance Monad ((->) r) where
    r -> a
f >>= :: forall a b. (r -> a) -> (a -> r -> b) -> r -> b
>>= a -> r -> b
k = \ r
r -> a -> r -> b
k (r -> a
f r
r) r
r


instance Functor Solo where
  fmap :: forall a b. (a -> b) -> Solo a -> Solo b
fmap a -> b
f (MkSolo a
a) = b -> Solo b
forall a. a -> Solo a
MkSolo (a -> b
f a
a)

  
  
  
  a
x <$ :: forall a b. a -> Solo b -> Solo a
<$ MkSolo b
_ = a -> Solo a
forall a. a -> Solo a
MkSolo a
x


instance Functor ((,) a) where
    fmap :: forall a b. (a -> b) -> (a, a) -> (a, b)
fmap a -> b
f (a
x,a
y) = (a
x, a -> b
f a
y)


instance  Functor Maybe  where
    fmap :: forall a b. (a -> b) -> Maybe a -> Maybe b
fmap a -> b
_ Maybe a
Nothing       = Maybe b
forall a. Maybe a
Nothing
    fmap a -> b
f (Just a
a)      = b -> Maybe b
forall a. a -> Maybe a
Just (a -> b
f a
a)


instance Applicative Maybe where
    pure :: forall a. a -> Maybe a
pure = a -> Maybe a
forall a. a -> Maybe a
Just

    Just a -> b
f  <*> :: forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
<*> Maybe a
m       = (a -> b) -> Maybe a -> Maybe b
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Maybe a
m
    Maybe (a -> b)
Nothing <*> Maybe a
_m      = Maybe b
forall a. Maybe a
Nothing

    liftA2 :: forall a b c. (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c
liftA2 a -> b -> c
f (Just a
x) (Just b
y) = c -> Maybe c
forall a. a -> Maybe a
Just (a -> b -> c
f a
x b
y)
    liftA2 a -> b -> c
_ Maybe a
_ Maybe b
_ = Maybe c
forall a. Maybe a
Nothing

    Just a
_m1 *> :: forall a b. Maybe a -> Maybe b -> Maybe b
*> Maybe b
m2      = Maybe b
m2
    Maybe a
Nothing  *> Maybe b
_m2     = Maybe b
forall a. Maybe a
Nothing


instance  Monad Maybe  where
    (Just a
x) >>= :: forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
>>= a -> Maybe b
k      = a -> Maybe b
k a
x
    Maybe a
Nothing  >>= a -> Maybe b
_      = Maybe b
forall a. Maybe a
Nothing

    >> :: forall a b. Maybe a -> Maybe b -> Maybe b
(>>) = Maybe a -> Maybe b -> Maybe b
forall a b. Maybe a -> Maybe b -> Maybe b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)




infixl 3 <|>




















class Applicative f => Alternative f where
    
    
    
    
    empty :: f a
    
    (<|>) :: f a -> f a -> f a

    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    some :: f a -> f [a]
    some f a
v = f [a]
some_v
      where
        many_v :: f [a]
many_v = f [a]
some_v f [a] -> f [a] -> f [a]
forall a. f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> f [a]
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
        some_v :: f [a]
some_v = (a -> [a] -> [a]) -> f a -> f [a] -> f [a]
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) f a
v f [a]
many_v

    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    many :: f a -> f [a]
    many f a
v = f [a]
many_v
      where
        many_v :: f [a]
many_v = f [a]
some_v f [a] -> f [a] -> f [a]
forall a. f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> f [a]
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
        some_v :: f [a]
some_v = (a -> [a] -> [a]) -> f a -> f [a] -> f [a]
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) f a
v f [a]
many_v





instance Alternative Maybe where
    empty :: forall a. Maybe a
empty = Maybe a
forall a. Maybe a
Nothing
    Maybe a
Nothing <|> :: forall a. Maybe a -> Maybe a -> Maybe a
<|> Maybe a
r = Maybe a
r
    Maybe a
l       <|> Maybe a
_ = Maybe a
l





class (Alternative m, Monad m) => MonadPlus m where
   
   
   
   
   
   
   
   
   
   
   mzero :: m a
   mzero = m a
forall a. m a
forall (f :: * -> *) a. Alternative f => f a
empty

   
   
   
   
   
   mplus :: m a -> m a -> m a
   mplus = m a -> m a -> m a
forall a. m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)




instance MonadPlus Maybe




infixr 5 :|




data NonEmpty a = a :| [a]
  deriving ( NonEmpty a -> NonEmpty a -> Bool
(NonEmpty a -> NonEmpty a -> Bool)
-> (NonEmpty a -> NonEmpty a -> Bool) -> Eq (NonEmpty a)
forall a. Eq a => NonEmpty a -> NonEmpty a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => NonEmpty a -> NonEmpty a -> Bool
== :: NonEmpty a -> NonEmpty a -> Bool
$c/= :: forall a. Eq a => NonEmpty a -> NonEmpty a -> Bool
/= :: NonEmpty a -> NonEmpty a -> Bool
Eq  
           , Eq (NonEmpty a) Eq (NonEmpty a) => (NonEmpty a -> NonEmpty a -> Ordering) -> (NonEmpty a -> NonEmpty a -> Bool) -> (NonEmpty a -> NonEmpty a -> Bool) -> (NonEmpty a -> NonEmpty a -> Bool) -> (NonEmpty a -> NonEmpty a -> Bool) -> (NonEmpty a -> NonEmpty a -> NonEmpty a) -> (NonEmpty a -> NonEmpty a -> NonEmpty a) -> Ord (NonEmpty a) NonEmpty a -> NonEmpty a -> Bool NonEmpty a -> NonEmpty a -> Ordering NonEmpty a -> NonEmpty a -> NonEmpty a forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a forall a. Ord a => Eq (NonEmpty a) forall a. Ord a => NonEmpty a -> NonEmpty a -> Bool forall a. Ord a => NonEmpty a -> NonEmpty a -> Ordering forall a. Ord a => NonEmpty a -> NonEmpty a -> NonEmpty a $ccompare :: forall a. Ord a => NonEmpty a -> NonEmpty a -> Ordering compare :: NonEmpty a -> NonEmpty a -> Ordering $c< :: forall a. Ord a => NonEmpty a -> NonEmpty a -> Bool < :: NonEmpty a -> NonEmpty a -> Bool $c<= :: forall a. Ord a => NonEmpty a -> NonEmpty a -> Bool <= :: NonEmpty a -> NonEmpty a -> Bool $c> :: forall a. Ord a => NonEmpty a -> NonEmpty a -> Bool > :: NonEmpty a -> NonEmpty a -> Bool $c>= :: forall a. Ord a => NonEmpty a -> NonEmpty a -> Bool >= :: NonEmpty a -> NonEmpty a -> Bool $cmax :: forall a. Ord a => NonEmpty a -> NonEmpty a -> NonEmpty a max :: NonEmpty a -> NonEmpty a -> NonEmpty a $cmin :: forall a. Ord a => NonEmpty a -> NonEmpty a -> NonEmpty a min :: NonEmpty a -> NonEmpty a -> NonEmpty a Ord 
           )


instance Functor NonEmpty where
  fmap :: forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
fmap a -> b
f ~(a
a :| [a]
as) = a -> b
f a
a b -> [b] -> NonEmpty b
forall a. a -> [a] -> NonEmpty a
:| (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f [a]
as
  a
b <$ :: forall a b. a -> NonEmpty b -> NonEmpty a
<$ ~(b
_ :| [b]
as)   = a
b   a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| (a
b a -> [b] -> [a]
forall a b. a -> [b] -> [a]
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [b]
as)


instance Applicative NonEmpty where
  pure :: forall a. a -> NonEmpty a
pure a
a = a
a a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| []
  <*> :: forall a b. NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b
(<*>) = NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
  liftA2 :: forall a b c.
(a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
liftA2 = (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2


instance Monad NonEmpty where
  ~(a
a :| [a]
as) >>= :: forall a b. NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b
>>= a -> NonEmpty b
f = b
b b -> [b] -> NonEmpty b
forall a. a -> [a] -> NonEmpty a
:| ([b]
bs [b] -> [b] -> [b]
forall a. [a] -> [a] -> [a]
++ [b]
bs')
    where b
b :| [b]
bs = a -> NonEmpty b
f a
a
          bs' :: [b]
bs' = [a]
as [a] -> (a -> [b]) -> [b]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= NonEmpty b -> [b]
forall {a}. NonEmpty a -> [a]
toList (NonEmpty b -> [b]) -> (a -> NonEmpty b) -> a -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> NonEmpty b
f
          toList :: NonEmpty a -> [a]
toList ~(a
c :| [a]
cs) = a
c a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
cs






instance Functor [] where
    {-# INLINE fmap #-}
    fmap :: forall a b. (a -> b) -> [a] -> [b]
fmap = (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map



instance Applicative [] where
    {-# INLINE pure #-}
    pure :: forall a. a -> [a]
pure a
x    = [a
x]
    {-# INLINE (<*>) #-}
    [a -> b]
fs <*> :: forall a b. [a -> b] -> [a] -> [b]
<*> [a]
xs = [a -> b
f a
x | a -> b
f <- [a -> b]
fs, a
x <- [a]
xs]
    {-# INLINE liftA2 #-}
    liftA2 :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
liftA2 a -> b -> c
f [a]
xs [b]
ys = [a -> b -> c
f a
x b
y | a
x <- [a]
xs, b
y <- [b]
ys]
    {-# INLINE (*>) #-}
    [a]
xs *> :: forall a b. [a] -> [b] -> [b]
*> [b]
ys  = [b
y | a
_ <- [a]
xs, b
y <- [b]
ys]



instance Monad []  where
    {-# INLINE (>>=) #-}
    [a]
xs >>= :: forall a b. [a] -> (a -> [b]) -> [b]
>>= a -> [b]
f             = [b
y | a
x <- [a]
xs, b
y <- a -> [b]
f a
x]
    {-# INLINE (>>) #-}
    >> :: forall a b. [a] -> [b] -> [b]
(>>) = [a] -> [b] -> [b]
forall a b. [a] -> [b] -> [b]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)




instance Alternative [] where
    empty :: forall a. [a]
empty = []
    <|> :: forall a. [a] -> [a] -> [a]
(<|>) = [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
(++)




instance MonadPlus []













foldr            :: (a -> b -> b) -> b -> [a] -> b


{-# INLINE [0] foldr #-}



foldr :: forall a b. (a -> b -> b) -> b -> [a] -> b
foldr a -> b -> b
k b
z = [a] -> b
go
          where
            go :: [a] -> b
go []     = b
z
            go (a
y:[a]
ys) = a
y a -> b -> b
`k` [a] -> b
go [a]
ys










build   :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
{-# INLINE [1] build #-}
        
        
        
        
        
        

build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build forall b. (a -> b -> b) -> b -> b
g = (a -> [a] -> [a]) -> [a] -> [a]
forall b. (a -> b -> b) -> b -> b
g (:) []










augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a]
{-# INLINE [1] augment #-}
augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a]
augment forall b. (a -> b -> b) -> b -> b
g [a]
xs = (a -> [a] -> [a]) -> [a] -> [a]
forall b. (a -> b -> b) -> b -> b
g (:) [a]
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 compiling
--      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 :: forall a b. (a -> b) -> [a] -> [b]
map a -> b
_ []     = []
map a -> b
f (a
x:[a]
xs) = a -> b
f a
x b -> [b] -> [b]
forall a. a -> [a] -> [a]
: (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map a -> b
f [a]
xs


mapFB ::  (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
{-# INLINE [0] mapFB #-} 
mapFB :: forall elt lst a.
(elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
mapFB elt -> lst -> lst
c a -> elt
f = \a
x lst
ys -> elt -> lst -> lst
c (a -> elt
f a
x) lst
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 [2] (++) #-}
  
  
  
++ :: forall a. [a] -> [a] -> [a]
(++) []     [a]
ys = [a]
ys
(++) (a
x:[a]
xs) [a]
ys = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a]
ys

{-# RULES
"++/literal"      forall x. (++) (unpackCString# x)     = unpackAppendCString# x
"++/literal_utf8" forall x. (++) (unpackCStringUtf8# x) = unpackAppendCStringUtf8# x #-}

{-# RULES
"++"    [~1] forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys
  #-}







otherwise               :: Bool
otherwise :: Bool
otherwise               =  Bool
True









































type String = [Char]

unsafeChr :: Int -> Char
unsafeChr :: Int -> Char
unsafeChr (I# Int#
i#) = Char# -> Char
C# (Int# -> Char#
chr# Int#
i#)


ord :: Char -> Int
ord :: Char -> Int
ord (C# Char#
c#) = Int# -> Int
I# (Char# -> Int#
ord# Char#
c#)



eqString :: String -> String -> Bool
eqString :: [Char] -> [Char] -> Bool
eqString []       []       = Bool
True
eqString (Char
c1:[Char]
cs1) (Char
c2:[Char]
cs2) = Char
c1 Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2 Bool -> Bool -> Bool
&& [Char]
cs1 [Char] -> [Char] -> Bool
`eqString` [Char]
cs2
eqString [Char]
_        [Char]
_        = Bool
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 :: Int
minInt  = Int# -> Int
I# (Int#
-0x8000000000000000#)
maxInt :: Int
maxInt  = Int# -> Int
I# Int#
0x7FFFFFFFFFFFFFFF#
#endif






















id                      :: a -> a
id :: forall a. a -> a
id a
x                    =  a
x



















assert :: Bool -> a -> a
assert :: forall a. Bool -> a -> a
assert Bool
_pred a
r = a
r

breakpoint :: a -> a
breakpoint :: forall a. a -> a
breakpoint a
r = a
r

breakpointCond :: Bool -> a -> a
breakpointCond :: forall a. Bool -> a -> a
breakpointCond Bool
_ a
r = a
r

data Opaque = forall a. O a














const                   :: a -> b -> a
const :: forall a b. a -> b -> a
const a
x b
_               =  a
x

















{-# INLINE (.) #-}


(.)    :: (b -> c) -> (a -> b) -> a -> c
. :: forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) b -> c
f a -> b
g = \a
x -> b -> c
f (a -> b
g a
x)














flip :: forall repc a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
flip :: forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> b -> c
f b
x a
y              =  a -> b -> c
f a
y b
x










{-# INLINE ($) #-}
($) :: forall repa repb (a :: TYPE repa) (b :: TYPE repb). (a -> b) -> a -> b
$ :: forall a b. (a -> b) -> a -> b
($) a -> b
f = a -> b
f





($!) :: forall r a (b :: TYPE r). (a -> b) -> a -> b
{-# INLINE ($!) #-}
a -> b
f $! :: forall a b. (a -> b) -> a -> b
$! a
x = let !vx :: a
vx = a
x in a -> b
f a
vx  


until                   :: (a -> Bool) -> (a -> a) -> a -> a
until :: forall a. (a -> Bool) -> (a -> a) -> a -> a
until a -> Bool
p a -> a
f = a -> a
go
  where
    go :: a -> a
go a
x | a -> Bool
p a
x          = a
x
         | Bool
otherwise    = a -> a
go (a -> a
f a
x)




asTypeOf                :: a -> a -> a
asTypeOf :: forall a. a -> a -> a
asTypeOf                =  a -> a -> a
forall a b. a -> b -> a
const






instance  Functor IO where
   fmap :: forall a b. (a -> b) -> IO a -> IO b
fmap a -> b
f IO a
x = IO a
x IO a -> (a -> IO b) -> IO b
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (b -> IO b
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> IO b) -> (a -> b) -> a -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f)


instance Applicative IO where
    {-# INLINE pure #-}
    {-# INLINE (*>) #-}
    {-# INLINE liftA2 #-}
    pure :: forall a. a -> IO a
pure  = a -> IO a
forall a. a -> IO a
returnIO
    *> :: forall a b. IO a -> IO b -> IO b
(*>)  = IO a -> IO b -> IO b
forall a b. IO a -> IO b -> IO b
thenIO
    <*> :: forall a b. IO (a -> b) -> IO a -> IO b
(<*>) = IO (a -> b) -> IO a -> IO b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
    liftA2 :: forall a b c. (a -> b -> c) -> IO a -> IO b -> IO c
liftA2 = (a -> b -> c) -> IO a -> IO b -> IO c
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2


instance  Monad IO  where
    {-# INLINE (>>)   #-}
    {-# INLINE (>>=)  #-}
    >> :: forall a b. IO a -> IO b -> IO b
(>>)      = IO a -> IO b -> IO b
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)
    >>= :: forall a b. IO a -> (a -> IO b) -> IO b
(>>=)     = IO a -> (a -> IO b) -> IO b
forall a b. IO a -> (a -> IO b) -> IO b
bindIO





instance Alternative IO where
    empty :: forall a. IO a
empty = [Char] -> IO a
forall a. [Char] -> IO a
failIO [Char]
"mzero"
    <|> :: forall a. IO a -> IO a -> IO a
(<|>) = IO a -> IO a -> IO a
forall a. IO a -> IO a -> IO a
mplusIO





instance MonadPlus IO

returnIO :: a -> IO a
returnIO :: forall a. a -> IO a
returnIO a
x = (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\ State# RealWorld
s -> (# State# RealWorld
s, a
x #))

bindIO :: IO a -> (a -> IO b) -> IO b
bindIO :: forall a b. IO a -> (a -> IO b) -> IO b
bindIO (IO State# RealWorld -> (# State# RealWorld, a #)
m) a -> IO b
k = (State# RealWorld -> (# State# RealWorld, b #)) -> IO b
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\ State# RealWorld
s -> case State# RealWorld -> (# State# RealWorld, a #)
m State# RealWorld
s of (# State# RealWorld
new_s, a
a #) -> IO b -> State# RealWorld -> (# State# RealWorld, b #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (a -> IO b
k a
a) State# RealWorld
new_s)

thenIO :: IO a -> IO b -> IO b
thenIO :: forall a b. IO a -> IO b -> IO b
thenIO (IO State# RealWorld -> (# State# RealWorld, a #)
m) IO b
k = (State# RealWorld -> (# State# RealWorld, b #)) -> IO b
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\ State# RealWorld
s -> case State# RealWorld -> (# State# RealWorld, a #)
m State# RealWorld
s of (# State# RealWorld
new_s, a
_ #) -> IO b -> State# RealWorld -> (# State# RealWorld, b #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO IO b
k State# RealWorld
new_s)





failIO :: String -> IO a
failIO :: forall a. [Char] -> IO a
failIO [Char]
s = (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (SomeException -> State# RealWorld -> (# State# RealWorld, a #)
forall a b. a -> State# RealWorld -> (# State# RealWorld, b #)
raiseIO# ([Char] -> SomeException
mkUserError [Char]
s))

unIO :: IO a -> (State# RealWorld -> (# State# RealWorld, a #))
unIO :: forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (IO State# RealWorld -> (# State# RealWorld, a #)
a) = State# RealWorld -> (# State# RealWorld, a #)
a


{-# INLINE getTag #-}
getTag :: forall {lev :: Levity} (a :: TYPE (BoxedRep lev))
       .  DataToTag a => a -> Int#
getTag :: forall a. DataToTag a => a -> Int#
getTag = a -> Int#
forall a. DataToTag a => a -> Int#
dataToTag#









{-# INLINE quotInt #-}
{-# INLINE remInt #-}
{-# INLINE divInt #-}
{-# INLINE modInt #-}
{-# INLINE quotRemInt #-}
{-# INLINE divModInt #-}










quotInt :: Int -> Int -> Int
(I# Int#
x) quotInt :: Int -> Int -> Int
`quotInt`  (I# Int#
y) = Int# -> Int
I# (Int#
x Int# -> Int# -> Int#
`quotInt#` Int#
y)











remInt  :: Int -> Int -> Int
(I# Int#
x) remInt :: Int -> Int -> Int
`remInt`   (I# Int#
y) = Int# -> Int
I# (Int#
x Int# -> Int# -> Int#
`remInt#`  Int#
y)









divInt  :: Int -> Int -> Int
(I# Int#
x) divInt :: Int -> Int -> Int
`divInt`   (I# Int#
y) = Int# -> Int
I# (Int#
x Int# -> Int# -> Int#
`divInt#`  Int#
y)











modInt  :: Int -> Int -> Int
(I# Int#
x) modInt :: Int -> Int -> Int
`modInt`   (I# Int#
y) = Int# -> Int
I# (Int#
x Int# -> Int# -> Int#
`modInt#`  Int#
y)













quotRemInt :: Int -> Int -> (Int, Int)
(I# Int#
x) quotRemInt :: Int -> Int -> (Int, Int)
`quotRemInt` (I# Int#
y) = case Int#
x Int# -> Int# -> (# Int#, Int# #)
`quotRemInt#` Int#
y of
                             (# Int#
q, Int#
r #) ->
                                 (Int# -> Int
I# Int#
q, Int# -> Int
I# Int#
r)












divModInt :: Int -> Int -> (Int, Int)
(I# Int#
x) divModInt :: Int -> Int -> (Int, Int)
`divModInt` (I# Int#
y) = case Int#
x Int# -> Int# -> (# Int#, Int# #)
`divModInt#` Int#
y of
                            (# Int#
q, Int#
r #) -> (Int# -> Int
I# Int#
q, Int# -> Int
I# Int#
r)




















shift_mask :: Int# -> Int# -> Int#
{-# INLINE shift_mask #-}
shift_mask :: Int# -> Int# -> Int#
shift_mask Int#
m Int#
b = Int# -> Int#
negateInt# (Int#
b Int# -> Int# -> Int#
<# Int#
m)



shiftL# :: Word# -> Int# -> Word#
Word#
a shiftL# :: Word# -> Int# -> Word#
`shiftL#` Int#
b = (Word#
a Word# -> Int# -> Word#
`uncheckedShiftL#` Int#
b) Word# -> Word# -> Word#
`and#` Int# -> Word#
int2Word# (Int# -> Int# -> Int#
shift_mask WORD_SIZE_IN_BITS# b)





shiftRL# :: Word# -> Int# -> Word#
Word#
a shiftRL# :: Word# -> Int# -> Word#
`shiftRL#` Int#
b = (Word#
a Word# -> Int# -> Word#
`uncheckedShiftRL#` Int#
b) Word# -> Word# -> Word#
`and#` Int# -> Word#
int2Word# (Int# -> Int# -> Int#
shift_mask WORD_SIZE_IN_BITS# b)



iShiftL# :: Int# -> Int# -> Int#
Int#
a iShiftL# :: Int# -> Int# -> Int#
`iShiftL#` Int#
b = (Int#
a Int# -> Int# -> Int#
`uncheckedIShiftL#` Int#
b) Int# -> Int# -> Int#
`andI#` Int# -> Int# -> Int#
shift_mask WORD_SIZE_IN_BITS# b




iShiftRA# :: Int# -> Int# -> Int#
Int#
a iShiftRA# :: Int# -> Int# -> Int#
`iShiftRA#` Int#
b | Int# -> Bool
isTrue# (Int#
b Int# -> Int# -> Int#
>=# WORD_SIZE_IN_BITS#) = negateInt# (a <# 0#)
                | Bool
otherwise                          = Int#
a Int# -> Int# -> Int#
`uncheckedIShiftRA#` Int#
b




iShiftRL# :: Int# -> Int# -> Int#
Int#
a iShiftRL# :: Int# -> Int# -> Int#
`iShiftRL#` Int#
b = (Int#
a Int# -> Int# -> Int#
`uncheckedIShiftRL#` Int#
b) Int# -> Int# -> Int#
`andI#` Int# -> Int# -> Int#
shift_mask WORD_SIZE_IN_BITS# 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
"unpack-append-nil" forall a   . unpackAppendCString# a []    = unpackCString# a

"unpack-utf8"       [~1] forall a   . unpackCStringUtf8# a             = build (unpackFoldrCStringUtf8# a)
"unpack-list-utf8"  [1]  forall a   . unpackFoldrCStringUtf8# a (:) [] = unpackCStringUtf8# a
"unpack-append-utf8"     forall a n . unpackFoldrCStringUtf8# a (:) n  = unpackAppendCStringUtf8# a n
"unpack-append-nil-utf8" forall a   . unpackAppendCStringUtf8# a []    = unpackCStringUtf8# a

-- There's a built-in rule (in GHC.Core.Op.ConstantFold) for
--      unpackFoldr "foo" c (unpackFoldr "baz" c n)  =  unpackFoldr "foobaz" c n

-- See also the Note [String literals in GHC] in CString.hs

  #-}

RetroSearch is an open source project built by @garambo | Open a GitHub Issue

Search and Browse the WWW like it's 1997 | Search results from DuckDuckGo

HTML: 3.2 | Encoding: UTF-8 | Version: 0.7.4