dph-base-0.3: Basic Definitions for Data-Parallel Haskell.ContentsIndex
Data.Array.Parallel.Base
Portabilitynon-portable (unboxed values and GHC libraries)
Stabilityinternal
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Contents
Strict pairs
Strict sums
Strict Maybe
Lazy wrapper
Class of hyperstrict types
Description
Interface to the Base modules
Synopsis
check :: String -> Int -> Int -> a -> a
checkCritical :: String -> Int -> Int -> a -> a
checkLen :: String -> Int -> Int -> a -> a
checkEq :: (Eq a, Show a) => String -> String -> a -> a -> b -> b
checkNotEmpty :: String -> Int -> a -> a
uninitialised :: String -> a
data a :*: b = !a :*: !b
fstS :: (a :*: b) -> a
sndS :: (a :*: b) -> b
pairS :: (a, b) -> a :*: b
unpairS :: (a :*: b) -> (a, b)
curryS :: ((a :*: b) -> c) -> a -> b -> c
uncurryS :: (a -> b -> c) -> (a :*: b) -> c
unsafe_pairS :: (a, b) -> a :*: b
unsafe_unpairS :: (a :*: b) -> (a, b)
data EitherS a b
= LeftS !a
| RightS !b
data MaybeS a
= NothingS
| JustS !a
maybeS :: b -> (a -> b) -> MaybeS a -> b
fromMaybeS :: a -> MaybeS a -> a
data Lazy a = Lazy a
class HS a
fromBool :: Num a => Bool -> a
toBool :: Num a => a -> Bool
showsApp :: Show a => Int -> String -> a -> ShowS
readApp :: Read a => String -> ReadPrec a
readsApp :: Read a => Int -> String -> ReadS a
class Rebox a where
rebox :: a -> a
dseq :: a -> b -> b
newtype Box a = Box a
Documentation
check :: String -> Int -> Int -> a -> a
checkCritical :: String -> Int -> Int -> a -> a
checkLen :: String -> Int -> Int -> a -> a
checkEq :: (Eq a, Show a) => String -> String -> a -> a -> b -> b
checkNotEmpty :: String -> Int -> a -> a
uninitialised :: String -> a
Strict pairs
data a :*: b
Strict pair
Constructors
!a :*: !b
show/hide Instances
(Eq a, Eq b) => Eq (a :*: b)
(Ord a, Ord b) => Ord (a :*: b)
(Read a, Read b) => Read (a :*: b)
(Show a, Show b) => Show (a :*: b)
(HS a, HS b) => HS (a :*: b)
(Rebox a, Rebox b) => Rebox (a :*: b)
fstS :: (a :*: b) -> a
sndS :: (a :*: b) -> b
pairS :: (a, b) -> a :*: b
unpairS :: (a :*: b) -> (a, b)
curryS :: ((a :*: b) -> c) -> a -> b -> c
uncurryS :: (a -> b -> c) -> (a :*: b) -> c
unsafe_pairS :: (a, b) -> a :*: b

Same as pairS but comes with the unsafe rule

 unsafe_unpairS . unsafe_pairS = id
unsafe_unpairS :: (a :*: b) -> (a, b)

Same as unpairS but comes with the unsafe rule

 unsafe_unpairS . unsafe_pairS = id
Strict sums
data EitherS a b
Strict sum
Constructors
LeftS !a
RightS !b
show/hide Instances
(HS a, HS b) => HS (EitherS a b)
(Rebox a, Rebox b) => Rebox (EitherS a b)
Strict Maybe
data MaybeS a
Strict Maybe
Constructors
NothingS
JustS !a
show/hide Instances
maybeS :: b -> (a -> b) -> MaybeS a -> b
fromMaybeS :: a -> MaybeS a -> a
Lazy wrapper
data Lazy a
Constructors
Lazy a
show/hide Instances
Functor Lazy
Eq a => Eq (Lazy a)
Ord a => Ord (Lazy a)
Read a => Read (Lazy a)
Show a => Show (Lazy a)
Rebox (Lazy a)
Class of hyperstrict types
class HS a
The class of hyperstrict types. These are those types for which weak head-normal form and normal form are the same. That is, once they are evaluated to WHNF, they are guaranteed to contain no thunks
show/hide Instances
HS Bool
HS Char
HS Double
HS Float
HS Int
HS Word8
HS ()
HS a => HS (MaybeS a)
HS e => HS (BUArr e)
HS e => HS (BBArr e)
(HS a, HS b) => HS (EitherS a b)
(HS a, HS b) => HS (a :*: b)
HS e => HS (MBUArr s e)
fromBool :: Num a => Bool -> a
toBool :: Num a => a -> Bool
showsApp :: Show a => Int -> String -> a -> ShowS
readApp :: Read a => String -> ReadPrec a
readsApp :: Read a => Int -> String -> ReadS a
class Rebox a where
Methods
rebox :: a -> a
dseq :: a -> b -> b
show/hide Instances
newtype Box a
Constructors
Box a
show/hide Instances
Produced by Haddock version 2.3.0