{-# LANGUAGE Safe #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Copilot.Language.Operators.BitWise
( Bits ((.&.), complement, (.|.))
, (.^.)
, (.<<.)
, (.>>.)
) where
import Copilot.Core (Typed, typeOf)
import qualified Copilot.Core as Core
import Copilot.Language.Stream
import qualified Prelude as P
import Data.Bits
instance (Typed a, Bits a) => Bits (Stream a) where
.&. :: Stream a -> Stream a -> Stream a
(.&.) = forall a b c.
(Typed a, Typed b, Typed c) =>
Op2 a b c -> Stream a -> Stream b -> Stream c
Op2 (forall a. Bits a => Type a -> Op2 a a a
Core.BwAnd forall a. Typed a => Type a
typeOf)
complement :: Stream a -> Stream a
complement = forall a b. (Typed a, Typed b) => Op1 a b -> Stream a -> Stream b
Op1 (forall a. Bits a => Type a -> Op1 a a
Core.BwNot forall a. Typed a => Type a
typeOf)
.|. :: Stream a -> Stream a -> Stream a
(.|.) = forall a b c.
(Typed a, Typed b, Typed c) =>
Op2 a b c -> Stream a -> Stream b -> Stream c
Op2 (forall a. Bits a => Type a -> Op2 a a a
Core.BwOr forall a. Typed a => Type a
typeOf)
xor :: Stream a -> Stream a -> Stream a
xor = forall a b c.
(Typed a, Typed b, Typed c) =>
Op2 a b c -> Stream a -> Stream b -> Stream c
Op2 (forall a. Bits a => Type a -> Op2 a a a
Core.BwXor forall a. Typed a => Type a
typeOf)
shiftL :: Stream a -> Int -> Stream a
shiftL = forall a. HasCallStack => [Char] -> a
P.error [Char]
"shiftL undefined, for left-shifting use .<<."
shiftR :: Stream a -> Int -> Stream a
shiftR = forall a. HasCallStack => [Char] -> a
P.error [Char]
"shiftR undefined, for right-shifting use .>>."
rotate :: Stream a -> Int -> Stream a
rotate = forall a. HasCallStack => [Char] -> a
P.error [Char]
"tbd: rotate"
bitSize :: Stream a -> Int
bitSize = forall a. HasCallStack => [Char] -> a
P.error [Char]
"tbd: bitSize"
bitSizeMaybe :: Stream a -> Maybe Int
bitSizeMaybe = forall a. HasCallStack => [Char] -> a
P.error [Char]
"tbd: bitSizeMaybe"
isSigned :: Stream a -> Bool
isSigned = forall a. HasCallStack => [Char] -> a
P.error [Char]
"tbd: issigned"
testBit :: Stream a -> Int -> Bool
testBit = forall a. HasCallStack => [Char] -> a
P.error [Char]
"tbd: testBit"
bit :: Int -> Stream a
bit = forall a. HasCallStack => [Char] -> a
P.error [Char]
"tbd: bit"
popCount :: Stream a -> Int
popCount = forall a. HasCallStack => [Char] -> a
P.error [Char]
"tbd: popCount"
(.^.) :: Bits a => a -> a -> a
.^. :: forall a. Bits a => a -> a -> a
(.^.) = forall a. Bits a => a -> a -> a
xor
(.<<.) :: (Bits a, Typed a, Typed b, P.Integral b)
=> Stream a -> Stream b -> Stream a
.<<. :: forall a b.
(Bits a, Typed a, Typed b, Integral b) =>
Stream a -> Stream b -> Stream a
(.<<.) = forall a b c.
(Typed a, Typed b, Typed c) =>
Op2 a b c -> Stream a -> Stream b -> Stream c
Op2 (forall a b. (Bits a, Integral b) => Type a -> Type b -> Op2 a b a
Core.BwShiftL forall a. Typed a => Type a
typeOf forall a. Typed a => Type a
typeOf)
(.>>.) :: (Bits a, Typed a, Typed b, P.Integral b)
=> Stream a -> Stream b -> Stream a
.>>. :: forall a b.
(Bits a, Typed a, Typed b, Integral b) =>
Stream a -> Stream b -> Stream a
(.>>.) = forall a b c.
(Typed a, Typed b, Typed c) =>
Op2 a b c -> Stream a -> Stream b -> Stream c
Op2 (forall a b. (Bits a, Integral b) => Type a -> Type b -> Op2 a b a
Core.BwShiftR forall a. Typed a => Type a
typeOf forall a. Typed a => Type a
typeOf)