diff options
author | Niklas Hambüchen <mail@nh2.me> | 2017-07-23 21:18:08 +0200 |
---|---|---|
committer | Niklas Hambüchen <mail@nh2.me> | 2017-07-23 21:18:08 +0200 |
commit | 8e79121454171b145e5d102e5713299b43604d88 (patch) | |
tree | 002a13425e32fdeff4601be0d8b1bb2a851b9181 /packages/base | |
parent | a08df91da6362d348635211a6d77d85501a72ab2 (diff) |
Fix compilation with GHC 8.2 by adding some type signatures.
Fixes this compile error:
src/Internal/Util.hs:625:5: error:
• Could not deduce (Eq t)
from the context: (Indexable (c t) a, Indexable (c t) t,
Linear t c, Num (c t), Fractional t, Num a, Eq a)
bound by the inferred type for ‘redu’:
forall a t (c :: * -> *).
(Indexable (c t) a, Indexable (c t) t, Linear t c, Num (c t),
Fractional t, Num a, Eq a) =>
(Int, [c t]) -> [c t]
at src/Internal/Util.hs:(625,5)-(632,20)
• In the ambiguity check for the inferred type for ‘redu’
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
Diffstat (limited to 'packages/base')
-rw-r--r-- | packages/base/src/Internal/Util.hs | 9 |
1 files changed, 9 insertions, 0 deletions
diff --git a/packages/base/src/Internal/Util.hs b/packages/base/src/Internal/Util.hs index 17d3e50..ec21fe4 100644 --- a/packages/base/src/Internal/Util.hs +++ b/packages/base/src/Internal/Util.hs | |||
@@ -2,6 +2,7 @@ | |||
2 | {-# LANGUAGE FlexibleInstances #-} | 2 | {-# LANGUAGE FlexibleInstances #-} |
3 | {-# LANGUAGE MultiParamTypeClasses #-} | 3 | {-# LANGUAGE MultiParamTypeClasses #-} |
4 | {-# LANGUAGE FunctionalDependencies #-} | 4 | {-# LANGUAGE FunctionalDependencies #-} |
5 | {-# LANGUAGE ScopedTypeVariables #-} | ||
5 | {-# LANGUAGE ViewPatterns #-} | 6 | {-# LANGUAGE ViewPatterns #-} |
6 | 7 | ||
7 | 8 | ||
@@ -613,6 +614,9 @@ gaussElim_1 x y = dropColumns (rows x) (flipud $ fromRows s2) | |||
613 | s1 = fromRows $ pivotDown (rows x) 0 rs -- interesting | 614 | s1 = fromRows $ pivotDown (rows x) 0 rs -- interesting |
614 | s2 = pivotUp (rows x-1) (toRows $ flipud s1) | 615 | s2 = pivotUp (rows x-1) (toRows $ flipud s1) |
615 | 616 | ||
617 | pivotDown | ||
618 | :: forall t . (Fractional t, Num (Vector t), Ord t, Indexable (Vector t) t, Numeric t) | ||
619 | => Int -> Int -> [Vector t] -> [Vector t] | ||
616 | pivotDown t n xs | 620 | pivotDown t n xs |
617 | | t == n = [] | 621 | | t == n = [] |
618 | | otherwise = y : pivotDown t (n+1) ys | 622 | | otherwise = y : pivotDown t (n+1) ys |
@@ -622,6 +626,7 @@ pivotDown t n xs | |||
622 | pivot k = (const k &&& id) | 626 | pivot k = (const k &&& id) |
623 | . sortBy (flip compare `on` (abs. (!k))) | 627 | . sortBy (flip compare `on` (abs. (!k))) |
624 | 628 | ||
629 | redu :: (Int, [Vector t]) -> [Vector t] | ||
625 | redu (k,x:zs) | 630 | redu (k,x:zs) |
626 | | p == 0 = error "gauss: singular!" -- FIXME | 631 | | p == 0 = error "gauss: singular!" -- FIXME |
627 | | otherwise = u : map f zs | 632 | | otherwise = u : map f zs |
@@ -632,12 +637,16 @@ pivotDown t n xs | |||
632 | redu (_,[]) = [] | 637 | redu (_,[]) = [] |
633 | 638 | ||
634 | 639 | ||
640 | pivotUp | ||
641 | :: forall t . (Fractional t, Num (Vector t), Ord t, Indexable (Vector t) t, Numeric t) | ||
642 | => Int -> [Vector t] -> [Vector t] | ||
635 | pivotUp n xs | 643 | pivotUp n xs |
636 | | n == -1 = [] | 644 | | n == -1 = [] |
637 | | otherwise = y : pivotUp (n-1) ys | 645 | | otherwise = y : pivotUp (n-1) ys |
638 | where | 646 | where |
639 | y:ys = redu' (n,xs) | 647 | y:ys = redu' (n,xs) |
640 | 648 | ||
649 | redu' :: (Int, [Vector t]) -> [Vector t] | ||
641 | redu' (k,x:zs) = u : map f zs | 650 | redu' (k,x:zs) = u : map f zs |
642 | where | 651 | where |
643 | u = x | 652 | u = x |