Movatterモバイル変換
[0]ホーム
{-# LANGUAGE BangPatterns #-}{-# LANGUAGE CPP #-}{-# LANGUAGE MagicHash #-}{-# LANGUAGE NoImplicitPrelude #-}{-# LANGUAGE StandaloneDeriving #-}{-# LANGUAGE Trustworthy #-}{-# OPTIONS_HADDOCK not-home #-}------------------------------------------------------------------------------- |-- Module : GHC.Enum-- Copyright : (c) The University of Glasgow, 1992-2002-- License : see libraries/base/LICENSE---- Maintainer : cvs-ghc@haskell.org-- Stability : internal-- Portability : non-portable (GHC extensions)---- The 'Enum' and 'Bounded' classes.-------------------------------------------------------------------------------#include "MachDeps.h"moduleGHC.Enum(Bounded(..),Enum(..),boundedEnumFrom,boundedEnumFromThen,toEnumError,fromEnumError,succError,predError,-- Instances for Bounded and Enum: (), Char, Int)whereimportGHC.Basehiding(many)importGHC.CharimportGHC.Num.IntegerimportGHC.NumimportGHC.ShowimportGHC.Tuple(Solo(..))default()-- Double isn't available yet-- | The 'Bounded' class is used to name the upper and lower limits of a-- type. 'Ord' is not a superclass of 'Bounded' since types that are not-- totally ordered may also have upper and lower bounds.---- The 'Bounded' class may be derived for any enumeration type;-- 'minBound' is the first constructor listed in the @data@ declaration-- and 'maxBound' is the last.-- 'Bounded' may also be derived for single-constructor datatypes whose-- constituent types are in 'Bounded'.classBoundedawhereminBound,maxBound::a-- | Class 'Enum' defines operations on sequentially ordered types.---- The @enumFrom@... methods are used in Haskell's translation of-- arithmetic sequences.---- Instances of 'Enum' may be derived for any enumeration type (types-- whose constructors have no fields). The nullary constructors are-- assumed to be numbered left-to-right by 'fromEnum' from @0@ through @n-1@.-- See Chapter 10 of the /Haskell Report/ for more details.---- For any type that is an instance of class 'Bounded' as well as 'Enum',-- the following should hold:---- * The calls @'succ' 'maxBound'@ and @'pred' 'minBound'@ should result in-- a runtime error.---- * 'fromEnum' and 'toEnum' should give a runtime error if the-- result value is not representable in the result type.-- For example, @'toEnum' 7 :: 'Bool'@ is an error.---- * 'enumFrom' and 'enumFromThen' should be defined with an implicit bound,-- thus:---- > enumFrom x = enumFromTo x maxBound-- > enumFromThen x y = enumFromThenTo x y bound-- > where-- > bound | fromEnum y >= fromEnum x = maxBound-- > | otherwise = minBound--classEnumawhere-- | the successor of a value. For numeric types, 'succ' adds 1.succ::a->a-- | the predecessor of a value. For numeric types, 'pred' subtracts 1.pred::a->a-- | Convert from an 'Int'.toEnum::Int->a-- | Convert to an 'Int'.-- It is implementation-dependent what 'fromEnum' returns when-- applied to a value that is too large to fit in an 'Int'.fromEnum::a->Int-- | Used in Haskell's translation of @[n..]@ with @[n..] = enumFrom n@,-- a possible implementation being @enumFrom n = n : enumFrom (succ n)@.-- For example:---- * @enumFrom 4 :: [Integer] = [4,5,6,7,...]@-- * @enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: Int]@enumFrom::a->[a]-- | Used in Haskell's translation of @[n,n'..]@-- with @[n,n'..] = enumFromThen n n'@, a possible implementation being-- @enumFromThen n n' = n : n' : worker (f x) (f x n')@,-- @worker s v = v : worker s (s v)@, @x = fromEnum n' - fromEnum n@ and-- @f n y-- | n > 0 = f (n - 1) (succ y)-- | n < 0 = f (n + 1) (pred y)-- | otherwise = y@-- For example:---- * @enumFromThen 4 6 :: [Integer] = [4,6,8,10...]@-- * @enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: Int]@enumFromThen::a->a->[a]-- | Used in Haskell's translation of @[n..m]@ with-- @[n..m] = enumFromTo n m@, a possible implementation being-- @enumFromTo n m-- | n <= m = n : enumFromTo (succ n) m-- | otherwise = []@.-- For example:---- * @enumFromTo 6 10 :: [Int] = [6,7,8,9,10]@-- * @enumFromTo 42 1 :: [Integer] = []@enumFromTo::a->a->[a]-- | Used in Haskell's translation of @[n,n'..m]@ with-- @[n,n'..m] = enumFromThenTo n n' m@, a possible implementation-- being @enumFromThenTo n n' m = worker (f x) (c x) n m@,-- @x = fromEnum n' - fromEnum n@, @c x = bool (>=) (<=) (x > 0)@-- @f n y-- | n > 0 = f (n - 1) (succ y)-- | n < 0 = f (n + 1) (pred y)-- | otherwise = y@ and-- @worker s c v m-- | c v m = v : worker s c (s v) m-- | otherwise = []@-- For example:---- * @enumFromThenTo 4 2 -6 :: [Integer] = [4,2,0,-2,-4,-6]@-- * @enumFromThenTo 6 8 2 :: [Int] = []@enumFromThenTo::a->a->a->[a]succ=Int -> aforall a. Enum a => Int -> atoEnum(Int -> a) -> (a -> Int) -> a -> aforall b c a. (b -> c) -> (a -> b) -> a -> c.(Int -> Int -> Intforall a. Num a => a -> a -> a+Int1)(Int -> Int) -> (a -> Int) -> a -> Intforall b c a. (b -> c) -> (a -> b) -> a -> c.a -> Intforall a. Enum a => a -> IntfromEnumpred=Int -> aforall a. Enum a => Int -> atoEnum(Int -> a) -> (a -> Int) -> a -> aforall b c a. (b -> c) -> (a -> b) -> a -> c.(Int -> Int -> Intforall a. Num a => a -> a -> asubtractInt1)(Int -> Int) -> (a -> Int) -> a -> Intforall b c a. (b -> c) -> (a -> b) -> a -> c.a -> Intforall a. Enum a => a -> IntfromEnum-- See Note [Stable Unfolding for list producers]{-# INLINABLEenumFrom#-}enumFromax=(Int -> a) -> [Int] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInt -> aforall a. Enum a => Int -> atoEnum[a -> Intforall a. Enum a => a -> IntfromEnumax..]-- See Note [Stable Unfolding for list producers]{-# INLINABLEenumFromThen#-}enumFromThenaxay=(Int -> a) -> [Int] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInt -> aforall a. Enum a => Int -> atoEnum[a -> Intforall a. Enum a => a -> IntfromEnumax,a -> Intforall a. Enum a => a -> IntfromEnumay..]-- See Note [Stable Unfolding for list producers]{-# INLINABLEenumFromTo#-}enumFromToaxay=(Int -> a) -> [Int] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInt -> aforall a. Enum a => Int -> atoEnum[a -> Intforall a. Enum a => a -> IntfromEnumax..a -> Intforall a. Enum a => a -> IntfromEnumay]-- See Note [Stable Unfolding for list producers]{-# INLINABLEenumFromThenTo#-}enumFromThenToax1ax2ay=(Int -> a) -> [Int] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInt -> aforall a. Enum a => Int -> atoEnum[a -> Intforall a. Enum a => a -> IntfromEnumax1,a -> Intforall a. Enum a => a -> IntfromEnumax2..a -> Intforall a. Enum a => a -> IntfromEnumay]-- See Note [Inline Enum method helpers]{-# INLINEboundedEnumFrom#-}-- Default methods for bounded enumerationsboundedEnumFrom::(Enuma,Boundeda)=>a->[a]boundedEnumFrom :: forall a. (Enum a, Bounded a) => a -> [a]boundedEnumFroman=(Int -> a) -> [Int] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInt -> aforall a. Enum a => Int -> atoEnum[a -> Intforall a. Enum a => a -> IntfromEnuman..a -> Intforall a. Enum a => a -> IntfromEnum(aforall a. Bounded a => amaxBounda -> a -> aforall a. a -> a -> a`asTypeOf`an)]-- See Note [Inline Enum method helpers]{-# INLINEboundedEnumFromThen#-}boundedEnumFromThen::(Enuma,Boundeda)=>a->a->[a]boundedEnumFromThen :: forall a. (Enum a, Bounded a) => a -> a -> [a]boundedEnumFromThenan1an2|Inti_n2Int -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Inti_n1=(Int -> a) -> [Int] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInt -> aforall a. Enum a => Int -> atoEnum[Inti_n1,Inti_n2..a -> Intforall a. Enum a => a -> IntfromEnum(aforall a. Bounded a => amaxBounda -> a -> aforall a. a -> a -> a`asTypeOf`an1)]|Boolotherwise=(Int -> a) -> [Int] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInt -> aforall a. Enum a => Int -> atoEnum[Inti_n1,Inti_n2..a -> Intforall a. Enum a => a -> IntfromEnum(aforall a. Bounded a => aminBounda -> a -> aforall a. a -> a -> a`asTypeOf`an1)]wherei_n1 :: Inti_n1=a -> Intforall a. Enum a => a -> IntfromEnuman1i_n2 :: Inti_n2=a -> Intforall a. Enum a => a -> IntfromEnuman2{- Note [Stable Unfolding for list producers]~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~The INLINABLE/INLINE pragmas ensure that we export stable (unoptimised)unfoldings in the interface file so we can do list fusion at usage sites.Related tickets: #15185, #8763, #18178.Note [Inline Enum method helpers]~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~The overloaded `numericEnumFrom` functions are used to abbreviate Enuminstances. We call them "method helpers". For example, in GHC.Float: numericEnumFromTo :: (Ord a, Fractional a) => a -> a -> [a] mnumericEnumFromTo = ...blah... instance Enum Double where ... enumFromTo = numericEnumFromToSimilarly with the overloaded `boundedEnumFrom` functions. E.g. in GHC.Word boundedEnumFrom :: (Enum a, Bounded a) => a -> [a] boundedEnumFrom n = map toEnum [fromEnum n .. fromEnum (maxBound `asTypeOf` n)] instance Enum Word8 where ... enumFrom = boundedEnumFromIn both cases, it is super-important to specialise these overloadedhelper function (`numericEnumFromTo`, `boundedEnumFrom` etc) to theparticular type of the instance, else every use of that instance willbe inefficient.Moreover (see Note [Stable Unfolding for list producers]) the helperfunction is a list producer, so we want it to have a stable unfoldingto support fusion.So we attach an INLINE pragma to them.Alternatives might be* An `INLINABLE` pragma on `numericEnumFromTo`, relying on the specialiser to create a specialised version. But (a) if the instance method is marked INLINE we may get spurious INLINE loop-breaker warnings (#21343), and (b) specialision gains no extra sharing, because there is just one call at each type.* Using `inline` at the call site enumFromTo = inline numericEnumFromTo But that means remembering to do this in multiple places.-}-------------------------------------------------------------------------- Helper functions------------------------------------------------------------------------{-# NOINLINEtoEnumError#-}toEnumError::(Showa)=>String->Int->(a,a)->btoEnumError :: forall a b. Show a => String -> Int -> (a, a) -> btoEnumErrorStringinst_tyInti(a, a)bnds=String -> bforall a. String -> aerrorWithoutStackTrace(String -> b) -> String -> bforall a b. (a -> b) -> a -> b$String"Enum.toEnum{"String -> String -> Stringforall a. [a] -> [a] -> [a]++Stringinst_tyString -> String -> Stringforall a. [a] -> [a] -> [a]++String"}: tag ("String -> String -> Stringforall a. [a] -> [a] -> [a]++Int -> Stringforall a. Show a => a -> StringshowIntiString -> String -> Stringforall a. [a] -> [a] -> [a]++String") is outside of bounds "String -> String -> Stringforall a. [a] -> [a] -> [a]++(a, a) -> Stringforall a. Show a => a -> Stringshow(a, a)bnds{-# NOINLINEfromEnumError#-}fromEnumError::(Showa)=>String->a->bfromEnumError :: forall a b. Show a => String -> a -> bfromEnumErrorStringinst_tyax=String -> bforall a. String -> aerrorWithoutStackTrace(String -> b) -> String -> bforall a b. (a -> b) -> a -> b$String"Enum.fromEnum{"String -> String -> Stringforall a. [a] -> [a] -> [a]++Stringinst_tyString -> String -> Stringforall a. [a] -> [a] -> [a]++String"}: value ("String -> String -> Stringforall a. [a] -> [a] -> [a]++a -> Stringforall a. Show a => a -> StringshowaxString -> String -> Stringforall a. [a] -> [a] -> [a]++String") is outside of Int's bounds "String -> String -> Stringforall a. [a] -> [a] -> [a]++(Int, Int) -> Stringforall a. Show a => a -> Stringshow(Intforall a. Bounded a => aminBound::Int,Intforall a. Bounded a => amaxBound::Int){-# NOINLINEsuccError#-}succError::String->asuccError :: forall a. String -> asuccErrorStringinst_ty=String -> aforall a. String -> aerrorWithoutStackTrace(String -> a) -> String -> aforall a b. (a -> b) -> a -> b$String"Enum.succ{"String -> String -> Stringforall a. [a] -> [a] -> [a]++Stringinst_tyString -> String -> Stringforall a. [a] -> [a] -> [a]++String"}: tried to take `succ' of maxBound"{-# NOINLINEpredError#-}predError::String->apredError :: forall a. String -> apredErrorStringinst_ty=String -> aforall a. String -> aerrorWithoutStackTrace(String -> a) -> String -> aforall a b. (a -> b) -> a -> b$String"Enum.pred{"String -> String -> Stringforall a. [a] -> [a] -> [a]++Stringinst_tyString -> String -> Stringforall a. [a] -> [a] -> [a]++String"}: tried to take `pred' of minBound"-------------------------------------------------------------------------- Tuples-------------------------------------------------------------------------- | @since 2.01derivinginstanceBounded()-- | @since 2.01instanceEnum()wheresucc :: () -> ()succ()_=String -> ()forall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.().succ: bad argument"pred :: () -> ()pred()_=String -> ()forall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.().pred: bad argument"toEnum :: Int -> ()toEnumIntx|IntxInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int0=()|Boolotherwise=String -> ()forall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.().toEnum: bad argument"fromEnum :: () -> IntfromEnum()=Int0enumFrom :: () -> [()]enumFrom()=[()]enumFromThen :: () -> () -> [()]enumFromThen()()=letmany :: [()]many=()() -> [()] -> [()]forall a. a -> [a] -> [a]:[()]manyin[()]manyenumFromTo :: () -> () -> [()]enumFromTo()()=[()]enumFromThenTo :: () -> () -> () -> [()]enumFromThenTo()()()=letmany :: [()]many=()() -> [()] -> [()]forall a. a -> [a] -> [a]:[()]manyin[()]manyinstanceEnuma=>Enum(Soloa)wheresucc :: Solo a -> Solo asucc(MkSoloaa)=a -> Solo aforall a. a -> Solo aMkSolo(a -> aforall a. Enum a => a -> asuccaa)pred :: Solo a -> Solo apred(MkSoloaa)=a -> Solo aforall a. a -> Solo aMkSolo(a -> aforall a. Enum a => a -> apredaa)toEnum :: Int -> Solo atoEnumIntx=a -> Solo aforall a. a -> Solo aMkSolo(Int -> aforall a. Enum a => Int -> atoEnumIntx)fromEnum :: Solo a -> IntfromEnum(MkSoloax)=a -> Intforall a. Enum a => a -> IntfromEnumaxenumFrom :: Solo a -> [Solo a]enumFrom(MkSoloax)=[a -> Solo aforall a. a -> Solo aMkSoloaa|aa<-a -> [a]forall a. Enum a => a -> [a]enumFromax]enumFromThen :: Solo a -> Solo a -> [Solo a]enumFromThen(MkSoloax)(MkSoloay)=[a -> Solo aforall a. a -> Solo aMkSoloaa|aa<-a -> a -> [a]forall a. Enum a => a -> a -> [a]enumFromThenaxay]enumFromTo :: Solo a -> Solo a -> [Solo a]enumFromTo(MkSoloax)(MkSoloay)=[a -> Solo aforall a. a -> Solo aMkSoloaa|aa<-a -> a -> [a]forall a. Enum a => a -> a -> [a]enumFromToaxay]enumFromThenTo :: Solo a -> Solo a -> Solo a -> [Solo a]enumFromThenTo(MkSoloax)(MkSoloay)(MkSoloaz)=[a -> Solo aforall a. a -> Solo aMkSoloaa|aa<-a -> a -> a -> [a]forall a. Enum a => a -> a -> a -> [a]enumFromThenToaxayaz]derivinginstanceBoundeda=>Bounded(Soloa)-- Report requires instances up to 15-- | @since 2.01derivinginstance(Boundeda,Boundedb)=>Bounded(a,b)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc)=>Bounded(a,b,c)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd)=>Bounded(a,b,c,d)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede)=>Bounded(a,b,c,d,e)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede,Boundedf)=>Bounded(a,b,c,d,e,f)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede,Boundedf,Boundedg)=>Bounded(a,b,c,d,e,f,g)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede,Boundedf,Boundedg,Boundedh)=>Bounded(a,b,c,d,e,f,g,h)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede,Boundedf,Boundedg,Boundedh,Boundedi)=>Bounded(a,b,c,d,e,f,g,h,i)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede,Boundedf,Boundedg,Boundedh,Boundedi,Boundedj)=>Bounded(a,b,c,d,e,f,g,h,i,j)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede,Boundedf,Boundedg,Boundedh,Boundedi,Boundedj,Boundedk)=>Bounded(a,b,c,d,e,f,g,h,i,j,k)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede,Boundedf,Boundedg,Boundedh,Boundedi,Boundedj,Boundedk,Boundedl)=>Bounded(a,b,c,d,e,f,g,h,i,j,k,l)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede,Boundedf,Boundedg,Boundedh,Boundedi,Boundedj,Boundedk,Boundedl,Boundedm)=>Bounded(a,b,c,d,e,f,g,h,i,j,k,l,m)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede,Boundedf,Boundedg,Boundedh,Boundedi,Boundedj,Boundedk,Boundedl,Boundedm,Boundedn)=>Bounded(a,b,c,d,e,f,g,h,i,j,k,l,m,n)-- | @since 2.01derivinginstance(Boundeda,Boundedb,Boundedc,Boundedd,Boundede,Boundedf,Boundedg,Boundedh,Boundedi,Boundedj,Boundedk,Boundedl,Boundedm,Boundedn,Boundedo)=>Bounded(a,b,c,d,e,f,g,h,i,j,k,l,m,n,o)-------------------------------------------------------------------------- Bool-------------------------------------------------------------------------- | @since 2.01derivinginstanceBoundedBool-- | @since 2.01instanceEnumBoolwheresucc :: Bool -> BoolsuccBoolFalse=BoolTruesuccBoolTrue=String -> Boolforall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.Bool.succ: bad argument"pred :: Bool -> BoolpredBoolTrue=BoolFalsepredBoolFalse=String -> Boolforall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.Bool.pred: bad argument"toEnum :: Int -> BooltoEnumIntn|IntnInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int0=BoolFalse|IntnInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int1=BoolTrue|Boolotherwise=String -> Boolforall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.Bool.toEnum: bad argument"fromEnum :: Bool -> IntfromEnumBoolFalse=Int0fromEnumBoolTrue=Int1-- Use defaults for the restenumFrom :: Bool -> [Bool]enumFrom=Bool -> [Bool]forall a. (Enum a, Bounded a) => a -> [a]boundedEnumFromenumFromThen :: Bool -> Bool -> [Bool]enumFromThen=Bool -> Bool -> [Bool]forall a. (Enum a, Bounded a) => a -> a -> [a]boundedEnumFromThen-------------------------------------------------------------------------- Ordering-------------------------------------------------------------------------- | @since 2.01derivinginstanceBoundedOrdering-- | @since 2.01instanceEnumOrderingwheresucc :: Ordering -> OrderingsuccOrderingLT=OrderingEQsuccOrderingEQ=OrderingGTsuccOrderingGT=String -> Orderingforall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.Ordering.succ: bad argument"pred :: Ordering -> OrderingpredOrderingGT=OrderingEQpredOrderingEQ=OrderingLTpredOrderingLT=String -> Orderingforall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.Ordering.pred: bad argument"toEnum :: Int -> OrderingtoEnumIntn|IntnInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int0=OrderingLT|IntnInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int1=OrderingEQ|IntnInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int2=OrderingGTtoEnumInt_=String -> Orderingforall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.Ordering.toEnum: bad argument"fromEnum :: Ordering -> IntfromEnumOrderingLT=Int0fromEnumOrderingEQ=Int1fromEnumOrderingGT=Int2-- Use defaults for the restenumFrom :: Ordering -> [Ordering]enumFrom=Ordering -> [Ordering]forall a. (Enum a, Bounded a) => a -> [a]boundedEnumFromenumFromThen :: Ordering -> Ordering -> [Ordering]enumFromThen=Ordering -> Ordering -> [Ordering]forall a. (Enum a, Bounded a) => a -> a -> [a]boundedEnumFromThen-------------------------------------------------------------------------- Char-------------------------------------------------------------------------- | @since 2.01instanceBoundedCharwhereminBound :: CharminBound=Char'\0'maxBound :: CharmaxBound=Char'\x10FFFF'-- | @since 2.01instanceEnumCharwheresucc :: Char -> Charsucc(C#Char#c#)|Int# -> BoolisTrue#(Char# -> Int#ord#Char#c#Int# -> Int# -> Int#/=#Int#0x10FFFF#)=Char# -> CharC#(Int# -> Char#chr#(Char# -> Int#ord#Char#c#Int# -> Int# -> Int#+#Int#1#))|Boolotherwise=String -> Charforall a. String -> aerrorWithoutStackTrace(String"Prelude.Enum.Char.succ: bad argument")pred :: Char -> Charpred(C#Char#c#)|Int# -> BoolisTrue#(Char# -> Int#ord#Char#c#Int# -> Int# -> Int#/=#Int#0#)=Char# -> CharC#(Int# -> Char#chr#(Char# -> Int#ord#Char#c#Int# -> Int# -> Int#-#Int#1#))|Boolotherwise=String -> Charforall a. String -> aerrorWithoutStackTrace(String"Prelude.Enum.Char.pred: bad argument")toEnum :: Int -> ChartoEnum=Int -> CharchrfromEnum :: Char -> IntfromEnum=Char -> Intord-- See Note [Stable Unfolding for list producers]{-# INLINEenumFrom#-}enumFrom :: Char -> StringenumFrom(C#Char#x)=Int# -> Int# -> StringeftChar(Char# -> Int#ord#Char#x)Int#0x10FFFF#-- Blarg: technically I guess enumFrom isn't strict!-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromTo#-}enumFromTo :: Char -> Char -> StringenumFromTo(C#Char#x)(C#Char#y)=Int# -> Int# -> StringeftChar(Char# -> Int#ord#Char#x)(Char# -> Int#ord#Char#y)-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromThen#-}enumFromThen :: Char -> Char -> StringenumFromThen(C#Char#x1)(C#Char#x2)=Int# -> Int# -> StringefdChar(Char# -> Int#ord#Char#x1)(Char# -> Int#ord#Char#x2)-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromThenTo#-}enumFromThenTo :: Char -> Char -> Char -> StringenumFromThenTo(C#Char#x1)(C#Char#x2)(C#Char#y)=Int# -> Int# -> Int# -> StringefdtChar(Char# -> Int#ord#Char#x1)(Char# -> Int#ord#Char#x2)(Char# -> Int#ord#Char#y)-- See Note [How the Enum rules work]{-# RULES"eftChar"[~1]forallxy.eftCharxy=build(\cn->eftCharFBcnxy)"efdChar"[~1]forallx1x2.efdCharx1x2=build(\cn->efdCharFBcnx1x2)"efdtChar"[~1]forallx1x2l.efdtCharx1x2l=build(\cn->efdtCharFBcnx1x2l)"eftCharList"[1]eftCharFB(:)[]=eftChar"efdCharList"[1]efdCharFB(:)[]=efdChar"efdtCharList"[1]efdtCharFB(:)[]=efdtChar#-}-- We can do better than for Ints because we don't-- have hassles about arithmetic overflow at maxBound{-# INLINE[0]eftCharFB#-}-- See Note [Inline FB functions] in GHC.ListeftCharFB::(Char->a->a)->a->Int#->Int#->aeftCharFB :: forall a. (Char -> a -> a) -> a -> Int# -> Int# -> aeftCharFBChar -> a -> acanInt#x0Int#y=Int# -> agoInt#x0wherego :: Int# -> agoInt#x|Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#y)=an|Boolotherwise=Char# -> CharC#(Int# -> Char#chr#Int#x)Char -> a -> a`c`Int# -> ago(Int#xInt# -> Int# -> Int#+#Int#1#){-# NOINLINE[1]eftChar#-}-- Inline after rule "eftChar" is inactiveeftChar::Int#->Int#->StringeftChar :: Int# -> Int# -> StringeftCharInt#xInt#y|Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#y)=[]|Boolotherwise=Char# -> CharC#(Int# -> Char#chr#Int#x)Char -> String -> Stringforall a. a -> [a] -> [a]:Int# -> Int# -> StringeftChar(Int#xInt# -> Int# -> Int#+#Int#1#)Int#y-- For enumFromThenTo we give up on inlining{-# INLINE[0]efdCharFB#-}-- See Note [Inline FB functions] in GHC.ListefdCharFB::(Char->a->a)->a->Int#->Int#->aefdCharFB :: forall a. (Char -> a -> a) -> a -> Int# -> Int# -> aefdCharFBChar -> a -> acanInt#x1Int#x2|Int# -> BoolisTrue#(Int#deltaInt# -> Int# -> Int#>=#Int#0#)=(Char -> a -> a) -> a -> Int# -> Int# -> Int# -> aforall a. (Char -> a -> a) -> a -> Int# -> Int# -> Int# -> ago_up_char_fbChar -> a -> acanInt#x1Int#deltaInt#0x10FFFF#|Boolotherwise=(Char -> a -> a) -> a -> Int# -> Int# -> Int# -> aforall a. (Char -> a -> a) -> a -> Int# -> Int# -> Int# -> ago_dn_char_fbChar -> a -> acanInt#x1Int#deltaInt#0#where!delta :: Int#delta=Int#x2Int# -> Int# -> Int#-#Int#x1{-# NOINLINE[1]efdChar#-}-- Inline after rule "efdChar" is inactiveefdChar::Int#->Int#->StringefdChar :: Int# -> Int# -> StringefdCharInt#x1Int#x2|Int# -> BoolisTrue#(Int#deltaInt# -> Int# -> Int#>=#Int#0#)=Int# -> Int# -> Int# -> Stringgo_up_char_listInt#x1Int#deltaInt#0x10FFFF#|Boolotherwise=Int# -> Int# -> Int# -> Stringgo_dn_char_listInt#x1Int#deltaInt#0#where!delta :: Int#delta=Int#x2Int# -> Int# -> Int#-#Int#x1{-# INLINE[0]efdtCharFB#-}-- See Note [Inline FB functions] in GHC.ListefdtCharFB::(Char->a->a)->a->Int#->Int#->Int#->aefdtCharFB :: forall a. (Char -> a -> a) -> a -> Int# -> Int# -> Int# -> aefdtCharFBChar -> a -> acanInt#x1Int#x2Int#lim|Int# -> BoolisTrue#(Int#deltaInt# -> Int# -> Int#>=#Int#0#)=(Char -> a -> a) -> a -> Int# -> Int# -> Int# -> aforall a. (Char -> a -> a) -> a -> Int# -> Int# -> Int# -> ago_up_char_fbChar -> a -> acanInt#x1Int#deltaInt#lim|Boolotherwise=(Char -> a -> a) -> a -> Int# -> Int# -> Int# -> aforall a. (Char -> a -> a) -> a -> Int# -> Int# -> Int# -> ago_dn_char_fbChar -> a -> acanInt#x1Int#deltaInt#limwhere!delta :: Int#delta=Int#x2Int# -> Int# -> Int#-#Int#x1{-# NOINLINE[1]efdtChar#-}-- Inline after rule "efdtChar" is inactiveefdtChar::Int#->Int#->Int#->StringefdtChar :: Int# -> Int# -> Int# -> StringefdtCharInt#x1Int#x2Int#lim|Int# -> BoolisTrue#(Int#deltaInt# -> Int# -> Int#>=#Int#0#)=Int# -> Int# -> Int# -> Stringgo_up_char_listInt#x1Int#deltaInt#lim|Boolotherwise=Int# -> Int# -> Int# -> Stringgo_dn_char_listInt#x1Int#deltaInt#limwhere!delta :: Int#delta=Int#x2Int# -> Int# -> Int#-#Int#x1go_up_char_fb::(Char->a->a)->a->Int#->Int#->Int#->ago_up_char_fb :: forall a. (Char -> a -> a) -> a -> Int# -> Int# -> Int# -> ago_up_char_fbChar -> a -> acanInt#x0Int#deltaInt#lim=Int# -> ago_upInt#x0wherego_up :: Int# -> ago_upInt#x|Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#lim)=an|Boolotherwise=Char# -> CharC#(Int# -> Char#chr#Int#x)Char -> a -> a`c`Int# -> ago_up(Int#xInt# -> Int# -> Int#+#Int#delta)go_dn_char_fb::(Char->a->a)->a->Int#->Int#->Int#->ago_dn_char_fb :: forall a. (Char -> a -> a) -> a -> Int# -> Int# -> Int# -> ago_dn_char_fbChar -> a -> acanInt#x0Int#deltaInt#lim=Int# -> ago_dnInt#x0wherego_dn :: Int# -> ago_dnInt#x|Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<#Int#lim)=an|Boolotherwise=Char# -> CharC#(Int# -> Char#chr#Int#x)Char -> a -> a`c`Int# -> ago_dn(Int#xInt# -> Int# -> Int#+#Int#delta)go_up_char_list::Int#->Int#->Int#->Stringgo_up_char_list :: Int# -> Int# -> Int# -> Stringgo_up_char_listInt#x0Int#deltaInt#lim=Int# -> Stringgo_upInt#x0wherego_up :: Int# -> Stringgo_upInt#x|Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#lim)=[]|Boolotherwise=Char# -> CharC#(Int# -> Char#chr#Int#x)Char -> String -> Stringforall a. a -> [a] -> [a]:Int# -> Stringgo_up(Int#xInt# -> Int# -> Int#+#Int#delta)go_dn_char_list::Int#->Int#->Int#->Stringgo_dn_char_list :: Int# -> Int# -> Int# -> Stringgo_dn_char_listInt#x0Int#deltaInt#lim=Int# -> Stringgo_dnInt#x0wherego_dn :: Int# -> Stringgo_dnInt#x|Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<#Int#lim)=[]|Boolotherwise=Char# -> CharC#(Int# -> Char#chr#Int#x)Char -> String -> Stringforall a. a -> [a] -> [a]:Int# -> Stringgo_dn(Int#xInt# -> Int# -> Int#+#Int#delta)-------------------------------------------------------------------------- Int------------------------------------------------------------------------{-Be careful about these instances. (a) remember that you have to count down as well as up e.g. [13,12..0] (b) be careful of Int overflow (c) remember that Int is bounded, so [1..] terminates at maxInt-}-- | @since 2.01instanceBoundedIntwhereminBound :: IntminBound=IntminIntmaxBound :: IntmaxBound=IntmaxInt-- | @since 2.01instanceEnumIntwheresucc :: Int -> IntsuccIntx|IntxInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Intforall a. Bounded a => amaxBound=String -> Intforall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.succ{Int}: tried to take `succ' of maxBound"|Boolotherwise=IntxInt -> Int -> Intforall a. Num a => a -> a -> a+Int1pred :: Int -> IntpredIntx|IntxInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Intforall a. Bounded a => aminBound=String -> Intforall a. String -> aerrorWithoutStackTraceString"Prelude.Enum.pred{Int}: tried to take `pred' of minBound"|Boolotherwise=IntxInt -> Int -> Intforall a. Num a => a -> a -> a-Int1toEnum :: Int -> InttoEnumIntx=IntxfromEnum :: Int -> IntfromEnumIntx=Intx-- See Note [Stable Unfolding for list producers]{-# INLINEenumFrom#-}enumFrom :: Int -> [Int]enumFrom(I#Int#x)=Int# -> Int# -> [Int]eftIntInt#xInt#maxInt#where!(I#Int#maxInt#)=IntmaxInt-- Blarg: technically I guess enumFrom isn't strict!-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromTo#-}enumFromTo :: Int -> Int -> [Int]enumFromTo(I#Int#x)(I#Int#y)=Int# -> Int# -> [Int]eftIntInt#xInt#y-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromThen#-}enumFromThen :: Int -> Int -> [Int]enumFromThen(I#Int#x1)(I#Int#x2)=Int# -> Int# -> [Int]efdIntInt#x1Int#x2-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromThenTo#-}enumFromThenTo :: Int -> Int -> Int -> [Int]enumFromThenTo(I#Int#x1)(I#Int#x2)(I#Int#y)=Int# -> Int# -> Int# -> [Int]efdtIntInt#x1Int#x2Int#y------------------------------------------------------- eftInt and eftIntFB deal with [a..b], which is the-- most common form, so we take a lot of care-- In particular, we have rules for deforestation{-# RULES"eftInt"[~1]forallxy.eftIntxy=build(\cn->eftIntFBcnxy)"eftIntList"[1]eftIntFB(:)[]=eftInt#-}{- Note [How the Enum rules work]~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~* Phase 2: eftInt ---> build . eftIntFB* Phase 1: inline build; eftIntFB (:) --> eftInt* Phase 0: optionally inline eftInt-}{-# NOINLINE[1]eftInt#-}eftInt::Int#->Int#->[Int]-- [x1..x2]eftInt :: Int# -> Int# -> [Int]eftIntInt#x0Int#y|Int# -> BoolisTrue#(Int#x0Int# -> Int# -> Int#>#Int#y)=[]|Boolotherwise=Int# -> [Int]goInt#x0wherego :: Int# -> [Int]goInt#x=Int# -> IntI#Int#xInt -> [Int] -> [Int]forall a. a -> [a] -> [a]:ifInt# -> BoolisTrue#(Int#xInt# -> Int# -> Int#==#Int#y)then[]elseInt# -> [Int]go(Int#xInt# -> Int# -> Int#+#Int#1#){-# INLINE[0]eftIntFB#-}-- See Note [Inline FB functions] in GHC.ListeftIntFB::(Int->r->r)->r->Int#->Int#->reftIntFB :: forall r. (Int -> r -> r) -> r -> Int# -> Int# -> reftIntFBInt -> r -> rcrnInt#x0Int#y|Int# -> BoolisTrue#(Int#x0Int# -> Int# -> Int#>#Int#y)=rn|Boolotherwise=Int# -> rgoInt#x0wherego :: Int# -> rgoInt#x=Int# -> IntI#Int#xInt -> r -> r`c`ifInt# -> BoolisTrue#(Int#xInt# -> Int# -> Int#==#Int#y)thenrnelseInt# -> rgo(Int#xInt# -> Int# -> Int#+#Int#1#)-- Watch out for y=maxBound; hence ==, not >-- Be very careful not to have more than one "c"-- so that when eftInfFB is inlined we can inline-- whatever is bound to "c"------------------------------------------------------- efdInt and efdtInt deal with [a,b..] and [a,b..c].-- The code is more complicated because of worries about Int overflow.-- See Note [How the Enum rules work]{-# RULES"efdtInt"[~1]forallx1x2y.efdtIntx1x2y=build(\cn->efdtIntFBcnx1x2y)"efdtIntUpList"[1]efdtIntFB(:)[]=efdtInt#-}efdInt::Int#->Int#->[Int]-- [x1,x2..maxInt]efdInt :: Int# -> Int# -> [Int]efdIntInt#x1Int#x2|Int# -> BoolisTrue#(Int#x2Int# -> Int# -> Int#>=#Int#x1)=caseIntmaxIntofI#Int#y->Int# -> Int# -> Int# -> [Int]efdtIntUpInt#x1Int#x2Int#y|Boolotherwise=caseIntminIntofI#Int#y->Int# -> Int# -> Int# -> [Int]efdtIntDnInt#x1Int#x2Int#y{-# NOINLINE[1]efdtInt#-}efdtInt::Int#->Int#->Int#->[Int]-- [x1,x2..y]efdtInt :: Int# -> Int# -> Int# -> [Int]efdtIntInt#x1Int#x2Int#y|Int# -> BoolisTrue#(Int#x2Int# -> Int# -> Int#>=#Int#x1)=Int# -> Int# -> Int# -> [Int]efdtIntUpInt#x1Int#x2Int#y|Boolotherwise=Int# -> Int# -> Int# -> [Int]efdtIntDnInt#x1Int#x2Int#y{-# INLINE[0]efdtIntFB#-}-- See Note [Inline FB functions] in GHC.ListefdtIntFB::(Int->r->r)->r->Int#->Int#->Int#->refdtIntFB :: forall r. (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> refdtIntFBInt -> r -> rcrnInt#x1Int#x2Int#y|Int# -> BoolisTrue#(Int#x2Int# -> Int# -> Int#>=#Int#x1)=(Int -> r -> r) -> r -> Int# -> Int# -> Int# -> rforall r. (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> refdtIntUpFBInt -> r -> rcrnInt#x1Int#x2Int#y|Boolotherwise=(Int -> r -> r) -> r -> Int# -> Int# -> Int# -> rforall r. (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> refdtIntDnFBInt -> r -> rcrnInt#x1Int#x2Int#y-- Requires x2 >= x1efdtIntUp::Int#->Int#->Int#->[Int]efdtIntUp :: Int# -> Int# -> Int# -> [Int]efdtIntUpInt#x1Int#x2Int#y-- Be careful about overflow!|Int# -> BoolisTrue#(Int#yInt# -> Int# -> Int#<#Int#x2)=ifInt# -> BoolisTrue#(Int#yInt# -> Int# -> Int#<#Int#x1)then[]else[Int# -> IntI#Int#x1]|Boolotherwise=-- Common case: x1 <= x2 <= ylet!delta :: Int#delta=Int#x2Int# -> Int# -> Int#-#Int#x1-- >= 0!y' :: Int#y'=Int#yInt# -> Int# -> Int#-#Int#delta-- x1 <= y' <= y; hence y' is representable-- Invariant: x <= y-- Note that: z <= y' => z + delta won't overflow-- so we are guaranteed not to overflow if/when we recursego_up :: Int# -> [Int]go_upInt#x|Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#y')=[Int# -> IntI#Int#x]|Boolotherwise=Int# -> IntI#Int#xInt -> [Int] -> [Int]forall a. a -> [a] -> [a]:Int# -> [Int]go_up(Int#xInt# -> Int# -> Int#+#Int#delta)inInt# -> IntI#Int#x1Int -> [Int] -> [Int]forall a. a -> [a] -> [a]:Int# -> [Int]go_upInt#x2-- Requires x2 >= x1{-# INLINE[0]efdtIntUpFB#-}-- See Note [Inline FB functions] in GHC.ListefdtIntUpFB::(Int->r->r)->r->Int#->Int#->Int#->refdtIntUpFB :: forall r. (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> refdtIntUpFBInt -> r -> rcrnInt#x1Int#x2Int#y-- Be careful about overflow!|Int# -> BoolisTrue#(Int#yInt# -> Int# -> Int#<#Int#x2)=ifInt# -> BoolisTrue#(Int#yInt# -> Int# -> Int#<#Int#x1)thenrnelseInt# -> IntI#Int#x1Int -> r -> r`c`rn|Boolotherwise=-- Common case: x1 <= x2 <= ylet!delta :: Int#delta=Int#x2Int# -> Int# -> Int#-#Int#x1-- >= 0!y' :: Int#y'=Int#yInt# -> Int# -> Int#-#Int#delta-- x1 <= y' <= y; hence y' is representable-- Invariant: x <= y-- Note that: z <= y' => z + delta won't overflow-- so we are guaranteed not to overflow if/when we recursego_up :: Int# -> rgo_upInt#x|Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#y')=Int# -> IntI#Int#xInt -> r -> r`c`rn|Boolotherwise=Int# -> IntI#Int#xInt -> r -> r`c`Int# -> rgo_up(Int#xInt# -> Int# -> Int#+#Int#delta)inInt# -> IntI#Int#x1Int -> r -> r`c`Int# -> rgo_upInt#x2-- Requires x2 <= x1efdtIntDn::Int#->Int#->Int#->[Int]efdtIntDn :: Int# -> Int# -> Int# -> [Int]efdtIntDnInt#x1Int#x2Int#y-- Be careful about underflow!|Int# -> BoolisTrue#(Int#yInt# -> Int# -> Int#>#Int#x2)=ifInt# -> BoolisTrue#(Int#yInt# -> Int# -> Int#>#Int#x1)then[]else[Int# -> IntI#Int#x1]|Boolotherwise=-- Common case: x1 >= x2 >= ylet!delta :: Int#delta=Int#x2Int# -> Int# -> Int#-#Int#x1-- <= 0!y' :: Int#y'=Int#yInt# -> Int# -> Int#-#Int#delta-- y <= y' <= x1; hence y' is representable-- Invariant: x >= y-- Note that: z >= y' => z + delta won't underflow-- so we are guaranteed not to underflow if/when we recursego_dn :: Int# -> [Int]go_dnInt#x|Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<#Int#y')=[Int# -> IntI#Int#x]|Boolotherwise=Int# -> IntI#Int#xInt -> [Int] -> [Int]forall a. a -> [a] -> [a]:Int# -> [Int]go_dn(Int#xInt# -> Int# -> Int#+#Int#delta)inInt# -> IntI#Int#x1Int -> [Int] -> [Int]forall a. a -> [a] -> [a]:Int# -> [Int]go_dnInt#x2-- Requires x2 <= x1{-# INLINE[0]efdtIntDnFB#-}-- See Note [Inline FB functions] in GHC.ListefdtIntDnFB::(Int->r->r)->r->Int#->Int#->Int#->refdtIntDnFB :: forall r. (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> refdtIntDnFBInt -> r -> rcrnInt#x1Int#x2Int#y-- Be careful about underflow!|Int# -> BoolisTrue#(Int#yInt# -> Int# -> Int#>#Int#x2)=ifInt# -> BoolisTrue#(Int#yInt# -> Int# -> Int#>#Int#x1)thenrnelseInt# -> IntI#Int#x1Int -> r -> r`c`rn|Boolotherwise=-- Common case: x1 >= x2 >= ylet!delta :: Int#delta=Int#x2Int# -> Int# -> Int#-#Int#x1-- <= 0!y' :: Int#y'=Int#yInt# -> Int# -> Int#-#Int#delta-- y <= y' <= x1; hence y' is representable-- Invariant: x >= y-- Note that: z >= y' => z + delta won't underflow-- so we are guaranteed not to underflow if/when we recursego_dn :: Int# -> rgo_dnInt#x|Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<#Int#y')=Int# -> IntI#Int#xInt -> r -> r`c`rn|Boolotherwise=Int# -> IntI#Int#xInt -> r -> r`c`Int# -> rgo_dn(Int#xInt# -> Int# -> Int#+#Int#delta)inInt# -> IntI#Int#x1Int -> r -> r`c`Int# -> rgo_dnInt#x2-------------------------------------------------------------------------- Word-------------------------------------------------------------------------- | @since 2.01instanceBoundedWordwhereminBound :: WordminBound=Word0-- use unboxed literals for maxBound, because GHC doesn't optimise-- (fromInteger 0xffffffff :: Word).#if WORD_SIZE_IN_BITS == 32maxBound=W#0xFFFFFFFF###elif WORD_SIZE_IN_BITS == 64maxBound :: WordmaxBound=Word# -> WordW#Word#0xFFFFFFFFFFFFFFFF###else#error Unhandled value for WORD_SIZE_IN_BITS#endif-- | @since 2.01instanceEnumWordwheresucc :: Word -> WordsuccWordx|WordxWord -> Word -> Boolforall a. Eq a => a -> a -> Bool/=Wordforall a. Bounded a => amaxBound=WordxWord -> Word -> Wordforall a. Num a => a -> a -> a+Word1|Boolotherwise=String -> Wordforall a. String -> asuccErrorString"Word"pred :: Word -> WordpredWordx|WordxWord -> Word -> Boolforall a. Eq a => a -> a -> Bool/=Wordforall a. Bounded a => aminBound=WordxWord -> Word -> Wordforall a. Num a => a -> a -> a-Word1|Boolotherwise=String -> Wordforall a. String -> apredErrorString"Word"toEnum :: Int -> WordtoEnumi :: Inti@(I#Int#i#)|IntiInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Int0=Word# -> WordW#(Int# -> Word#int2Word#Int#i#)|Boolotherwise=String -> Int -> (Word, Word) -> Wordforall a b. Show a => String -> Int -> (a, a) -> btoEnumErrorString"Word"Inti(Wordforall a. Bounded a => aminBound::Word,Wordforall a. Bounded a => amaxBound::Word)fromEnum :: Word -> IntfromEnumx :: Wordx@(W#Word#x#)|WordxWord -> Word -> Boolforall a. Ord a => a -> a -> Bool<=WordmaxIntWord=Int# -> IntI#(Word# -> Int#word2Int#Word#x#)|Boolotherwise=String -> Word -> Intforall a b. Show a => String -> a -> bfromEnumErrorString"Word"Wordx{-# INLINEenumFrom#-}enumFrom :: Word -> [Word]enumFrom(W#Word#x#)=Word# -> Word# -> [Word]eftWordWord#x#Word#maxWord#where!(W#Word#maxWord#)=Wordforall a. Bounded a => amaxBound-- Blarg: technically I guess enumFrom isn't strict!{-# INLINEenumFromTo#-}enumFromTo :: Word -> Word -> [Word]enumFromTo(W#Word#x)(W#Word#y)=Word# -> Word# -> [Word]eftWordWord#xWord#y{-# INLINEenumFromThen#-}enumFromThen :: Word -> Word -> [Word]enumFromThen(W#Word#x1)(W#Word#x2)=Word# -> Word# -> [Word]efdWordWord#x1Word#x2{-# INLINEenumFromThenTo#-}enumFromThenTo :: Word -> Word -> Word -> [Word]enumFromThenTo(W#Word#x1)(W#Word#x2)(W#Word#y)=Word# -> Word# -> Word# -> [Word]efdtWordWord#x1Word#x2Word#ymaxIntWord::Word-- The biggest word representable as an IntmaxIntWord :: WordmaxIntWord=Word# -> WordW#(caseIntmaxIntofI#Int#i->Int# -> Word#int2Word#Int#i)------------------------------------------------------- eftWord and eftWordFB deal with [a..b], which is the-- most common form, so we take a lot of care-- In particular, we have rules for deforestation{-# RULES"eftWord"[~1]forallxy.eftWordxy=build(\cn->eftWordFBcnxy)"eftWordList"[1]eftWordFB(:)[]=eftWord#-}-- The Enum rules for Word work much the same way that they do for Int.-- See Note [How the Enum rules work].{-# NOINLINE[1]eftWord#-}eftWord::Word#->Word#->[Word]-- [x1..x2]eftWord :: Word# -> Word# -> [Word]eftWordWord#x0Word#y|Int# -> BoolisTrue#(Word#x0Word# -> Word# -> Int#`gtWord#`Word#y)=[]|Boolotherwise=Word# -> [Word]goWord#x0wherego :: Word# -> [Word]goWord#x=Word# -> WordW#Word#xWord -> [Word] -> [Word]forall a. a -> [a] -> [a]:ifInt# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`eqWord#`Word#y)then[]elseWord# -> [Word]go(Word#xWord# -> Word# -> Word#`plusWord#`Word#1##){-# INLINE[0]eftWordFB#-}-- See Note [Inline FB functions] in GHC.ListeftWordFB::(Word->r->r)->r->Word#->Word#->reftWordFB :: forall r. (Word -> r -> r) -> r -> Word# -> Word# -> reftWordFBWord -> r -> rcrnWord#x0Word#y|Int# -> BoolisTrue#(Word#x0Word# -> Word# -> Int#`gtWord#`Word#y)=rn|Boolotherwise=Word# -> rgoWord#x0wherego :: Word# -> rgoWord#x=Word# -> WordW#Word#xWord -> r -> r`c`ifInt# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`eqWord#`Word#y)thenrnelseWord# -> rgo(Word#xWord# -> Word# -> Word#`plusWord#`Word#1##)-- Watch out for y=maxBound; hence ==, not >-- Be very careful not to have more than one "c"-- so that when eftInfFB is inlined we can inline-- whatever is bound to "c"------------------------------------------------------- efdWord and efdtWord deal with [a,b..] and [a,b..c].-- The code is more complicated because of worries about Word overflow.-- See Note [How the Enum rules work]{-# RULES"efdtWord"[~1]forallx1x2y.efdtWordx1x2y=build(\cn->efdtWordFBcnx1x2y)"efdtWordUpList"[1]efdtWordFB(:)[]=efdtWord#-}efdWord::Word#->Word#->[Word]-- [x1,x2..maxWord]efdWord :: Word# -> Word# -> [Word]efdWordWord#x1Word#x2|Int# -> BoolisTrue#(Word#x2Word# -> Word# -> Int#`geWord#`Word#x1)=caseWordforall a. Bounded a => amaxBoundofW#Word#y->Word# -> Word# -> Word# -> [Word]efdtWordUpWord#x1Word#x2Word#y|Boolotherwise=caseWordforall a. Bounded a => aminBoundofW#Word#y->Word# -> Word# -> Word# -> [Word]efdtWordDnWord#x1Word#x2Word#y{-# NOINLINE[1]efdtWord#-}efdtWord::Word#->Word#->Word#->[Word]-- [x1,x2..y]efdtWord :: Word# -> Word# -> Word# -> [Word]efdtWordWord#x1Word#x2Word#y|Int# -> BoolisTrue#(Word#x2Word# -> Word# -> Int#`geWord#`Word#x1)=Word# -> Word# -> Word# -> [Word]efdtWordUpWord#x1Word#x2Word#y|Boolotherwise=Word# -> Word# -> Word# -> [Word]efdtWordDnWord#x1Word#x2Word#y{-# INLINE[0]efdtWordFB#-}-- See Note [Inline FB functions] in GHC.ListefdtWordFB::(Word->r->r)->r->Word#->Word#->Word#->refdtWordFB :: forall r. (Word -> r -> r) -> r -> Word# -> Word# -> Word# -> refdtWordFBWord -> r -> rcrnWord#x1Word#x2Word#y|Int# -> BoolisTrue#(Word#x2Word# -> Word# -> Int#`geWord#`Word#x1)=(Word -> r -> r) -> r -> Word# -> Word# -> Word# -> rforall r. (Word -> r -> r) -> r -> Word# -> Word# -> Word# -> refdtWordUpFBWord -> r -> rcrnWord#x1Word#x2Word#y|Boolotherwise=(Word -> r -> r) -> r -> Word# -> Word# -> Word# -> rforall r. (Word -> r -> r) -> r -> Word# -> Word# -> Word# -> refdtWordDnFBWord -> r -> rcrnWord#x1Word#x2Word#y-- Requires x2 >= x1efdtWordUp::Word#->Word#->Word#->[Word]efdtWordUp :: Word# -> Word# -> Word# -> [Word]efdtWordUpWord#x1Word#x2Word#y-- Be careful about overflow!|Int# -> BoolisTrue#(Word#yWord# -> Word# -> Int#`ltWord#`Word#x2)=ifInt# -> BoolisTrue#(Word#yWord# -> Word# -> Int#`ltWord#`Word#x1)then[]else[Word# -> WordW#Word#x1]|Boolotherwise=-- Common case: x1 <= x2 <= ylet!delta :: Word#delta=Word#x2Word# -> Word# -> Word#`minusWord#`Word#x1-- >= 0!y' :: Word#y'=Word#yWord# -> Word# -> Word#`minusWord#`Word#delta-- x1 <= y' <= y; hence y' is representable-- Invariant: x <= y-- Note that: z <= y' => z + delta won't overflow-- so we are guaranteed not to overflow if/when we recursego_up :: Word# -> [Word]go_upWord#x|Int# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`gtWord#`Word#y')=[Word# -> WordW#Word#x]|Boolotherwise=Word# -> WordW#Word#xWord -> [Word] -> [Word]forall a. a -> [a] -> [a]:Word# -> [Word]go_up(Word#xWord# -> Word# -> Word#`plusWord#`Word#delta)inWord# -> WordW#Word#x1Word -> [Word] -> [Word]forall a. a -> [a] -> [a]:Word# -> [Word]go_upWord#x2-- Requires x2 >= x1{-# INLINE[0]efdtWordUpFB#-}-- See Note [Inline FB functions] in GHC.ListefdtWordUpFB::(Word->r->r)->r->Word#->Word#->Word#->refdtWordUpFB :: forall r. (Word -> r -> r) -> r -> Word# -> Word# -> Word# -> refdtWordUpFBWord -> r -> rcrnWord#x1Word#x2Word#y-- Be careful about overflow!|Int# -> BoolisTrue#(Word#yWord# -> Word# -> Int#`ltWord#`Word#x2)=ifInt# -> BoolisTrue#(Word#yWord# -> Word# -> Int#`ltWord#`Word#x1)thenrnelseWord# -> WordW#Word#x1Word -> r -> r`c`rn|Boolotherwise=-- Common case: x1 <= x2 <= ylet!delta :: Word#delta=Word#x2Word# -> Word# -> Word#`minusWord#`Word#x1-- >= 0!y' :: Word#y'=Word#yWord# -> Word# -> Word#`minusWord#`Word#delta-- x1 <= y' <= y; hence y' is representable-- Invariant: x <= y-- Note that: z <= y' => z + delta won't overflow-- so we are guaranteed not to overflow if/when we recursego_up :: Word# -> rgo_upWord#x|Int# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`gtWord#`Word#y')=Word# -> WordW#Word#xWord -> r -> r`c`rn|Boolotherwise=Word# -> WordW#Word#xWord -> r -> r`c`Word# -> rgo_up(Word#xWord# -> Word# -> Word#`plusWord#`Word#delta)inWord# -> WordW#Word#x1Word -> r -> r`c`Word# -> rgo_upWord#x2-- Requires x2 <= x1efdtWordDn::Word#->Word#->Word#->[Word]efdtWordDn :: Word# -> Word# -> Word# -> [Word]efdtWordDnWord#x1Word#x2Word#y-- Be careful about underflow!|Int# -> BoolisTrue#(Word#yWord# -> Word# -> Int#`gtWord#`Word#x2)=ifInt# -> BoolisTrue#(Word#yWord# -> Word# -> Int#`gtWord#`Word#x1)then[]else[Word# -> WordW#Word#x1]|Boolotherwise=-- Common case: x1 >= x2 >= ylet!delta :: Word#delta=Word#x2Word# -> Word# -> Word#`minusWord#`Word#x1-- <= 0!y' :: Word#y'=Word#yWord# -> Word# -> Word#`minusWord#`Word#delta-- y <= y' <= x1; hence y' is representable-- Invariant: x >= y-- Note that: z >= y' => z + delta won't underflow-- so we are guaranteed not to underflow if/when we recursego_dn :: Word# -> [Word]go_dnWord#x|Int# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`ltWord#`Word#y')=[Word# -> WordW#Word#x]|Boolotherwise=Word# -> WordW#Word#xWord -> [Word] -> [Word]forall a. a -> [a] -> [a]:Word# -> [Word]go_dn(Word#xWord# -> Word# -> Word#`plusWord#`Word#delta)inWord# -> WordW#Word#x1Word -> [Word] -> [Word]forall a. a -> [a] -> [a]:Word# -> [Word]go_dnWord#x2-- Requires x2 <= x1{-# INLINE[0]efdtWordDnFB#-}-- See Note [Inline FB functions] in GHC.ListefdtWordDnFB::(Word->r->r)->r->Word#->Word#->Word#->refdtWordDnFB :: forall r. (Word -> r -> r) -> r -> Word# -> Word# -> Word# -> refdtWordDnFBWord -> r -> rcrnWord#x1Word#x2Word#y-- Be careful about underflow!|Int# -> BoolisTrue#(Word#yWord# -> Word# -> Int#`gtWord#`Word#x2)=ifInt# -> BoolisTrue#(Word#yWord# -> Word# -> Int#`gtWord#`Word#x1)thenrnelseWord# -> WordW#Word#x1Word -> r -> r`c`rn|Boolotherwise=-- Common case: x1 >= x2 >= ylet!delta :: Word#delta=Word#x2Word# -> Word# -> Word#`minusWord#`Word#x1-- <= 0!y' :: Word#y'=Word#yWord# -> Word# -> Word#`minusWord#`Word#delta-- y <= y' <= x1; hence y' is representable-- Invariant: x >= y-- Note that: z >= y' => z + delta won't underflow-- so we are guaranteed not to underflow if/when we recursego_dn :: Word# -> rgo_dnWord#x|Int# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`ltWord#`Word#y')=Word# -> WordW#Word#xWord -> r -> r`c`rn|Boolotherwise=Word# -> WordW#Word#xWord -> r -> r`c`Word# -> rgo_dn(Word#xWord# -> Word# -> Word#`plusWord#`Word#delta)inWord# -> WordW#Word#x1Word -> r -> r`c`Word# -> rgo_dnWord#x2-------------------------------------------------------------------------- Integer-------------------------------------------------------------------------- | @since 2.01instanceEnumIntegerwheresucc :: Integer -> IntegersuccIntegerx=IntegerxInteger -> Integer -> Integerforall a. Num a => a -> a -> a+Integer1pred :: Integer -> IntegerpredIntegerx=IntegerxInteger -> Integer -> Integerforall a. Num a => a -> a -> a-Integer1toEnum :: Int -> IntegertoEnum(I#Int#n)=Int# -> IntegerISInt#nfromEnum :: Integer -> IntfromEnumIntegern=Integer -> IntintegerToIntIntegern-- See Note [Stable Unfolding for list producers]{-# INLINEenumFrom#-}enumFrom :: Integer -> [Integer]enumFromIntegerx=Integer -> Integer -> [Integer]enumDeltaIntegerIntegerxInteger1-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromThen#-}enumFromThen :: Integer -> Integer -> [Integer]enumFromThenIntegerxIntegery=Integer -> Integer -> [Integer]enumDeltaIntegerIntegerx(IntegeryInteger -> Integer -> Integerforall a. Num a => a -> a -> a-Integerx)-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromTo#-}enumFromTo :: Integer -> Integer -> [Integer]enumFromToIntegerxIntegerlim=Integer -> Integer -> Integer -> [Integer]enumDeltaToIntegerIntegerxInteger1Integerlim-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromThenTo#-}enumFromThenTo :: Integer -> Integer -> Integer -> [Integer]enumFromThenToIntegerxIntegeryIntegerlim=Integer -> Integer -> Integer -> [Integer]enumDeltaToIntegerIntegerx(IntegeryInteger -> Integer -> Integerforall a. Num a => a -> a -> a-Integerx)Integerlim-- See Note [How the Enum rules work]{-# RULES"enumDeltaInteger"[~1]forallxy.enumDeltaIntegerxy=build(\c_->enumDeltaIntegerFBcxy)"efdtInteger"[~1]forallxdl.enumDeltaToIntegerxdl=build(\cn->enumDeltaToIntegerFBcnxdl)"efdtInteger1"[~1]forallxl.enumDeltaToIntegerx1l=build(\cn->enumDeltaToInteger1FBcnxl)"enumDeltaToInteger1FB"[1]forallcnx.enumDeltaToIntegerFBcnx1=enumDeltaToInteger1FBcnx"enumDeltaInteger"[1]enumDeltaIntegerFB(:)=enumDeltaInteger"enumDeltaToInteger"[1]enumDeltaToIntegerFB(:)[]=enumDeltaToInteger"enumDeltaToInteger1"[1]enumDeltaToInteger1FB(:)[]=enumDeltaToInteger1#-}{- Note [Enum Integer rules for literal 1] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~The "1" rules above specialise for the common case where delta = 1,so that we can avoid the delta>=0 test in enumDeltaToIntegerFB.Then enumDeltaToInteger1FB is nice and small and can be inlined,which would allow the constructor to be inlined and good things to happen.We match on the literal "1" both in phase 2 (rule "efdtInteger1") andphase 1 (rule "enumDeltaToInteger1FB"), just for belt and bracesWe do not do it for Int this way because hand-tuned code already exists, andthe special case varies more from the general case, due to the issue of overflows.-}{-# INLINE[0]enumDeltaIntegerFB#-}-- See Note [Inline FB functions] in GHC.ListenumDeltaIntegerFB::(Integer->b->b)->Integer->Integer->benumDeltaIntegerFB :: forall b. (Integer -> b -> b) -> Integer -> Integer -> benumDeltaIntegerFBInteger -> b -> bcIntegerx0Integerd=Integer -> bgoIntegerx0wherego :: Integer -> bgoIntegerx=IntegerxInteger -> b -> bforall a b. a -> b -> b`seq`(IntegerxInteger -> b -> b`c`Integer -> bgo(IntegerxInteger -> Integer -> Integerforall a. Num a => a -> a -> a+Integerd)){-# NOINLINE[1]enumDeltaInteger#-}-- Inline after rule "enumDeltaInteger" is inactiveenumDeltaInteger::Integer->Integer->[Integer]enumDeltaInteger :: Integer -> Integer -> [Integer]enumDeltaIntegerIntegerxIntegerd=IntegerxInteger -> [Integer] -> [Integer]forall a b. a -> b -> b`seq`(IntegerxInteger -> [Integer] -> [Integer]forall a. a -> [a] -> [a]:Integer -> Integer -> [Integer]enumDeltaInteger(IntegerxInteger -> Integer -> Integerforall a. Num a => a -> a -> a+Integerd)Integerd)-- strict accumulator, so-- head (drop 1000000 [1 .. ]-- works{-# INLINE[0]enumDeltaToIntegerFB#-}-- See Note [Inline FB functions] in GHC.List-- Don't inline this until RULE "enumDeltaToInteger" has had a chance to fireenumDeltaToIntegerFB::(Integer->a->a)->a->Integer->Integer->Integer->aenumDeltaToIntegerFB :: forall a.(Integer -> a -> a) -> a -> Integer -> Integer -> Integer -> aenumDeltaToIntegerFBInteger -> a -> acanIntegerxIntegerdeltaIntegerlim|IntegerdeltaInteger -> Integer -> Boolforall a. Ord a => a -> a -> Bool>=Integer0=(Integer -> a -> a) -> a -> Integer -> Integer -> Integer -> aforall a.(Integer -> a -> a) -> a -> Integer -> Integer -> Integer -> aup_fbInteger -> a -> acanIntegerxIntegerdeltaIntegerlim|Boolotherwise=(Integer -> a -> a) -> a -> Integer -> Integer -> Integer -> aforall a.(Integer -> a -> a) -> a -> Integer -> Integer -> Integer -> adn_fbInteger -> a -> acanIntegerxIntegerdeltaIntegerlim{-# INLINE[0]enumDeltaToInteger1FB#-}-- See Note [Inline FB functions] in GHC.List-- Don't inline this until RULE "enumDeltaToInteger" has had a chance to fireenumDeltaToInteger1FB::(Integer->a->a)->a->Integer->Integer->aenumDeltaToInteger1FB :: forall a. (Integer -> a -> a) -> a -> Integer -> Integer -> aenumDeltaToInteger1FBInteger -> a -> acanIntegerx0Integerlim=Integer -> ago(Integerx0::Integer)wherego :: Integer -> agoIntegerx|IntegerxInteger -> Integer -> Boolforall a. Ord a => a -> a -> Bool>Integerlim=an|Boolotherwise=IntegerxInteger -> a -> a`c`Integer -> ago(IntegerxInteger -> Integer -> Integerforall a. Num a => a -> a -> a+Integer1){-# NOINLINE[1]enumDeltaToInteger#-}-- Inline after rule "efdtInteger" is inactiveenumDeltaToInteger::Integer->Integer->Integer->[Integer]enumDeltaToInteger :: Integer -> Integer -> Integer -> [Integer]enumDeltaToIntegerIntegerxIntegerdeltaIntegerlim|IntegerdeltaInteger -> Integer -> Boolforall a. Ord a => a -> a -> Bool>=Integer0=Integer -> Integer -> Integer -> [Integer]up_listIntegerxIntegerdeltaIntegerlim|Boolotherwise=Integer -> Integer -> Integer -> [Integer]dn_listIntegerxIntegerdeltaIntegerlim{-# NOINLINE[1]enumDeltaToInteger1#-}-- Inline after rule "efdtInteger1" is inactiveenumDeltaToInteger1::Integer->Integer->[Integer]-- Special case for Delta = 1enumDeltaToInteger1 :: Integer -> Integer -> [Integer]enumDeltaToInteger1Integerx0Integerlim=Integer -> [Integer]go(Integerx0::Integer)wherego :: Integer -> [Integer]goIntegerx|IntegerxInteger -> Integer -> Boolforall a. Ord a => a -> a -> Bool>Integerlim=[]|Boolotherwise=IntegerxInteger -> [Integer] -> [Integer]forall a. a -> [a] -> [a]:Integer -> [Integer]go(IntegerxInteger -> Integer -> Integerforall a. Num a => a -> a -> a+Integer1)up_fb::(Integer->a->a)->a->Integer->Integer->Integer->aup_fb :: forall a.(Integer -> a -> a) -> a -> Integer -> Integer -> Integer -> aup_fbInteger -> a -> acanIntegerx0IntegerdeltaIntegerlim=Integer -> ago(Integerx0::Integer)wherego :: Integer -> agoIntegerx|IntegerxInteger -> Integer -> Boolforall a. Ord a => a -> a -> Bool>Integerlim=an|Boolotherwise=IntegerxInteger -> a -> a`c`Integer -> ago(IntegerxInteger -> Integer -> Integerforall a. Num a => a -> a -> a+Integerdelta)dn_fb::(Integer->a->a)->a->Integer->Integer->Integer->adn_fb :: forall a.(Integer -> a -> a) -> a -> Integer -> Integer -> Integer -> adn_fbInteger -> a -> acanIntegerx0IntegerdeltaIntegerlim=Integer -> ago(Integerx0::Integer)wherego :: Integer -> agoIntegerx|IntegerxInteger -> Integer -> Boolforall a. Ord a => a -> a -> Bool<Integerlim=an|Boolotherwise=IntegerxInteger -> a -> a`c`Integer -> ago(IntegerxInteger -> Integer -> Integerforall a. Num a => a -> a -> a+Integerdelta)up_list::Integer->Integer->Integer->[Integer]up_list :: Integer -> Integer -> Integer -> [Integer]up_listIntegerx0IntegerdeltaIntegerlim=Integer -> [Integer]go(Integerx0::Integer)wherego :: Integer -> [Integer]goIntegerx|IntegerxInteger -> Integer -> Boolforall a. Ord a => a -> a -> Bool>Integerlim=[]|Boolotherwise=IntegerxInteger -> [Integer] -> [Integer]forall a. a -> [a] -> [a]:Integer -> [Integer]go(IntegerxInteger -> Integer -> Integerforall a. Num a => a -> a -> a+Integerdelta)dn_list::Integer->Integer->Integer->[Integer]dn_list :: Integer -> Integer -> Integer -> [Integer]dn_listIntegerx0IntegerdeltaIntegerlim=Integer -> [Integer]go(Integerx0::Integer)wherego :: Integer -> [Integer]goIntegerx|IntegerxInteger -> Integer -> Boolforall a. Ord a => a -> a -> Bool<Integerlim=[]|Boolotherwise=IntegerxInteger -> [Integer] -> [Integer]forall a. a -> [a] -> [a]:Integer -> [Integer]go(IntegerxInteger -> Integer -> Integerforall a. Num a => a -> a -> a+Integerdelta)-------------------------------------------------------------------------- Natural-------------------------------------------------------------------------- | @since 4.8.0.0instanceEnumNaturalwheresucc :: Natural -> NaturalsuccNaturaln=NaturalnNatural -> Natural -> Naturalforall a. Num a => a -> a -> a+Natural1pred :: Natural -> NaturalpredNaturaln=NaturalnNatural -> Natural -> Naturalforall a. Num a => a -> a -> a-Natural1toEnum :: Int -> NaturaltoEnumi :: Inti@(I#Int#i#)|IntiInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Int0=Word# -> NaturalnaturalFromWord#(Int# -> Word#int2Word#Int#i#)|Boolotherwise=String -> Naturalforall a. String -> aerrorWithoutStackTraceString"toEnum: unexpected negative Int"fromEnum :: Natural -> IntfromEnum(NSWord#w)|IntiInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Int0=Intiwherei :: Inti=Int# -> IntI#(Word# -> Int#word2Int#Word#w)fromEnumNatural_=String -> Intforall a. String -> aerrorWithoutStackTraceString"fromEnum: out of Int range"-- See Note [Stable Unfolding for list producers]{-# INLINEenumFrom#-}enumFrom :: Natural -> [Natural]enumFromNaturalx=Natural -> Natural -> [Natural]enumDeltaNaturalNaturalxNatural1-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromThen#-}enumFromThen :: Natural -> Natural -> [Natural]enumFromThenNaturalxNaturaly|NaturalxNatural -> Natural -> Boolforall a. Ord a => a -> a -> Bool<=Naturaly=Natural -> Natural -> [Natural]enumDeltaNaturalNaturalx(NaturalyNatural -> Natural -> Naturalforall a. Num a => a -> a -> a-Naturalx)|Boolotherwise=Natural -> Natural -> Natural -> [Natural]enumNegDeltaToNaturalNaturalx(NaturalxNatural -> Natural -> Naturalforall a. Num a => a -> a -> a-Naturaly)Natural0-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromTo#-}enumFromTo :: Natural -> Natural -> [Natural]enumFromToNaturalxNaturallim=Natural -> Natural -> Natural -> [Natural]enumDeltaToNaturalNaturalxNatural1Naturallim-- See Note [Stable Unfolding for list producers]{-# INLINEenumFromThenTo#-}enumFromThenTo :: Natural -> Natural -> Natural -> [Natural]enumFromThenToNaturalxNaturalyNaturallim|NaturalxNatural -> Natural -> Boolforall a. Ord a => a -> a -> Bool<=Naturaly=Natural -> Natural -> Natural -> [Natural]enumDeltaToNaturalNaturalx(NaturalyNatural -> Natural -> Naturalforall a. Num a => a -> a -> a-Naturalx)Naturallim|Boolotherwise=Natural -> Natural -> Natural -> [Natural]enumNegDeltaToNaturalNaturalx(NaturalxNatural -> Natural -> Naturalforall a. Num a => a -> a -> a-Naturaly)Naturallim-- Helpers for 'Enum Natural'; TODO: optimise & make fusion workenumDeltaNatural::Natural->Natural->[Natural]enumDeltaNatural :: Natural -> Natural -> [Natural]enumDeltaNatural!NaturalxNaturald=NaturalxNatural -> [Natural] -> [Natural]forall a. a -> [a] -> [a]:Natural -> Natural -> [Natural]enumDeltaNatural(NaturalxNatural -> Natural -> Naturalforall a. Num a => a -> a -> a+Naturald)Naturald-- Inline to specialize{-# INLINEenumDeltaToNatural#-}enumDeltaToNatural::Natural->Natural->Natural->[Natural]enumDeltaToNatural :: Natural -> Natural -> Natural -> [Natural]enumDeltaToNaturalNaturalx0NaturaldeltaNaturallim=Natural -> [Natural]goNaturalx0wherego :: Natural -> [Natural]goNaturalx|NaturalxNatural -> Natural -> Boolforall a. Ord a => a -> a -> Bool>Naturallim=[]|Boolotherwise=NaturalxNatural -> [Natural] -> [Natural]forall a. a -> [a] -> [a]:Natural -> [Natural]go(NaturalxNatural -> Natural -> Naturalforall a. Num a => a -> a -> a+Naturaldelta)-- Inline to specialize{-# INLINEenumNegDeltaToNatural#-}enumNegDeltaToNatural::Natural->Natural->Natural->[Natural]enumNegDeltaToNatural :: Natural -> Natural -> Natural -> [Natural]enumNegDeltaToNaturalNaturalx0NaturalndeltaNaturallim=Natural -> [Natural]goNaturalx0wherego :: Natural -> [Natural]goNaturalx|NaturalxNatural -> Natural -> Boolforall a. Ord a => a -> a -> Bool<Naturallim=[]|NaturalxNatural -> Natural -> Boolforall a. Ord a => a -> a -> Bool>=Naturalndelta=NaturalxNatural -> [Natural] -> [Natural]forall a. a -> [a] -> [a]:Natural -> [Natural]go(NaturalxNatural -> Natural -> Naturalforall a. Num a => a -> a -> a-Naturalndelta)|Boolotherwise=[Naturalx]-- Instances from GHC.Types-- | @since 4.16.0.0derivinginstanceBoundedLevity-- | @since 4.16.0.0derivinginstanceEnumLevity-- | @since 4.10.0.0derivinginstanceBoundedVecCount-- | @since 4.10.0.0derivinginstanceEnumVecCount-- | @since 4.10.0.0derivinginstanceBoundedVecElem-- | @since 4.10.0.0derivinginstanceEnumVecElem
[8]ページ先頭