Copyright | (C) 2021 Koz Ross |
---|---|
License | BSD3 |
Maintainer | Koz Ross <koz.ross@retro-freedom.nz> |
Stability | stable |
Portability | GHC only |
Safe Haskell | Trustworthy |
Language | Haskell98 |
An 'ordered ring' is a ring with a total order.
Mathematical pedantry note
Many (if not most) of the instances of the OrderedRing
type class are not
truly ordered rings in the mathematical sense, as the
axioms imply that the
underlying set is either a singleton or infinite. Thus, the additional
properties of
ordered rings do not, in general, hold.
We indicate those instances that are 'truly' or 'mathematically' ordered rings in their documentation.
Synopsis
- newtype Modular a = Modular {
- getModular :: a
- class (Ring a, Ord a) => OrderedRing a where
Helper types
A wrapper to indicate the type is being treated as a modular arithmetic system whose modulus is the type's cardinality.
While we cannot guarantee that infinite types won't be wrapped by this, we only provide instances of the relevant type classes for those types we are certain are finite.
Since: 0.7
Modular | |
|
Instances
Data a => Data (Modular a) Source # | Since: 0.7 |
Defined in Data.Ring.Ordered gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Modular a -> c (Modular a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Modular a) # toConstr :: Modular a -> Constr # dataTypeOf :: Modular a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Modular a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Modular a)) # gmapT :: (forall b. Data b => b -> b) -> Modular a -> Modular a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Modular a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Modular a -> r # gmapQ :: (forall d. Data d => d -> u) -> Modular a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Modular a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Modular a -> m (Modular a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Modular a -> m (Modular a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Modular a -> m (Modular a) # | |
Bounded a => Bounded (Modular a) Source # | Since: 0.7 |
Generic (Modular a) Source # | |
Read a => Read (Modular a) Source # | Since: 0.7 |
Show a => Show (Modular a) Source # | Since: 0.7 |
Eq a => Eq (Modular a) Source # | Since: 0.7 |
Ord a => Ord (Modular a) Source # | Since: 0.7 |
Defined in Data.Ring.Ordered | |
OrderedRing (Modular Word16) Source # | Since: 0.7 |
OrderedRing (Modular Word32) Source # | Since: 0.7 |
OrderedRing (Modular Word64) Source # | Since: 0.7 |
OrderedRing (Modular Word8) Source # | Since: 0.7 |
OrderedRing (Modular Word) Source # | Since: 0.7 |
Ring (Modular Word16) Source # | |
Ring (Modular Word32) Source # | |
Ring (Modular Word64) Source # | |
Ring (Modular Word8) Source # | |
Ring (Modular Word) Source # | |
Semiring (Modular Word16) Source # | |
Semiring (Modular Word32) Source # | |
Semiring (Modular Word64) Source # | |
Semiring (Modular Word8) Source # | |
Semiring (Modular Word) Source # | |
type Rep (Modular a) Source # | Since: 0.7 |
Defined in Data.Ring.Ordered |
Ordered ring type class
class (Ring a, Ord a) => OrderedRing a where Source #
The class of rings which also have a total order.
Instance should satisfy the following laws:
abs
zero
=zero
abs
x =abs
(negate
x)x
-
abs
x =zero
signum
zero
=zero
- If
x
, then>
zero
signum
x =one
- If
x
, then<
zero
signum
x =negate
one
Since: 0.7
Compute the absolute value.
Determine the 'sign' of a value.
Instances
OrderedRing Int16 Source # | Since: 0.7 |
OrderedRing Int32 Source # | Since: 0.7 |
OrderedRing Int64 Source # | Since: 0.7 |
OrderedRing Int8 Source # | Since: 0.7 |
OrderedRing Integer Source # | This instance is a 'true' or 'mathematical' ordered ring, as Since: 0.7 |
OrderedRing () Source # | This instance is a 'true' or 'mathematical' ordered ring, as it is a
singleton. We assume that Since: 0.7 |
OrderedRing Int Source # | Since: 0.7 |
OrderedRing a => OrderedRing (Identity a) Source # | Where Since: 0.7 |
OrderedRing a => OrderedRing (Down a) Source # | Where Since: 0.7 |
OrderedRing a => OrderedRing (Dual a) Source # | Where Since: 0.7 |
Integral a => OrderedRing (Ratio a) Source # | Where Since: 0.7 |
OrderedRing (Modular Word16) Source # | Since: 0.7 |
OrderedRing (Modular Word32) Source # | Since: 0.7 |
OrderedRing (Modular Word64) Source # | Since: 0.7 |
OrderedRing (Modular Word8) Source # | Since: 0.7 |
OrderedRing (Modular Word) Source # | Since: 0.7 |
HasResolution a => OrderedRing (Fixed a) Source # | Since: 0.7 |
OrderedRing a => OrderedRing (Const a b) Source # | Where Since: 0.7 |