| Copyright | [2018..2020] The Accelerate Team |
|---|---|
| License | BSD3 |
| Maintainer | Trevor L. McDonell <trevor.mcdonell@gmail.com> |
| Stability | experimental |
| Portability | non-portable (GHC extensions) |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.Array.Accelerate.Data.Either
Contents
Description
Since: 1.2.0.0
Synopsis
- data Either a b
- pattern Left_ :: forall a b. (HasCallStack, Elt a, Elt b) => Exp a -> Exp (Either a b)
- pattern Right_ :: forall a b. (HasCallStack, Elt a, Elt b) => Exp b -> Exp (Either a b)
- either :: (Elt a, Elt b, Elt c) => (Exp a -> Exp c) -> (Exp b -> Exp c) -> Exp (Either a b) -> Exp c
- isLeft :: (Elt a, Elt b) => Exp (Either a b) -> Exp Bool
- isRight :: (Elt a, Elt b) => Exp (Either a b) -> Exp Bool
- fromLeft :: (Elt a, Elt b) => Exp (Either a b) -> Exp a
- fromRight :: (Elt a, Elt b) => Exp (Either a b) -> Exp b
- lefts :: (Shape sh, Slice sh, Elt a, Elt b) => Acc (Array (sh :. Int) (Either a b)) -> Acc (Vector a, Array sh Int)
- rights :: (Shape sh, Slice sh, Elt a, Elt b) => Acc (Array (sh :. Int) (Either a b)) -> Acc (Vector b, Array sh Int)
Documentation
The Either type represents values with two possibilities: a value of
type is either Either a b or Left a.Right b
The Either type is sometimes used to represent a value which is
either correct or an error; by convention, the Left constructor is
used to hold an error value and the Right constructor is used to
hold a correct value (mnemonic: "right" also means "correct").
Examples
The type is the type of values which can be either
a Either String IntString or an Int. The Left constructor can be used only on
Strings, and the Right constructor can be used only on Ints:
>>>let s = Left "foo" :: Either String Int>>>sLeft "foo">>>let n = Right 3 :: Either String Int>>>nRight 3>>>:type ss :: Either String Int>>>:type nn :: Either String Int
The fmap from our Functor instance will ignore Left values, but
will apply the supplied function to values contained in a Right:
>>>let s = Left "foo" :: Either String Int>>>let n = Right 3 :: Either String Int>>>fmap (*2) sLeft "foo">>>fmap (*2) nRight 6
The Monad instance for Either allows us to chain together multiple
actions which may fail, and fail overall if any of the individual
steps failed. First we'll write a function that can either parse an
Int from a Char, or fail.
>>>import Data.Char ( digitToInt, isDigit )>>>:{let parseEither :: Char -> Either String Int parseEither c | isDigit c = Right (digitToInt c) | otherwise = Left "parse error">>>:}
The following should work, since both '1' and '2' can be
parsed as Ints.
>>>:{let parseMultiple :: Either String Int parseMultiple = do x <- parseEither '1' y <- parseEither '2' return (x + y)>>>:}
>>>parseMultipleRight 3
But the following should fail overall, since the first operation where
we attempt to parse 'm' as an Int will fail:
>>>:{let parseMultiple :: Either String Int parseMultiple = do x <- parseEither 'm' y <- parseEither '2' return (x + y)>>>:}
>>>parseMultipleLeft "parse error"
Instances
| Eq2 Either | Since: base-4.9.0.0 |
| Ord2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
| Read2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] # | |
| Show2 Either | Since: base-4.9.0.0 |
| NFData2 Either | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
| Hashable2 Either | |
| Generic1 (Either a :: Type -> Type) | |
| (Lift Exp a, Lift Exp b, Elt (Plain a), Elt (Plain b)) => Lift Exp (Either a b) Source # | |
| (Lift a, Lift b) => Lift (Either a b :: Type) | |
| Elt a => Monad (Either a) Source # | |
| Elt a => Functor (Either a) Source # | |
Defined in Data.Array.Accelerate.Data.Either | |
| MonadFix (Either e) | Since: base-4.3.0.0 |
Defined in Control.Monad.Fix | |
| Foldable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Either a m -> m # foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> Either a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 # toList :: Either a a0 -> [a0] # length :: Either a a0 -> Int # elem :: Eq a0 => a0 -> Either a a0 -> Bool # maximum :: Ord a0 => Either a a0 -> a0 # minimum :: Ord a0 => Either a a0 -> a0 # | |
| Eq a => Eq1 (Either a) | Since: base-4.9.0.0 |
| Ord a => Ord1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
| Read a => Read1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] # | |
| Show a => Show1 (Either a) | Since: base-4.9.0.0 |
| Traversable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
| Applicative (Either e) | Since: base-3.0 |
| Functor (Either a) | Since: base-3.0 |
| Monad (Either e) | Since: base-4.4.0.0 |
| (Elt a, Elt b) => Semigroup (Exp (Either a b)) Source # | |
| NFData a => NFData1 (Either a) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
| e ~ SomeException => MonadCatch (Either e) | Since: exceptions-0.8.3 |
| e ~ SomeException => MonadMask (Either e) | Since: exceptions-0.8.3 |
Defined in Control.Monad.Catch | |
| e ~ SomeException => MonadThrow (Either e) | |
Defined in Control.Monad.Catch | |
| Hashable a => Hashable1 (Either a) | |
Defined in Data.Hashable.Class | |
| MonadBaseControl (Either e) (Either e) | |
| (Eq a, Eq b) => Eq (Either a b) Source # | |
| (Ord a, Ord b) => Ord (Either a b) Source # | |
Defined in Data.Array.Accelerate.Data.Either Methods (<) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # (>) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # (<=) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # (>=) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # min :: Exp (Either a b) -> Exp (Either a b) -> Exp (Either a b) Source # max :: Exp (Either a b) -> Exp (Either a b) -> Exp (Either a b) Source # compare :: Exp (Either a b) -> Exp (Either a b) -> Exp Ordering Source # | |
| (Elt a, Elt b) => Elt (Either a b) Source # | |
| (Data a, Data b) => Data (Either a b) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Either a b -> c (Either a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) # toConstr :: Either a b -> Constr # dataTypeOf :: Either a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Either a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Either a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) # | |
| Semigroup (Either a b) | Since: base-4.9.0.0 |
| Generic (Either a b) | |
| (Read a, Read b) => Read (Either a b) | Since: base-3.0 |
| (Show a, Show b) => Show (Either a b) | Since: base-3.0 |
| (NFData a, NFData b) => NFData (Either a b) | |
Defined in Control.DeepSeq | |
| (Eq a, Eq b) => Eq (Either a b) | Since: base-2.1 |
| (Ord a, Ord b) => Ord (Either a b) | Since: base-2.1 |
| (Hashable a, Hashable b) => Hashable (Either a b) | |
| (a ~ a', b ~ b') => Each (Either a a') (Either b b') a b | Since: microlens-0.4.11 |
| type Rep1 (Either a :: Type -> Type) | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 (Either a :: Type -> Type) = D1 ('MetaData "Either" "Data.Either" "base" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |
| type StM (Either e) a | |
Defined in Control.Monad.Trans.Control | |
| type Plain (Either a b) Source # | |
| type Rep (Either a b) | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep (Either a b) = D1 ('MetaData "Either" "Data.Either" "base" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))) | |
either :: (Elt a, Elt b, Elt c) => (Exp a -> Exp c) -> (Exp b -> Exp c) -> Exp (Either a b) -> Exp c Source #
lefts :: (Shape sh, Slice sh, Elt a, Elt b) => Acc (Array (sh :. Int) (Either a b)) -> Acc (Vector a, Array sh Int) Source #
rights :: (Shape sh, Slice sh, Elt a, Elt b) => Acc (Array (sh :. Int) (Either a b)) -> Acc (Vector b, Array sh Int) Source #
Orphan instances
| (Lift Exp a, Lift Exp b, Elt (Plain a), Elt (Plain b)) => Lift Exp (Either a b) Source # | |
| Elt a => Monad (Either a) Source # | |
| Elt a => Functor (Either a) Source # | |
| (Elt a, Elt b) => Semigroup (Exp (Either a b)) Source # | |
| (Eq a, Eq b) => Eq (Either a b) Source # | |
| (Ord a, Ord b) => Ord (Either a b) Source # | |
Methods (<) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # (>) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # (<=) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # (>=) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # min :: Exp (Either a b) -> Exp (Either a b) -> Exp (Either a b) Source # max :: Exp (Either a b) -> Exp (Either a b) -> Exp (Either a b) Source # compare :: Exp (Either a b) -> Exp (Either a b) -> Exp Ordering Source # | |