Skip to content
Snippets Groups Projects
Commit 44dd6306 authored by Ian Lynagh's avatar Ian Lynagh
Browse files

Don't define our own list type

We can now use [] as it has been moved to ghc-prim.
parent 1f3ef8a1
No related branches found
No related tags found
No related merge requests found
...@@ -42,15 +42,12 @@ data Integer = Positive !Positive | Negative !Positive | Naught ...@@ -42,15 +42,12 @@ data Integer = Positive !Positive | Negative !Positive | Naught
-- Positive's have the property that they contain at least one Bit, -- Positive's have the property that they contain at least one Bit,
-- and their last Bit is One. -- and their last Bit is One.
type Positive = Digits type Positive = Digits
type Positives = List Positive type Positives = [Positive]
data Digits = Some !Digit !Digits data Digits = Some !Digit !Digits
| None | None
type Digit = Word# type Digit = Word#
-- XXX Could move [] above us
data List a = Nil | Cons a (List a)
mkInteger :: Bool -- non-negative? mkInteger :: Bool -- non-negative?
-> [Int] -- absolute value in 31 bit chunks, least significant first -> [Int] -- absolute value in 31 bit chunks, least significant first
-- ideally these would be Words rather than Ints, but -- ideally these would be Words rather than Ints, but
...@@ -743,9 +740,9 @@ quotRemPositive :: Positive -> Positive -> (# Integer, Integer #) ...@@ -743,9 +740,9 @@ quotRemPositive :: Positive -> Positive -> (# Integer, Integer #)
subtractors = mkSubtractors (WORD_SIZE_IN_BITS# -# 1#) subtractors = mkSubtractors (WORD_SIZE_IN_BITS# -# 1#)
mkSubtractors (!n) = if n ==# 0# mkSubtractors (!n) = if n ==# 0#
then Cons ys Nil then [ys]
else Cons (ys `smallShiftLPositive` n) else (ys `smallShiftLPositive` n)
(mkSubtractors (n -# 1#)) : (mkSubtractors (n -# 1#))
-- The main function. Go the the end of xs, then walk -- The main function. Go the the end of xs, then walk
-- back trying to divide the number we accumulate by ys. -- back trying to divide the number we accumulate by ys.
...@@ -761,8 +758,8 @@ quotRemPositive :: Positive -> Positive -> (# Integer, Integer #) ...@@ -761,8 +758,8 @@ quotRemPositive :: Positive -> Positive -> (# Integer, Integer #)
(# some d ds, m'' #) (# some d ds, m'' #)
g :: Digit -> Positives -> Digits -> (# Digit, Digits #) g :: Digit -> Positives -> Digits -> (# Digit, Digits #)
g (!d) Nil (!m) = (# d, m #) g (!d) [] (!m) = (# d, m #)
g (!d) (Cons sub subs) (!m) g (!d) (sub : subs) (!m)
= case d `uncheckedShiftL#` 1# of = case d `uncheckedShiftL#` 1# of
d' -> d' ->
case m `comparePositive` sub of case m `comparePositive` sub of
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment