uom-plugin-0.4.0.0: Units of measure as a GHC type-checker plugin
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.UnitsOfMeasure.Singleton

Description

This module defines singleton types for integers and concrete units.

Synopsis

Singletons for units

data SUnit (u :: UnitSyntax Symbol) where Source #

Singleton type for concrete units of measure represented as lists of base units

Constructors

SUnit :: SList xs -> SList ys -> SUnit (xs :/ ys) 

Instances

Instances details
TestEquality SUnit Source # 
Instance details

Defined in Data.UnitsOfMeasure.Singleton

Methods

testEquality :: forall (a :: k) (b :: k). SUnit a -> SUnit b -> Maybe (a :~: b) #

forgetSUnit :: SUnit u -> UnitSyntax String Source #

Extract the runtime syntactic representation from a singleton unit

class KnownUnit (u :: UnitSyntax Symbol) where Source #

A constraint KnownUnit u means that u must be a concrete unit that is statically known but passed at runtime

Methods

unitSing :: SUnit u Source #

Instances

Instances details
(KnownList xs, KnownList ys) => KnownUnit (xs ':/ ys) Source # 
Instance details

Defined in Data.UnitsOfMeasure.Singleton

Methods

unitSing :: SUnit (xs ':/ ys) Source #

unitVal :: forall proxy u. KnownUnit u => proxy u -> UnitSyntax String Source #

Extract the runtime syntactic representation of a KnownUnit

testEquivalentSUnit :: SUnit u -> SUnit v -> Maybe (Pack u :~: Pack v) Source #

Test whether two SUnits represent the same units, up to the equivalence relation. TODO: this currently uses unsafeCoerce, but in principle it should be possible to avoid it.

Singletons for lists

data SList (xs :: [Symbol]) where Source #

Singleton type for lists of base units

Constructors

SNil :: SList '[] 
SCons :: KnownSymbol x => proxy x -> SList xs -> SList (x ': xs) 

Instances

Instances details
TestEquality SList Source # 
Instance details

Defined in Data.UnitsOfMeasure.Singleton

Methods

testEquality :: forall (a :: k) (b :: k). SList a -> SList b -> Maybe (a :~: b) #

class KnownList (xs :: [Symbol]) where Source #

A constraint KnownList xs means that xs must be a list of base units that is statically known but passed at runtime

Methods

listSing :: SList xs Source #

Instances

Instances details
KnownList ('[] :: [Symbol]) Source # 
Instance details

Defined in Data.UnitsOfMeasure.Singleton

Methods

listSing :: SList '[] Source #

(KnownSymbol x, KnownList xs) => KnownList (x ': xs) Source # 
Instance details

Defined in Data.UnitsOfMeasure.Singleton

Methods

listSing :: SList (x ': xs) Source #