Skip to content

Commit

Permalink
Added workaround for GHC 8.0.1
Browse files Browse the repository at this point in the history
  • Loading branch information
Hiromi ISHII committed Aug 2, 2016
1 parent 809a9fe commit 5dd837d
Show file tree
Hide file tree
Showing 4 changed files with 6 additions and 5 deletions.
4 changes: 2 additions & 2 deletions algebra.cabal
Expand Up @@ -51,8 +51,8 @@ library
mtl >= 2.0.1 && < 2.3,
nats >= 0.1 && < 2,
semigroups >= 0.9 && < 1,
semigroupoids >= 4 && < 5,
transformers >= 0.2 && < 0.5,
semigroupoids >= 4 && < 6,
transformers >= 0.2 && < 0.6,
tagged >= 0.4.2 && < 1,
void >= 0.5.5.1 && < 1

Expand Down
1 change: 1 addition & 0 deletions src/Numeric/Decidable/Units.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE ConstrainedClassMethods #-}
module Numeric.Decidable.Units
( DecidableUnits(..)
, recipUnitIntegral
Expand Down
4 changes: 2 additions & 2 deletions src/Numeric/Domain/Euclidean.hs
Expand Up @@ -11,9 +11,9 @@ import Numeric.Domain.Class
import Numeric.Natural (Natural)
import Numeric.Ring.Class
import Prelude (Eq (..), Integer, Maybe (..), abs)
import Prelude (fst, otherwise)
import Prelude (fst, otherwise, fail)
import Prelude (signum, snd, ($), (.))
import qualified Prelude as P
import qualified Prelude as P

infixl 7 `quot`, `rem`
infix 7 `divide`
Expand Down
2 changes: 1 addition & 1 deletion src/Numeric/Quadrance/Class.hs
Expand Up @@ -19,7 +19,7 @@ class Additive r => Quadrance r m where
instance Quadrance () a where
quadrance _ = ()

instance Monoidal r => Quadrance r () where
instance (Additive r, Monoidal r) => Quadrance r () where
quadrance _ = zero

instance (Quadrance r a, Quadrance r b) => Quadrance r (a,b) where
Expand Down

0 comments on commit 5dd837d

Please sign in to comment.