{-# LANGUAGE CPP #-}
#if MIN_VERSION_base(4,6,0)
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeOperators #-}
#endif
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.Semiring.Generic
(
#if MIN_VERSION_base(4,6,0)
GSemiring(..)
, gzero
, gone
, gplus
, gtimes
, GRing(..)
, gnegate
, GenericSemiring(..)
#endif
) where
#if MIN_VERSION_base(4,6,0)
import Data.Semiring
import GHC.Generics
import Prelude hiding (Num(..))
newtype GenericSemiring a = GenericSemiring a
deriving (Generic)
instance (Semiring a) => Semiring (GenericSemiring a) where
zero = gzero; one = gone; plus = gplus; times = gtimes;
instance (Semiring a, Semiring b) => Semiring (a,b) where
zero = gzero; one = gone; plus = gplus; times = gtimes;
instance (Semiring a, Semiring b, Semiring c) => Semiring (a,b,c) where
zero = gzero; one = gone; plus = gplus; times = gtimes;
instance (Semiring a, Semiring b, Semiring c, Semiring d) => Semiring (a,b,c,d) where
zero = gzero; one = gone; plus = gplus; times = gtimes;
instance (Semiring a, Semiring b, Semiring c, Semiring d, Semiring e) => Semiring (a,b,c,d,e) where
zero = gzero; one = gone; plus = gplus; times = gtimes;
instance (Semiring a, Semiring b, Semiring c, Semiring d, Semiring e, Semiring f) => Semiring (a,b,c,d,e,f) where
zero = gzero; one = gone; plus = gplus; times = gtimes;
instance (Semiring a, Semiring b, Semiring c, Semiring d, Semiring e, Semiring f, Semiring g) => Semiring (a,b,c,d,e,f,g) where
zero = gzero; one = gone; plus = gplus; times = gtimes;
instance (Ring a, Ring b) => Ring (a,b) where
negate = gnegate
instance (Ring a, Ring b, Ring c) => Ring (a,b,c) where
negate = gnegate
instance (Ring a, Ring b, Ring c, Ring d) => Ring (a,b,c,d) where
negate = gnegate
instance (Ring a, Ring b, Ring c, Ring d, Ring e) => Ring (a,b,c,d,e) where
negate = gnegate
instance (Ring a, Ring b, Ring c, Ring d, Ring e, Ring f) => Ring (a,b,c,d,e,f) where
negate = gnegate
instance (Ring a, Ring b, Ring c, Ring d, Ring e, Ring f, Ring g) => Ring (a,b,c,d,e,f,g) where
negate = gnegate
class GSemiring f where
#if __GLASGOW_HASKELL__ >= 708
{-# MINIMAL gplus', gzero', gtimes', gone' #-}
#endif
gzero' :: f a
gone' :: f a
gplus' :: f a -> f a -> f a
gtimes' :: f a -> f a -> f a
class GRing f where
#if __GLASGOW_HASKELL__ >= 708
{-# MINIMAL gnegate' #-}
#endif
gnegate' :: f a -> f a
gzero :: (Generic a, GSemiring (Rep a)) => a
gzero = to gzero'
gone :: (Generic a, GSemiring (Rep a)) => a
gone = to gone'
gplus :: (Generic a, GSemiring (Rep a)) => a -> a -> a
gplus x y = to $ from x `gplus'` from y
gtimes :: (Generic a, GSemiring (Rep a)) => a -> a -> a
gtimes x y = to $ from x `gtimes'` from y
gnegate :: (Generic a, GRing (Rep a)) => a -> a
gnegate x = to $ gnegate' $ from x
instance GSemiring U1 where
gzero' = U1
gone' = U1
gplus' _ _ = U1
gtimes' _ _ = U1
instance GRing U1 where
gnegate' _ = U1
instance (GSemiring a, GSemiring b) => GSemiring (a :*: b) where
gzero' = gzero' :*: gzero'
gone' = gone' :*: gone'
gplus' (a :*: b) (c :*: d) = gplus' a c :*: gplus' b d
gtimes' (a :*: b) (c :*: d) = gtimes' a c :*: gplus' b d
instance (GRing a, GRing b) => GRing (a :*: b) where
gnegate' (a :*: b) = gnegate' a :*: gnegate' b
instance (GSemiring a) => GSemiring (M1 i c a) where
gzero' = M1 gzero'
gone' = M1 gone'
gplus' (M1 x) (M1 y) = M1 $ gplus' x y
gtimes' (M1 x) (M1 y) = M1 $ gtimes' x y
instance (GRing a) => GRing (M1 i c a) where
gnegate' (M1 x) = M1 $ gnegate' x
instance (Semiring a) => GSemiring (K1 i a) where
gzero' = K1 zero
gone' = K1 one
gplus' (K1 x) (K1 y) = K1 $ plus x y
gtimes' (K1 x) (K1 y) = K1 $ times x y
instance (Ring a) => GRing (K1 i a) where
gnegate' (K1 x) = K1 $ negate x
#endif