nat-sized-numbers-0.2.0.0: Variable-sized numbers from type-level nats.

Safe HaskellNone
LanguageHaskell2010

Numeric.Sized.IntOfSize

Description

This module exports the IntOfSize type and associated functions.

Synopsis

Documentation

newtype IntOfSize n Source #

An integer type with a size decided by a type-level nat. Numeric operations wraparound by default:

>>> (127 :: IntOfSize 8) + 1
-128

Constructors

IntOfSize 

Instances

KnownNat n => Bounded (IntOfSize n) Source # 
KnownNat n => Enum (IntOfSize n) Source # 
KnownNat n => Eq (IntOfSize n) Source # 

Methods

(==) :: IntOfSize n -> IntOfSize n -> Bool #

(/=) :: IntOfSize n -> IntOfSize n -> Bool #

KnownNat n => Integral (IntOfSize n) Source # 
KnownNat n => Num (IntOfSize n) Source # 
KnownNat n => Ord (IntOfSize n) Source # 
KnownNat n => Real (IntOfSize n) Source # 
KnownNat n => Show (IntOfSize n) Source # 
KnownNat n => Ix (IntOfSize n) Source # 
Generic (IntOfSize n) Source # 

Associated Types

type Rep (IntOfSize n) :: * -> * #

Methods

from :: IntOfSize n -> Rep (IntOfSize n) x #

to :: Rep (IntOfSize n) x -> IntOfSize n #

KnownNat n => Bits (IntOfSize n) Source # 
KnownNat n => FiniteBits (IntOfSize n) Source # 
type Rep (IntOfSize n) Source # 
type Rep (IntOfSize n) = D1 (MetaData "IntOfSize" "Numeric.Sized.IntOfSize" "nat-sized-numbers-0.2.0.0-G32RKoDML39HRDzfqWsuNm" True) (C1 (MetaCons "IntOfSize" PrefixI True) (S1 (MetaSel (Just Symbol "getIntOfSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

allIntsOfSize :: KnownNat n => [IntOfSize n] Source #

Generate all values, in a sensible order

>>> allIntsOfSize :: [IntOfSize 4]
[0,-1,1,-2,2,-3,3,-4,4,-5,5,-6,6,-7,7,-8]