{-# LANGUAGE ParallelArrays #-} {-# OPTIONS_GHC -fvectorise #-} -- NB: Cannot use any parallel array syntax except the type constructor module Data.Array.Parallel.Prelude.Bool ( Bool(..), otherwise, (&&), (||), not, andP, orP, -- FIXME: the Simplifier drops these bindings *after* vectorisation if not exported (although, -- they are referenced in the code generated by the vectoriser) and_l, or_l, not_l ) where import Data.Array.Parallel.VectDepend () -- see Note [Vectoriser dependencies] in the same module import Data.Array.Parallel.PArr () import Data.Array.Parallel.Lifted.Closure import Data.Array.Parallel.PArray.PReprInstances import Data.Array.Parallel.Lifted.Scalar import qualified Data.Array.Parallel.Unlifted as U import qualified Prelude as P import Prelude (Bool(..), otherwise) -- NB: re-export 'Prelude.otherwise' instead of rolling a new one as the former is special-cased -- in the Desugarer import Data.Bits infixr 3 && infixr 2 || (&&) :: Bool -> Bool -> Bool (&&) = (P.&&) {-# VECTORISE (&&) = closure2 (P.&&) and_l #-} and_l :: PArray Bool -> PArray Bool -> PArray Bool {-# INLINE and_l #-} and_l (PArray n# bs) (PArray _ cs) = PArray n# P.$ case bs of { PBool sel1 -> case cs of { PBool sel2 -> PBool P.$ U.tagsToSel2 (U.zipWith (.&.) (U.tagsSel2 sel1) (U.tagsSel2 sel2)) }} {-# NOVECTORISE and_l #-} (||) :: Bool -> Bool -> Bool (||) = (P.||) {-# VECTORISE (||) = closure2 (P.||) or_l #-} or_l :: PArray Bool -> PArray Bool -> PArray Bool {-# INLINE or_l #-} or_l (PArray n# bs) (PArray _ cs) = PArray n# P.$ case bs of { PBool sel1 -> case cs of { PBool sel2 -> PBool P.$ U.tagsToSel2 (U.zipWith (.|.) (U.tagsSel2 sel1) (U.tagsSel2 sel2)) }} {-# NOVECTORISE or_l #-} not :: Bool -> Bool not = P.not {-# VECTORISE not = closure1 P.not not_l #-} not_l :: PArray Bool -> PArray Bool {-# INLINE not_l #-} not_l (PArray n# bs) = PArray n# P.$ case bs of { PBool sel -> PBool P.$ U.tagsToSel2 (U.map complement (U.tagsSel2 sel)) } {-# NOVECTORISE not_l #-} andP:: [:Bool:] -> Bool {-# NOINLINE andP #-} andP _ = True {-# VECTORISE andP = closure1 (scalar_fold (&&) True) (scalar_folds (&&) True) #-} orP:: [:Bool:] -> Bool {-# NOINLINE orP #-} orP _ = True {-# VECTORISE orP = closure1 (scalar_fold (||) False) (scalar_folds (||) False) #-}