{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module Biobase.Types.Energy where

import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Generic.Mutable as VGM
import Data.Primitive.Types

import Biobase.Types.Ring



-- | Some default instances. Left out the Num one, so that you have to
-- explicitly instanciate if you want to go around the Ring structure.

newtype Energy = Energy {unEnergy :: Int}
  deriving (Show, Read, Eq, Ord)



-- | Ring operations over Energy values.

instance Ring Energy where
  (Energy a) .+. (Energy b) = Energy $ a `min` b
  {-# INLINE (.+.) #-}
  (Energy a) .*. (Energy b) = Energy $ a + b
  {-# INLINE (.*.) #-}
  (Energy a) .^. k = Energy $ a * k
  {-# INLINE (.^.) #-}
  (Energy a) .^^. k = Energy . round $ fromIntegral a * k
  {-# INLINE (.^^.) #-}
  neg (Energy a) = Energy $ negate a
  {-# INLINE neg #-}
  one = Energy 0
  {-# INLINE one #-}
  zero = Energy 10000000
  {-# INLINE zero #-}
  isZero (Energy a) = a >= 1000000
  {-# INLINE isZero #-}



-- * Vector instances.

deriving instance VGM.MVector VU.MVector Energy
deriving instance VG.Vector VU.Vector Energy
deriving instance VU.Unbox Energy
deriving instance Prim Energy