File: Classes.hs

package info (click to toggle)
haskell-type-level-numbers 0.1.1.2-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 136 kB
  • sloc: haskell: 663; makefile: 5
file content (170 lines) | stat: -rw-r--r-- 5,356 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
{-# LANGUAGE EmptyDataDecls        #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE TypeOperators         #-}
{-# LANGUAGE UndecidableInstances  #-}
-- |
-- Module      : TypeLevel.Number.Classes
-- Copyright   : Alexey Khudyakov
-- License     : BSD3-style (see LICENSE)
--
-- Maintainer  : Alexey Khudyakov <alexey.skladnoy@gmail.com>
-- Stability   : unstable
-- Portability : unportable (GHC only)
--
-- This module contain interface type classes for operations with type
-- level numbers.
module TypeLevel.Number.Classes ( -- * Comparison of numbers
                                  Compare
                                , compareN
                                  -- ** Data labels for types comparison
                                , IsLesser
                                , IsEqual
                                , IsGreater
                                  -- ** Specialized type classes
                                  -- $comparing
                                , Lesser
                                , LesserEq
                                , Greater
                                , GreaterEq
                                  -- ** Special traits
                                , Positive
                                , NonZero
                                  -- * Arithmetic operations on numbers
                                , Next
                                , nextN
                                , Prev
                                , prevN
                                , Negate
                                , negateN
                                , Add
                                , addN
                                , Sub
                                , subN
                                , Mul
                                , mulN
                                , Div
                                , divN
                                  -- * Special classes
                                , Normalized
                                ) where

----------------------------------------------------------------
-- Comparison
----------------------------------------------------------------

-- | Type family for comparing two numbers. It's expected that for any
-- two valid 'n' and 'm' 'Compare n m' is equal to IsLess when 'n<m', IsEqual
-- when 'n=m' and IsGreater when 'n>m'.
type family Compare n m :: *

compareN :: n -> m -> Compare n m
compareN _ _ = undefined

data IsLesser
data IsEqual
data IsGreater

instance Show IsLesser  where show _  = "IsLesser"
instance Show IsEqual   where show _  = "IsEqual"
instance Show IsGreater where show _  = "IsGreater"

----------------------------------------------------------------

-- $comparing
-- These type classes are meant to be used in contexts to ensure
-- relations between numbers. For example:
-- 
-- > someFunction :: Lesser n m => Data n -> Data m -> Data n
-- > someFunction = ...
--
-- They have generic instances and every number which is instance of
-- Compare type family is instance of these type classes.
-- 
-- These instance could have problems. They weren't exensively tested.
-- Also error messages are really unhelpful.

-- | Numbers n and m are instances of this class if and only is n < m.
class Lesser n m

-- | Numbers n and m are instances of this class if and only is n > m.
class Greater n m

-- | Numbers n and m are instances of this class if and only is n <= m.
class LesserEq n m

-- | Numbers n and m are instances of this class if and only is n >= m.
class GreaterEq n m

-- a b c are instance of class only when a ~ b or a ~ c. Require ovelapping.
class    OneOfTwo a b c
instance OneOfTwo a a b
instance OneOfTwo a b a
instance OneOfTwo a a a

instance (Compare n m ~ IsLesser ) => Lesser n m
instance (Compare n m ~ IsGreater) => Greater n m
-- Instances for LessEq and GreaterEq are trickier.
instance (OneOfTwo (Compare n m) IsLesser  IsEqual) => LesserEq n m
instance (OneOfTwo (Compare n m) IsGreater IsEqual) => GreaterEq n m

-- | Non-zero number. For naturals it's same as positive
class NonZero n

-- | Positive number. 
class Positive n

----------------------------------------------------------------

-- | Next number.
type family Next n :: *

nextN :: n -> Next n
nextN _ = undefined

-- | Previous number
type family Prev n :: *

prevN :: n -> Prev n
prevN _ = undefined

-- | Negate number.
type family Negate n :: *

negateN :: n -> Negate n
negateN _ = undefined

----------------------------------------------------------------

-- | Sum of two numbers.
type family  Add n m :: *

addN :: n -> m -> Add n m
addN _ _ = undefined

-- | Difference of two numbers.
type family Sub n m :: *

subN :: n -> m -> Sub n m
subN _ _ = undefined

-- | Product of two numbers.
type family Mul n m :: *
       
mulN :: n -> m -> Mul n m
mulN _ _ = undefined

-- | Division of two numbers. 'n' and 'm' should be instances of this
-- class only if remainder of 'n/m' is zero.
type family Div n m :: *

divN :: n -> m -> Div n m
divN _ _ = undefined

----------------------------------------------------------------

-- | Usually numbers have non-unique representation. This type family
-- is canonical representation of number.
type family Normalized n :: *