{-# language BangPatterns #-}
{-# language DataKinds #-}
{-# language LambdaCase #-}
{-# language MagicHash #-}
{-# language UnboxedTuples #-}

-- This provides an interface to bytearrays in which every
-- boolean is represented by a full byte, not a bit. This
-- can waste space, so depending on your use case, you may
-- want something different.
module Basics.Bool
  ( -- Types
    T
  , T#
  , R
    -- Lifting
  , lift
  , unlift
    -- Compare
  , eq#
  , neq#
    -- Array
  , read#
  , write#
  , index#
  , set#
  , uninitialized#
  , initialized#
  , copy#
  , copyMutable#
  , shrink#
    -- Constants
  , def
    -- Metadata
  , size
    -- Encoding
  , shows
  ) where

import Prelude hiding (shows)

import GHC.Exts (RuntimeRep(IntRep))
import GHC.Exts (Int#,State#,MutableByteArray#,ByteArray#)

import qualified Prelude
import qualified GHC.Exts as Exts

type T = Bool
type T# = Int#
type R = 'IntRep

def :: T
{-# inline def #-}
def :: T
def = T
False

size :: Int
{-# inline size #-}
size :: Int
size = Int
1

lift :: T# -> T
{-# inline lift #-}
lift :: T# -> T
lift T#
x = forall a. T# -> a
Exts.tagToEnum# T#
x :: Bool

unlift :: T -> T#
{-# inline unlift #-}
unlift :: T -> T#
unlift = \case
  T
True -> T#
1#
  T
False -> T#
0#

eq# :: Int# -> Int# -> Int#
{-# inline eq# #-}
eq# :: T# -> T# -> T#
eq# = T# -> T# -> T#
(Exts.==#)

neq# :: Int# -> Int# -> Int#
{-# inline neq# #-}
neq# :: T# -> T# -> T#
neq# = T# -> T# -> T#
(Exts./=#)

index# :: ByteArray# -> Int# -> T#
{-# inline index# #-}
index# :: ByteArray# -> T# -> T#
index# ByteArray#
arr T#
i = Int8# -> T#
Exts.int8ToInt# (ByteArray# -> T# -> Int8#
Exts.indexInt8Array# ByteArray#
arr T#
i)

read# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, T# #)
{-# inline read# #-}
read# :: forall s.
MutableByteArray# s -> T# -> State# s -> (# State# s, T# #)
read# MutableByteArray# s
arr T#
i State# s
st =
  let !(# State# s
st', Int8#
v #) = forall d.
MutableByteArray# d -> T# -> State# d -> (# State# d, Int8# #)
Exts.readInt8Array# MutableByteArray# s
arr T#
i State# s
st
   in (# State# s
st', Int8# -> T#
Exts.int8ToInt# Int8#
v #)

write# :: MutableByteArray# s -> Int# -> T# -> State# s -> State# s
{-# inline write# #-}
write# :: forall s. MutableByteArray# s -> T# -> T# -> State# s -> State# s
write# MutableByteArray# s
arr T#
i T#
v State# s
st = forall d.
MutableByteArray# d -> T# -> Int8# -> State# d -> State# d
Exts.writeInt8Array# MutableByteArray# s
arr T#
i (T# -> Int8#
Exts.intToInt8# T#
v) State# s
st

set# :: MutableByteArray# s -> Int# -> Int# -> T# -> State# s -> State# s
{-# inline set# #-}
set# :: forall s.
MutableByteArray# s -> T# -> T# -> T# -> State# s -> State# s
set# = forall s.
MutableByteArray# s -> T# -> T# -> T# -> State# s -> State# s
Exts.setByteArray#

shrink# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
{-# inline shrink# #-}
shrink# :: forall s.
MutableByteArray# s
-> T# -> State# s -> (# State# s, MutableByteArray# s #)
shrink# MutableByteArray# s
m T#
i State# s
s = (# forall d. MutableByteArray# d -> T# -> State# d -> State# d
Exts.shrinkMutableByteArray# MutableByteArray# s
m T#
i State# s
s, MutableByteArray# s
m #)

uninitialized# :: Int# -> State# s -> (# State# s, MutableByteArray# s #)
{-# inline uninitialized# #-}
uninitialized# :: forall s. T# -> State# s -> (# State# s, MutableByteArray# s #)
uninitialized# = forall s. T# -> State# s -> (# State# s, MutableByteArray# s #)
Exts.newByteArray#

initialized# :: Int# -> T# -> State# s -> (# State# s, MutableByteArray# s #)
{-# inline initialized# #-}
initialized# :: forall s.
T# -> T# -> State# s -> (# State# s, MutableByteArray# s #)
initialized# T#
n T#
e State# s
s0 = case forall s. T# -> State# s -> (# State# s, MutableByteArray# s #)
Exts.newByteArray# T#
n State# s
s0 of
  (# State# s
s1, MutableByteArray# s
a #) -> case forall s.
MutableByteArray# s -> T# -> T# -> T# -> State# s -> State# s
set# MutableByteArray# s
a T#
0# T#
n T#
e State# s
s1 of
    State# s
s2 -> (# State# s
s2, MutableByteArray# s
a #)

copy# :: MutableByteArray# s -> Int# -> ByteArray# -> Int# -> Int# -> State# s -> State# s
{-# inline copy# #-}
copy# :: forall s.
MutableByteArray# s
-> T# -> ByteArray# -> T# -> T# -> State# s -> State# s
copy# MutableByteArray# s
dst T#
doff ByteArray#
src T#
soff T#
len =
  forall d.
ByteArray#
-> T# -> MutableByteArray# d -> T# -> T# -> State# d -> State# d
Exts.copyByteArray# ByteArray#
src T#
soff MutableByteArray# s
dst T#
doff T#
len

copyMutable# :: MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
{-# inline copyMutable# #-}
copyMutable# :: forall s.
MutableByteArray# s
-> T# -> MutableByteArray# s -> T# -> T# -> State# s -> State# s
copyMutable# MutableByteArray# s
dst T#
doff MutableByteArray# s
src T#
soff T#
len =
  forall s.
MutableByteArray# s
-> T# -> MutableByteArray# s -> T# -> T# -> State# s -> State# s
Exts.copyMutableByteArray# MutableByteArray# s
src T#
soff MutableByteArray# s
dst T#
doff T#
len

shows :: T -> String -> String
shows :: T -> String -> String
shows = forall a. Show a => a -> String -> String
Prelude.shows