typenums-0.1.4: Type level numbers using existing Nat functionality
Copyright(c) 2018-2021 Iris Ward
LicenseBSD3
Maintaineraditu.venyhandottir@gmail.com
Stabilityexperimental
Safe HaskellTrustworthy
LanguageHaskell2010

Data.TypeNums.Rats

Description

Type level rational numbers expressed as a ratio between a type-level integer and a type-level natural. For example Neg 3 :% 2.

See also: Data.TypeInts

Synopsis

Construction

data Rat Source #

Type constructor for a rational

Constructors

forall k. k :% Nat 

Instances

Instances details
(KnownInt n, KnownNat d, d /= 0) => KnownRat (n :% d :: Rat) Source # 
Instance details

Defined in Data.TypeNums.Rats

Methods

ratSing :: SRat (n :% d)

(TypeError ('Text "Denominator must not equal 0") :: Constraint) => KnownRat (n :% 0 :: Rat) Source # 
Instance details

Defined in Data.TypeNums.Rats

Methods

ratSing :: SRat (n :% 0)

Linking type and value level

class KnownRat r Source #

This class gives the (value-level) rational associated with a type-level rational. There are instances of this class for every combination of a concrete integer and concrete natural.

Minimal complete definition

ratSing

Instances

Instances details
KnownInt n => KnownRat (n :: k) Source # 
Instance details

Defined in Data.TypeNums.Rats

Methods

ratSing :: SRat n

(KnownInt n, KnownNat d, d /= 0) => KnownRat (n :% d :: Rat) Source # 
Instance details

Defined in Data.TypeNums.Rats

Methods

ratSing :: SRat (n :% d)

(TypeError ('Text "Denominator must not equal 0") :: Constraint) => KnownRat (n :% 0 :: Rat) Source # 
Instance details

Defined in Data.TypeNums.Rats

Methods

ratSing :: SRat (n :% 0)

ratVal :: forall proxy r. KnownRat r => proxy r -> Rational Source #

Get the value associated with a type-level rational

ratVal' :: forall r. KnownRat r => Proxy# r -> Rational Source #

Get the value associated with a type-level rational. The difference between this function and ratVal is that it takes a Proxy# parameter, which has zero runtime representation and so is entirely free.

data SomeRat Source #

This type represents unknown type-level integers.

Since: 0.1.1

Constructors

forall r.KnownRat r => SomeRat (Proxy r) 

Instances

Instances details
Eq SomeRat Source # 
Instance details

Defined in Data.TypeNums.Rats

Methods

(==) :: SomeRat -> SomeRat -> Bool #

(/=) :: SomeRat -> SomeRat -> Bool #

Ord SomeRat Source # 
Instance details

Defined in Data.TypeNums.Rats

Read SomeRat Source # 
Instance details

Defined in Data.TypeNums.Rats

Show SomeRat Source # 
Instance details

Defined in Data.TypeNums.Rats

someRatVal :: Rational -> SomeRat Source #

Convert a rational into an unknown type-level rational.

Since: 0.1.1