File: Group.hs

package info (click to toggle)
haskell-algebra 2.1.1.2-1
  • links: PTS, VCS
  • area: main
  • in suites: wheezy
  • size: 420 kB
  • sloc: haskell: 4,758; makefile: 2
file content (149 lines) | stat: -rw-r--r-- 4,269 bytes parent folder | download
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
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, TypeOperators #-}
module Numeric.Additive.Group
  ( -- * Additive Groups
    Group(..)
  ) where

import Data.Int
import Data.Word
import Data.Key
import Data.Functor.Representable.Trie
import Prelude hiding ((*), (+), (-), negate, subtract,zipWith)
import qualified Prelude
import Numeric.Additive.Class
import Numeric.Algebra.Class

infixl 6 - 
infixl 7 `times`

class (LeftModule Integer r, RightModule Integer r, Monoidal r) => Group r where
  (-)      :: r -> r -> r
  negate   :: r -> r
  subtract :: r -> r -> r
  times    :: Integral n => n -> r -> r
  times y0 x0 = case compare y0 0 of
    LT -> f (negate x0) (Prelude.negate y0)
    EQ -> zero
    GT -> f x0 y0
    where
      f x y 
        | even y = f (x + x) (y `quot` 2)
        | y == 1 = x
        | otherwise = g (x + x) ((y Prelude.- 1) `quot` 2) x
      g x y z 
        | even y = g (x + x) (y `quot` 2) z
        | y == 1 = x + z
        | otherwise = g (x + x) ((y Prelude.- 1) `quot` 2) (x + z)

  negate a = zero - a
  a - b  = a + negate b 
  subtract a b = negate a + b

instance Group r => Group (e -> r) where
  f - g = \x -> f x - g x
  negate f x = negate (f x)
  subtract f g x = subtract (f x) (g x)
  times n f e = times n (f e)

instance (HasTrie e, Group r) => Group (e :->: r) where
  (-) = zipWith (-)
  negate = fmap negate
  subtract = zipWith subtract
  times = fmap . times

instance Group Integer where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group Int where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group Int8 where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group Int16 where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group Int32 where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group Int64 where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group Word where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group Word8 where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group Word16 where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group Word32 where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group Word64 where
  (-) = (Prelude.-)
  negate = Prelude.negate
  subtract = Prelude.subtract
  times n r = fromIntegral n * r

instance Group () where 
  _ - _   = ()
  negate _ = ()
  subtract _ _  = ()
  times _ _   = ()

instance (Group a, Group b) => Group (a,b) where
  negate (a,b) = (negate a, negate b)
  (a,b) - (i,j) = (a-i, b-j)
  subtract (a,b) (i,j) = (subtract a i, subtract b j)
  times n (a,b) = (times n a,times n b)

instance (Group a, Group b, Group c) => Group (a,b,c) where
  negate (a,b,c) = (negate a, negate b, negate c)
  (a,b,c) - (i,j,k) = (a-i, b-j, c-k)
  subtract (a,b,c) (i,j,k) = (subtract a i, subtract b j, subtract c k)
  times n (a,b,c) = (times n a,times n b, times n c)

instance (Group a, Group b, Group c, Group d) => Group (a,b,c,d) where
  negate (a,b,c,d) = (negate a, negate b, negate c, negate d)
  (a,b,c,d) - (i,j,k,l) = (a-i, b-j, c-k, d-l)
  subtract (a,b,c,d) (i,j,k,l) = (subtract a i, subtract b j, subtract c k, subtract d l)
  times n (a,b,c,d) = (times n a,times n b, times n c, times n d)

instance (Group a, Group b, Group c, Group d, Group e) => Group (a,b,c,d,e) where
  negate (a,b,c,d,e) = (negate a, negate b, negate c, negate d, negate e)
  (a,b,c,d,e) - (i,j,k,l,m) = (a-i, b-j, c-k, d-l, e-m)
  subtract (a,b,c,d,e) (i,j,k,l,m) = (subtract a i, subtract b j, subtract c k, subtract d l, subtract e m)
  times n (a,b,c,d,e) = (times n a,times n b, times n c, times n d, times n e)