Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Int
- data Float
- data Char
- data IO a
- data Bool
- data Double
- data Word
- data Ordering
- data Maybe a
- class a ~# b => (a :: k) ~ (b :: k)
- data Integer
- data Either a b
- type Rational = Ratio Integer
- type String = [Char]
- class Read a where
- class Show a where
- type IOError = IOException
- class Bounded a where
- class Enum a where
- succ :: a -> a
- pred :: a -> a
- toEnum :: Int -> a
- fromEnum :: a -> Int
- enumFrom :: a -> [a]
- enumFromThen :: a -> a -> [a]
- enumFromTo :: a -> a -> [a]
- enumFromThenTo :: a -> a -> a -> [a]
- class Eq a where
- class Fractional a => Floating a where
- class Num a => Fractional a where
- (/) :: a -> a -> a
- recip :: a -> a
- fromRational :: Rational -> a
- class (Real a, Enum a) => Integral a where
- class Applicative m => Monad (m :: Type -> Type) where
- class Functor (f :: Type -> Type) where
- class Num a where
- class Eq a => Ord a where
- class (Num a, Ord a) => Real a where
- toRational :: a -> Rational
- class (RealFrac a, Floating a) => RealFloat a where
- floatRadix :: a -> Integer
- floatDigits :: a -> Int
- floatRange :: a -> (Int, Int)
- decodeFloat :: a -> (Integer, Int)
- encodeFloat :: Integer -> Int -> a
- exponent :: a -> Int
- significand :: a -> a
- scaleFloat :: Int -> a -> a
- isNaN :: a -> Bool
- isInfinite :: a -> Bool
- isDenormalized :: a -> Bool
- isNegativeZero :: a -> Bool
- isIEEE :: a -> Bool
- atan2 :: a -> a -> a
- class (Real a, Fractional a) => RealFrac a where
- class Monad m => MonadFail (m :: Type -> Type) where
- class Functor f => Applicative (f :: Type -> Type) where
- class Foldable (t :: Type -> Type) where
- foldMap :: Monoid m => (a -> m) -> t a -> m
- foldr :: (a -> b -> b) -> b -> t a -> b
- foldl :: (b -> a -> b) -> b -> t a -> b
- foldl' :: (b -> a -> b) -> b -> t a -> b
- foldr1 :: (a -> a -> a) -> t a -> a
- foldl1 :: (a -> a -> a) -> t a -> a
- null :: t a -> Bool
- length :: t a -> Int
- elem :: Eq a => a -> t a -> Bool
- maximum :: Ord a => t a -> a
- minimum :: Ord a => t a -> a
- sum :: Num a => t a -> a
- product :: Num a => t a -> a
- class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- sequenceA :: Applicative f => t (f a) -> f (t a)
- mapM :: Monad m => (a -> m b) -> t a -> m (t b)
- sequence :: Monad m => t (m a) -> m (t a)
- class Semigroup a
- class Semigroup a => Monoid a where
- type ShowS = String -> String
- type ReadS a = String -> [(a, String)]
- type FilePath = String
- error :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => [Char] -> a
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- even :: Integral a => a -> Bool
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- ($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b
- fst :: (a, b) -> a
- uncurry :: (a -> b -> c) -> (a, b) -> c
- id :: a -> a
- writeFile :: FilePath -> String -> IO ()
- getLine :: IO String
- putStrLn :: String -> IO ()
- filter :: (a -> Bool) -> [a] -> [a]
- cycle :: HasCallStack => [a] -> [a]
- (++) :: [a] -> [a] -> [a]
- seq :: forall {r :: RuntimeRep} a (b :: TYPE r). a -> b -> b
- concat :: Foldable t => t [a] -> [a]
- zip :: [a] -> [b] -> [(a, b)]
- print :: Show a => a -> IO ()
- otherwise :: Bool
- map :: (a -> b) -> [a] -> [b]
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- (^) :: (Num a, Integral b) => a -> b -> a
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
- errorWithoutStackTrace :: forall (r :: RuntimeRep) (a :: TYPE r). [Char] -> a
- undefined :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => a
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- const :: a -> b -> a
- (.) :: (b -> c) -> (a -> b) -> a -> c
- flip :: (a -> b -> c) -> b -> a -> c
- ($!) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b
- until :: (a -> Bool) -> (a -> a) -> a -> a
- asTypeOf :: a -> a -> a
- subtract :: Num a => a -> a -> a
- maybe :: b -> (a -> b) -> Maybe a -> b
- head :: HasCallStack => [a] -> a
- tail :: HasCallStack => [a] -> [a]
- last :: HasCallStack => [a] -> a
- init :: HasCallStack => [a] -> [a]
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- iterate :: (a -> a) -> a -> [a]
- repeat :: a -> [a]
- replicate :: Int -> a -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- take :: Int -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- splitAt :: Int -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- reverse :: [a] -> [a]
- and :: Foldable t => t Bool -> Bool
- or :: Foldable t => t Bool -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- (!!) :: HasCallStack => [a] -> Int -> a
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- unzip :: [(a, b)] -> ([a], [b])
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- shows :: Show a => a -> ShowS
- showChar :: Char -> ShowS
- showString :: String -> ShowS
- showParen :: Bool -> ShowS -> ShowS
- odd :: Integral a => a -> Bool
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- gcd :: Integral a => a -> a -> a
- lcm :: Integral a => a -> a -> a
- lex :: ReadS String
- readParen :: Bool -> ReadS a -> ReadS a
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- reads :: Read a => ReadS a
- read :: Read a => String -> a
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- snd :: (a, b) -> b
- curry :: ((a, b) -> c) -> a -> b -> c
- lines :: String -> [String]
- unlines :: [String] -> String
- words :: String -> [String]
- unwords :: [String] -> String
- userError :: String -> IOError
- ioError :: IOError -> IO a
- putChar :: Char -> IO ()
- putStr :: String -> IO ()
- getChar :: IO Char
- getContents :: IO String
- interact :: (String -> String) -> IO ()
- readFile :: FilePath -> IO String
- appendFile :: FilePath -> String -> IO ()
- readLn :: Read a => IO a
- readIO :: Read a => String -> IO a
- class Bits b => FiniteBits b where
- finiteBitSize :: b -> Int
- countLeadingZeros :: b -> Int
- countTrailingZeros :: b -> Int
- class Eq a => Bits a where
- (.&.) :: a -> a -> a
- (.|.) :: a -> a -> a
- xor :: a -> a -> a
- complement :: a -> a
- shift :: a -> Int -> a
- rotate :: a -> Int -> a
- zeroBits :: a
- bit :: Int -> a
- setBit :: a -> Int -> a
- clearBit :: a -> Int -> a
- complementBit :: a -> Int -> a
- testBit :: a -> Int -> Bool
- bitSizeMaybe :: a -> Maybe Int
- bitSize :: a -> Int
- isSigned :: a -> Bool
- unsafeShiftL :: a -> Int -> a
- unsafeShiftR :: a -> Int -> a
- rotateL :: a -> Int -> a
- rotateR :: a -> Int -> a
- popCount :: a -> Int
- bitDefault :: (Bits a, Num a) => Int -> a
- testBitDefault :: (Bits a, Num a) => a -> Int -> Bool
- popCountDefault :: (Bits a, Num a) => a -> Int
- toIntegralSized :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b
- shiftL :: Bits a => a -> Int -> a
- shiftR :: Bits a => a -> Int -> a
Documentation
Instances
Data Int | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int -> c Int Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int Source # toConstr :: Int -> Constr Source # dataTypeOf :: Int -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) Source # gmapT :: (forall b. Data b => b -> b) -> Int -> Int Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source # | |
Storable Int | Since: base-2.1 |
Bits Int | Since: base-2.1 |
Defined in GHC.Bits (.&.) :: Int -> Int -> Int Source # (.|.) :: Int -> Int -> Int Source # xor :: Int -> Int -> Int Source # complement :: Int -> Int Source # shift :: Int -> Int -> Int Source # rotate :: Int -> Int -> Int Source # setBit :: Int -> Int -> Int Source # clearBit :: Int -> Int -> Int Source # complementBit :: Int -> Int -> Int Source # testBit :: Int -> Int -> Bool Source # bitSizeMaybe :: Int -> Maybe Int Source # bitSize :: Int -> Int Source # isSigned :: Int -> Bool Source # shiftL :: Int -> Int -> Int Source # unsafeShiftL :: Int -> Int -> Int Source # shiftR :: Int -> Int -> Int Source # unsafeShiftR :: Int -> Int -> Int Source # rotateL :: Int -> Int -> Int Source # | |
FiniteBits Int | Since: base-4.6.0.0 |
Bounded Int | Since: base-2.1 |
Enum Int | Since: base-2.1 |
Defined in GHC.Enum | |
Ix Int | Since: base-2.1 |
Num Int | Since: base-2.1 |
Read Int | Since: base-2.1 |
Integral Int | Since: base-2.0.1 |
Real Int | Since: base-2.0.1 |
Show Int | Since: base-2.1 |
PrintfArg Int | Since: base-2.1 |
Defined in Text.Printf formatArg :: Int -> FieldFormatter Source # parseFormat :: Int -> ModifierParser Source # | |
Binary Int | |
NFData Int | |
Defined in Control.DeepSeq | |
Uniquable Int Source # | |
Binary Int Source # | |
ToJson Int Source # | |
Outputable Int Source # | |
Eq Int | |
Ord Int | |
HpcHash Int | |
IArray UArray Int | |
Defined in Data.Array.Base bounds :: Ix i => UArray i Int -> (i, i) Source # numElements :: Ix i => UArray i Int -> Int unsafeArray :: Ix i => (i, i) -> [(Int, Int)] -> UArray i Int unsafeAt :: Ix i => UArray i Int -> Int -> Int unsafeReplace :: Ix i => UArray i Int -> [(Int, Int)] -> UArray i Int unsafeAccum :: Ix i => (Int -> e' -> Int) -> UArray i Int -> [(Int, e')] -> UArray i Int unsafeAccumArray :: Ix i => (Int -> e' -> Int) -> Int -> (i, i) -> [(Int, e')] -> UArray i Int | |
Lift Int | |
MArray IOUArray Int IO | |
Defined in Data.Array.IO.Internals getBounds :: Ix i => IOUArray i Int -> IO (i, i) Source # getNumElements :: Ix i => IOUArray i Int -> IO Int newArray :: Ix i => (i, i) -> Int -> IO (IOUArray i Int) Source # newArray_ :: Ix i => (i, i) -> IO (IOUArray i Int) Source # unsafeNewArray_ :: Ix i => (i, i) -> IO (IOUArray i Int) unsafeRead :: Ix i => IOUArray i Int -> Int -> IO Int unsafeWrite :: Ix i => IOUArray i Int -> Int -> Int -> IO () | |
Generic1 (URec Int :: k -> Type) | |
Foldable (UInt :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UInt m -> m Source # foldMap :: Monoid m => (a -> m) -> UInt a -> m Source # foldMap' :: Monoid m => (a -> m) -> UInt a -> m Source # foldr :: (a -> b -> b) -> b -> UInt a -> b Source # foldr' :: (a -> b -> b) -> b -> UInt a -> b Source # foldl :: (b -> a -> b) -> b -> UInt a -> b Source # foldl' :: (b -> a -> b) -> b -> UInt a -> b Source # foldr1 :: (a -> a -> a) -> UInt a -> a Source # foldl1 :: (a -> a -> a) -> UInt a -> a Source # toList :: UInt a -> [a] Source # null :: UInt a -> Bool Source # length :: UInt a -> Int Source # elem :: Eq a => a -> UInt a -> Bool Source # maximum :: Ord a => UInt a -> a Source # minimum :: Ord a => UInt a -> a Source # | |
Traversable (UInt :: Type -> Type) | Since: base-4.9.0.0 |
Binary (HieAST TypeIndex) Source # | |
Binary (HieASTs TypeIndex) Source # | |
Binary (HieArgs TypeIndex) Source # | |
Binary (HieType TypeIndex) Source # | |
Binary (IdentifierDetails TypeIndex) Source # | |
Defined in GHC.Iface.Ext.Types | |
Binary (NodeInfo TypeIndex) Source # | |
Binary (SourcedNodeInfo TypeIndex) Source # | |
Defined in GHC.Iface.Ext.Types | |
MArray (STUArray s) Int (ST s) | |
Defined in Data.Array.Base getBounds :: Ix i => STUArray s i Int -> ST s (i, i) Source # getNumElements :: Ix i => STUArray s i Int -> ST s Int newArray :: Ix i => (i, i) -> Int -> ST s (STUArray s i Int) Source # newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int) Source # unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int) unsafeRead :: Ix i => STUArray s i Int -> Int -> ST s Int unsafeWrite :: Ix i => STUArray s i Int -> Int -> Int -> ST s () | |
Functor (URec Int :: Type -> Type) | Since: base-4.9.0.0 |
Generic (URec Int p) | |
Show (URec Int p) | Since: base-4.9.0.0 |
Eq (URec Int p) | Since: base-4.9.0.0 |
Ord (URec Int p) | Since: base-4.9.0.0 |
data URec Int (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Int :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Int p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Instances
Instances
Data Char | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Char -> c Char Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char Source # toConstr :: Char -> Constr Source # dataTypeOf :: Char -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Char) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) Source # gmapT :: (forall b. Data b => b -> b) -> Char -> Char Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source # | |
Storable Char | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Char -> Int Source # alignment :: Char -> Int Source # peekElemOff :: Ptr Char -> Int -> IO Char Source # pokeElemOff :: Ptr Char -> Int -> Char -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Char Source # pokeByteOff :: Ptr b -> Int -> Char -> IO () Source # | |
Bounded Char | Since: base-2.1 |
Enum Char | Since: base-2.1 |
Ix Char | Since: base-2.1 |
Read Char | Since: base-2.1 |
Show Char | Since: base-2.1 |
IsChar Char | Since: base-2.1 |
PrintfArg Char | Since: base-2.1 |
Defined in Text.Printf formatArg :: Char -> FieldFormatter Source # parseFormat :: Char -> ModifierParser Source # | |
Binary Char | |
NFData Char | |
Defined in Control.DeepSeq | |
Binary Char Source # | |
ToJson String Source # | |
Outputable Char Source # | |
Eq Char | |
Ord Char | |
HpcHash Char | |
ErrorList Char | |
IArray UArray Char | |
Defined in Data.Array.Base bounds :: Ix i => UArray i Char -> (i, i) Source # numElements :: Ix i => UArray i Char -> Int unsafeArray :: Ix i => (i, i) -> [(Int, Char)] -> UArray i Char unsafeAt :: Ix i => UArray i Char -> Int -> Char unsafeReplace :: Ix i => UArray i Char -> [(Int, Char)] -> UArray i Char unsafeAccum :: Ix i => (Char -> e' -> Char) -> UArray i Char -> [(Int, e')] -> UArray i Char unsafeAccumArray :: Ix i => (Char -> e' -> Char) -> Char -> (i, i) -> [(Int, e')] -> UArray i Char | |
Lift Char | |
MArray IOUArray Char IO | |
Defined in Data.Array.IO.Internals getBounds :: Ix i => IOUArray i Char -> IO (i, i) Source # getNumElements :: Ix i => IOUArray i Char -> IO Int newArray :: Ix i => (i, i) -> Char -> IO (IOUArray i Char) Source # newArray_ :: Ix i => (i, i) -> IO (IOUArray i Char) Source # unsafeNewArray_ :: Ix i => (i, i) -> IO (IOUArray i Char) unsafeRead :: Ix i => IOUArray i Char -> Int -> IO Char unsafeWrite :: Ix i => IOUArray i Char -> Int -> Char -> IO () | |
Generic1 (URec Char :: k -> Type) | |
Foldable (UChar :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UChar m -> m Source # foldMap :: Monoid m => (a -> m) -> UChar a -> m Source # foldMap' :: Monoid m => (a -> m) -> UChar a -> m Source # foldr :: (a -> b -> b) -> b -> UChar a -> b Source # foldr' :: (a -> b -> b) -> b -> UChar a -> b Source # foldl :: (b -> a -> b) -> b -> UChar a -> b Source # foldl' :: (b -> a -> b) -> b -> UChar a -> b Source # foldr1 :: (a -> a -> a) -> UChar a -> a Source # foldl1 :: (a -> a -> a) -> UChar a -> a Source # toList :: UChar a -> [a] Source # null :: UChar a -> Bool Source # length :: UChar a -> Int Source # elem :: Eq a => a -> UChar a -> Bool Source # maximum :: Ord a => UChar a -> a Source # minimum :: Ord a => UChar a -> a Source # | |
Traversable (UChar :: Type -> Type) | Since: base-4.9.0.0 |
OutputCap [Char] | |
Defined in System.Console.Terminfo.Base | |
TermStr [Char] | |
Defined in System.Console.Terminfo.Base | |
MArray (STUArray s) Char (ST s) | |
Defined in Data.Array.Base getBounds :: Ix i => STUArray s i Char -> ST s (i, i) Source # getNumElements :: Ix i => STUArray s i Char -> ST s Int newArray :: Ix i => (i, i) -> Char -> ST s (STUArray s i Char) Source # newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Char) Source # unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Char) unsafeRead :: Ix i => STUArray s i Char -> Int -> ST s Char unsafeWrite :: Ix i => STUArray s i Char -> Int -> Char -> ST s () | |
Functor (URec Char :: Type -> Type) | Since: base-4.9.0.0 |
Generic (URec Char p) | |
Show (URec Char p) | Since: base-4.9.0.0 |
Eq (URec Char p) | Since: base-4.9.0.0 |
Ord (URec Char p) | Since: base-4.9.0.0 |
data URec Char (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
type Compare (a :: Char) (b :: Char) | |
Defined in Data.Type.Ord | |
type Rep1 (URec Char :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Char p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Instances
Instances
Data Bool | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bool -> c Bool Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool Source # toConstr :: Bool -> Constr Source # dataTypeOf :: Bool -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bool) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) Source # gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool Source # | |
Storable Bool | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Bool -> Int Source # alignment :: Bool -> Int Source # peekElemOff :: Ptr Bool -> Int -> IO Bool Source # pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Bool Source # pokeByteOff :: Ptr b -> Int -> Bool -> IO () Source # | |
Bits Bool | Interpret Since: base-4.7.0.0 |
Defined in GHC.Bits (.&.) :: Bool -> Bool -> Bool Source # (.|.) :: Bool -> Bool -> Bool Source # xor :: Bool -> Bool -> Bool Source # complement :: Bool -> Bool Source # shift :: Bool -> Int -> Bool Source # rotate :: Bool -> Int -> Bool Source # setBit :: Bool -> Int -> Bool Source # clearBit :: Bool -> Int -> Bool Source # complementBit :: Bool -> Int -> Bool Source # testBit :: Bool -> Int -> Bool Source # bitSizeMaybe :: Bool -> Maybe Int Source # bitSize :: Bool -> Int Source # isSigned :: Bool -> Bool Source # shiftL :: Bool -> Int -> Bool Source # unsafeShiftL :: Bool -> Int -> Bool Source # shiftR :: Bool -> Int -> Bool Source # unsafeShiftR :: Bool -> Int -> Bool Source # rotateL :: Bool -> Int -> Bool Source # | |
FiniteBits Bool | Since: base-4.7.0.0 |
Bounded Bool | Since: base-2.1 |
Enum Bool | Since: base-2.1 |
Generic Bool | |
SingKind Bool | Since: base-4.9.0.0 |
Defined in GHC.Generics type DemoteRep Bool | |
Ix Bool | Since: base-2.1 |
Read Bool | Since: base-2.1 |
Show Bool | Since: base-2.1 |
Binary Bool | |
NFData Bool | |
Defined in Control.DeepSeq | |
Binary Bool Source # | |
Outputable Bool Source # | |
Eq Bool | |
Ord Bool | |
HpcHash Bool | |
IArray UArray Bool | |
Defined in Data.Array.Base bounds :: Ix i => UArray i Bool -> (i, i) Source # numElements :: Ix i => UArray i Bool -> Int unsafeArray :: Ix i => (i, i) -> [(Int, Bool)] -> UArray i Bool unsafeAt :: Ix i => UArray i Bool -> Int -> Bool unsafeReplace :: Ix i => UArray i Bool -> [(Int, Bool)] -> UArray i Bool unsafeAccum :: Ix i => (Bool -> e' -> Bool) -> UArray i Bool -> [(Int, e')] -> UArray i Bool unsafeAccumArray :: Ix i => (Bool -> e' -> Bool) -> Bool -> (i, i) -> [(Int, e')] -> UArray i Bool | |
SingI 'False | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
SingI 'True | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Lift Bool | |
MArray IOUArray Bool IO | |
Defined in Data.Array.IO.Internals getBounds :: Ix i => IOUArray i Bool -> IO (i, i) Source # getNumElements :: Ix i => IOUArray i Bool -> IO Int newArray :: Ix i => (i, i) -> Bool -> IO (IOUArray i Bool) Source # newArray_ :: Ix i => (i, i) -> IO (IOUArray i Bool) Source # unsafeNewArray_ :: Ix i => (i, i) -> IO (IOUArray i Bool) unsafeRead :: Ix i => IOUArray i Bool -> Int -> IO Bool unsafeWrite :: Ix i => IOUArray i Bool -> Int -> Bool -> IO () | |
MArray (STUArray s) Bool (ST s) | |
Defined in Data.Array.Base getBounds :: Ix i => STUArray s i Bool -> ST s (i, i) Source # getNumElements :: Ix i => STUArray s i Bool -> ST s Int newArray :: Ix i => (i, i) -> Bool -> ST s (STUArray s i Bool) Source # newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Bool) Source # unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Bool) unsafeRead :: Ix i => STUArray s i Bool -> Int -> ST s Bool unsafeWrite :: Ix i => STUArray s i Bool -> Int -> Bool -> ST s () | |
type DemoteRep Bool | |
Defined in GHC.Generics | |
type Rep Bool | Since: base-4.6.0.0 |
data Sing (a :: Bool) | |
type Anno Bool Source # | |
Defined in GHC.Hs.Decls |
Instances
Instances
Data Word | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word -> c Word Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word Source # toConstr :: Word -> Constr Source # dataTypeOf :: Word -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) Source # gmapT :: (forall b. Data b => b -> b) -> Word -> Word Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source # | |
Storable Word | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Word -> Int Source # alignment :: Word -> Int Source # peekElemOff :: Ptr Word -> Int -> IO Word Source # pokeElemOff :: Ptr Word -> Int -> Word -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Word Source # pokeByteOff :: Ptr b -> Int -> Word -> IO () Source # | |
Bits Word | Since: base-2.1 |
Defined in GHC.Bits (.&.) :: Word -> Word -> Word Source # (.|.) :: Word -> Word -> Word Source # xor :: Word -> Word -> Word Source # complement :: Word -> Word Source # shift :: Word -> Int -> Word Source # rotate :: Word -> Int -> Word Source # setBit :: Word -> Int -> Word Source # clearBit :: Word -> Int -> Word Source # complementBit :: Word -> Int -> Word Source # testBit :: Word -> Int -> Bool Source # bitSizeMaybe :: Word -> Maybe Int Source # bitSize :: Word -> Int Source # isSigned :: Word -> Bool Source # shiftL :: Word -> Int -> Word Source # unsafeShiftL :: Word -> Int -> Word Source # shiftR :: Word -> Int -> Word Source # unsafeShiftR :: Word -> Int -> Word Source # rotateL :: Word -> Int -> Word Source # | |
FiniteBits Word | Since: base-4.6.0.0 |
Bounded Word | Since: base-2.1 |
Enum Word | Since: base-2.1 |
Ix Word | Since: base-4.6.0.0 |
Num Word | Since: base-2.1 |
Read Word | Since: base-4.5.0.0 |
Integral Word | Since: base-2.1 |
Real Word | Since: base-2.1 |
Show Word | Since: base-2.1 |
PrintfArg Word | Since: base-2.1 |
Defined in Text.Printf formatArg :: Word -> FieldFormatter Source # parseFormat :: Word -> ModifierParser Source # | |
Binary Word | |
NFData Word | |
Defined in Control.DeepSeq | |
Outputable Word Source # | |
Eq Word | |
Ord Word | |
IArray UArray Word | |
Defined in Data.Array.Base bounds :: Ix i => UArray i Word -> (i, i) Source # numElements :: Ix i => UArray i Word -> Int unsafeArray :: Ix i => (i, i) -> [(Int, Word)] -> UArray i Word unsafeAt :: Ix i => UArray i Word -> Int -> Word unsafeReplace :: Ix i => UArray i Word -> [(Int, Word)] -> UArray i Word unsafeAccum :: Ix i => (Word -> e' -> Word) -> UArray i Word -> [(Int, e')] -> UArray i Word unsafeAccumArray :: Ix i => (Word -> e' -> Word) -> Word -> (i, i) -> [(Int, e')] -> UArray i Word | |
Lift Word | |
MArray IOUArray Word IO | |
Defined in Data.Array.IO.Internals getBounds :: Ix i => IOUArray i Word -> IO (i, i) Source # getNumElements :: Ix i => IOUArray i Word -> IO Int newArray :: Ix i => (i, i) -> Word -> IO (IOUArray i Word) Source # newArray_ :: Ix i => (i, i) -> IO (IOUArray i Word) Source # unsafeNewArray_ :: Ix i => (i, i) -> IO (IOUArray i Word) unsafeRead :: Ix i => IOUArray i Word -> Int -> IO Word unsafeWrite :: Ix i => IOUArray i Word -> Int -> Word -> IO () | |
Generic1 (URec Word :: k -> Type) | |
Foldable (UWord :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UWord m -> m Source # foldMap :: Monoid m => (a -> m) -> UWord a -> m Source # foldMap' :: Monoid m => (a -> m) -> UWord a -> m Source # foldr :: (a -> b -> b) -> b -> UWord a -> b Source # foldr' :: (a -> b -> b) -> b -> UWord a -> b Source # foldl :: (b -> a -> b) -> b -> UWord a -> b Source # foldl' :: (b -> a -> b) -> b -> UWord a -> b Source # foldr1 :: (a -> a -> a) -> UWord a -> a Source # foldl1 :: (a -> a -> a) -> UWord a -> a Source # toList :: UWord a -> [a] Source # null :: UWord a -> Bool Source # length :: UWord a -> Int Source # elem :: Eq a => a -> UWord a -> Bool Source # maximum :: Ord a => UWord a -> a Source # minimum :: Ord a => UWord a -> a Source # | |
Traversable (UWord :: Type -> Type) | Since: base-4.9.0.0 |
MArray (STUArray s) Word (ST s) | |
Defined in Data.Array.Base getBounds :: Ix i => STUArray s i Word -> ST s (i, i) Source # getNumElements :: Ix i => STUArray s i Word -> ST s Int newArray :: Ix i => (i, i) -> Word -> ST s (STUArray s i Word) Source # newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word) Source # unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word) unsafeRead :: Ix i => STUArray s i Word -> Int -> ST s Word unsafeWrite :: Ix i => STUArray s i Word -> Int -> Word -> ST s () | |
Functor (URec Word :: Type -> Type) | Since: base-4.9.0.0 |
Generic (URec Word p) | |
Show (URec Word p) | Since: base-4.9.0.0 |
Eq (URec Word p) | Since: base-4.9.0.0 |
Ord (URec Word p) | Since: base-4.9.0.0 |
data URec Word (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Word :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Word p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Instances
Data Ordering | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordering -> c Ordering Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering Source # toConstr :: Ordering -> Constr Source # dataTypeOf :: Ordering -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) Source # gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source # | |
Monoid Ordering | Since: base-2.1 |
Semigroup Ordering | Since: base-4.9.0.0 |
Bounded Ordering | Since: base-2.1 |
Enum Ordering | Since: base-2.1 |
Defined in GHC.Enum succ :: Ordering -> Ordering Source # pred :: Ordering -> Ordering Source # toEnum :: Int -> Ordering Source # fromEnum :: Ordering -> Int Source # enumFrom :: Ordering -> [Ordering] Source # enumFromThen :: Ordering -> Ordering -> [Ordering] Source # enumFromTo :: Ordering -> Ordering -> [Ordering] Source # enumFromThenTo :: Ordering -> Ordering -> Ordering -> [Ordering] Source # | |
Generic Ordering | |
Ix Ordering | Since: base-2.1 |
Read Ordering | Since: base-2.1 |
Show Ordering | Since: base-2.1 |
Binary Ordering | |
NFData Ordering | |
Defined in Control.DeepSeq | |
Outputable Ordering Source # | |
Eq Ordering | |
Ord Ordering | |
Defined in GHC.Classes | |
type Rep Ordering | Since: base-4.6.0.0 |
The Maybe
type encapsulates an optional value. A value of type
either contains a value of type Maybe
aa
(represented as
),
or it is empty (represented as Just
aNothing
). Using Maybe
is a good way to
deal with errors or exceptional cases without resorting to drastic
measures such as error
.
The Maybe
type is also a monad. It is a simple kind of error
monad, where all errors are represented by Nothing
. A richer
error monad can be built using the Either
type.
Instances
MonadFail Maybe | Since: base-4.9.0.0 |
MonadFix Maybe | Since: base-2.1 |
Foldable Maybe | Since: base-2.1 |
Defined in Data.Foldable fold :: Monoid m => Maybe m -> m Source # foldMap :: Monoid m => (a -> m) -> Maybe a -> m Source # foldMap' :: Monoid m => (a -> m) -> Maybe a -> m Source # foldr :: (a -> b -> b) -> b -> Maybe a -> b Source # foldr' :: (a -> b -> b) -> b -> Maybe a -> b Source # foldl :: (b -> a -> b) -> b -> Maybe a -> b Source # foldl' :: (b -> a -> b) -> b -> Maybe a -> b Source # foldr1 :: (a -> a -> a) -> Maybe a -> a Source # foldl1 :: (a -> a -> a) -> Maybe a -> a Source # toList :: Maybe a -> [a] Source # null :: Maybe a -> Bool Source # length :: Maybe a -> Int Source # elem :: Eq a => a -> Maybe a -> Bool Source # maximum :: Ord a => Maybe a -> a Source # minimum :: Ord a => Maybe a -> a Source # | |
Eq1 Maybe | Since: base-4.9.0.0 |
Ord1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Maybe a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Maybe a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Maybe a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Maybe a] Source # | |
Show1 Maybe | Since: base-4.9.0.0 |
Traversable Maybe | Since: base-2.1 |
Alternative Maybe | Since: base-2.1 |
Applicative Maybe | Since: base-2.1 |
Functor Maybe | Since: base-2.1 |
Monad Maybe | Since: base-2.1 |
MonadPlus Maybe | Since: base-2.1 |
NFData1 Maybe | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
MonadThrow Maybe | |
Generic1 Maybe | |
OutputableP env a => OutputableP env (Maybe a) Source # | |
Lift a => Lift (Maybe a :: Type) | |
Data a => Data (Maybe a) | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Maybe a -> c (Maybe a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) Source # toConstr :: Maybe a -> Constr Source # dataTypeOf :: Maybe a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe a)) Source # gmapT :: (forall b. Data b => b -> b) -> Maybe a -> Maybe a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Maybe a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) Source # | |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
Generic (Maybe a) | |
SingKind a => SingKind (Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics type DemoteRep (Maybe a) | |
Read a => Read (Maybe a) | Since: base-2.1 |
Show a => Show (Maybe a) | Since: base-2.1 |
Binary a => Binary (Maybe a) | |
NFData a => NFData (Maybe a) | |
Defined in Control.DeepSeq | |
Binary a => Binary (Maybe a) Source # | |
Outputable a => Outputable (Maybe a) Source # | |
Eq (DeBruijn a) => Eq (DeBruijn (Maybe a)) Source # | |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Ord a => Ord (Maybe a) | Since: base-2.1 |
SingI ('Nothing :: Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
SingI a2 => SingI ('Just a2 :: Maybe a1) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep1 Maybe | Since: base-4.6.0.0 |
type DemoteRep (Maybe a) | |
Defined in GHC.Generics | |
type Rep (Maybe a) | Since: base-4.6.0.0 |
Defined in GHC.Generics | |
data Sing (b :: Maybe a) | |
type Anno (Maybe Role) Source # | |
type Anno (Maybe Role) Source # | |
Instances
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
Int
String
or an Int
. The Left
constructor can be used only on
String
s, and the Right
constructor can be used only on Int
s:
>>>
let s = Left "foo" :: Either String Int
>>>
s
Left "foo">>>
let n = Right 3 :: Either String Int
>>>
n
Right 3>>>
:type s
s :: Either String Int>>>
:type n
n :: 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) s
Left "foo">>>
fmap (*2) n
Right 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 Int
s.
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither '1' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Right 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)>>>
:}
>>>
parseMultiple
Left "parse error"
Instances
Bifunctor Either | Since: base-4.8.0.0 |
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 liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) Source # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] Source # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) Source # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] Source # | |
Show2 Either | Since: base-4.9.0.0 |
NFData2 Either | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Generic1 (Either a :: Type -> Type) | |
(Lift a, Lift b) => Lift (Either a b :: Type) | |
MonadFix (Either e) | Since: base-4.3.0.0 |
Foldable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Either a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Either a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source # toList :: Either a a0 -> [a0] Source # null :: Either a a0 -> Bool Source # length :: Either a a0 -> Int Source # elem :: Eq a0 => a0 -> Either a a0 -> Bool Source # maximum :: Ord a0 => Either a a0 -> a0 Source # minimum :: Ord a0 => Either a a0 -> a0 Source # | |
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 liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) Source # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] Source # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) Source # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] Source # | |
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 |
Defined in Data.Either | |
Functor (Either a) | Since: base-3.0 |
Monad (Either e) | Since: base-4.4.0.0 |
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) | |
(Data a, Data b) => Data (Either a b) | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Either a b -> c (Either a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) Source # toConstr :: Either a b -> Constr Source # dataTypeOf :: Either a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Either a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Either a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source # | |
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 |
(Binary a, Binary b) => Binary (Either a b) | |
(NFData a, NFData b) => NFData (Either a b) | |
Defined in Control.DeepSeq | |
(Binary a, Binary b) => Binary (Either a b) Source # | |
(Outputable a, Outputable b) => Outputable (Either a b) Source # | |
(Eq a, Eq b) => Eq (Either a b) | Since: base-2.1 |
(Ord a, Ord b) => Ord (Either a b) | Since: base-2.1 |
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 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))) |
Parsing of String
s, producing values.
Derived instances of Read
make the following assumptions, which
derived instances of Show
obey:
- If the constructor is defined to be an infix operator, then the
derived
Read
instance will parse only infix applications of the constructor (not the prefix form). - Associativity is not used to reduce the occurrence of parentheses, although precedence may be.
- If the constructor is defined using record syntax, the derived
Read
will parse only the record-syntax form, and furthermore, the fields must be given in the same order as the original declaration. - The derived
Read
instance allows arbitrary Haskell whitespace between tokens of the input string. Extra parentheses are also allowed.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Read
in Haskell 2010 is equivalent to
instance (Read a) => Read (Tree a) where readsPrec d r = readParen (d > app_prec) (\r -> [(Leaf m,t) | ("Leaf",s) <- lex r, (m,t) <- readsPrec (app_prec+1) s]) r ++ readParen (d > up_prec) (\r -> [(u:^:v,w) | (u,s) <- readsPrec (up_prec+1) r, (":^:",t) <- lex s, (v,w) <- readsPrec (up_prec+1) t]) r where app_prec = 10 up_prec = 5
Note that right-associativity of :^:
is unused.
The derived instance in GHC is equivalent to
instance (Read a) => Read (Tree a) where readPrec = parens $ (prec app_prec $ do Ident "Leaf" <- lexP m <- step readPrec return (Leaf m)) +++ (prec up_prec $ do u <- step readPrec Symbol ":^:" <- lexP v <- step readPrec return (u :^: v)) where app_prec = 10 up_prec = 5 readListPrec = readListPrecDefault
Why do both readsPrec
and readPrec
exist, and why does GHC opt to
implement readPrec
in derived Read
instances instead of readsPrec
?
The reason is that readsPrec
is based on the ReadS
type, and although
ReadS
is mentioned in the Haskell 2010 Report, it is not a very efficient
parser data structure.
readPrec
, on the other hand, is based on a much more efficient ReadPrec
datatype (a.k.a "new-style parsers"), but its definition relies on the use
of the RankNTypes
language extension. Therefore, readPrec
(and its
cousin, readListPrec
) are marked as GHC-only. Nevertheless, it is
recommended to use readPrec
instead of readsPrec
whenever possible
for the efficiency improvements it brings.
As mentioned above, derived Read
instances in GHC will implement
readPrec
instead of readsPrec
. The default implementations of
readsPrec
(and its cousin, readList
) will simply use readPrec
under
the hood. If you are writing a Read
instance by hand, it is recommended
to write it like so:
instanceRead
T wherereadPrec
= ...readListPrec
=readListPrecDefault
:: Int | the operator precedence of the enclosing
context (a number from |
-> ReadS a |
attempts to parse a value from the front of the string, returning a list of (parsed value, remaining string) pairs. If there is no successful parse, the returned list is empty.
Derived instances of Read
and Show
satisfy the following:
That is, readsPrec
parses the string produced by
showsPrec
, and delivers the value that
showsPrec
started with.
Instances
Read All | Since: base-2.1 |
Read Any | Since: base-2.1 |
Read Version | Since: base-2.1 |
Read Void | Reading a Since: base-4.8.0.0 |
Read CBool | |
Read CChar | |
Read CClock | |
Read CDouble | |
Read CFloat | |
Read CInt | |
Read CIntMax | |
Read CIntPtr | |
Read CLLong | |
Read CLong | |
Read CPtrdiff | |
Read CSChar | |
Read CSUSeconds | |
Defined in Foreign.C.Types | |
Read CShort | |
Read CSigAtomic | |
Defined in Foreign.C.Types | |
Read CSize | |
Read CTime | |
Read CUChar | |
Read CUInt | |
Read CUIntMax | |
Read CUIntPtr | |
Read CULLong | |
Defined in Foreign.C.Types readsPrec :: |