Copyright | (C) 2013-2016 University of Twente 2017 Myrtle Software Ltd Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Unsafe |
Language | Haskell2010 |
Extensions |
|
Clash.Prelude
Contents
Description
CλaSH (pronounced ‘clash’) is a functional hardware description language that borrows both its syntax and semantics from the functional programming language Haskell. The merits of using a functional language to describe hardware comes from the fact that combinational circuits can be directly modeled as mathematical functions and that functional languages lend themselves very well at describing and (de-)composing mathematical functions.
This package provides:
- Prelude library containing datatypes and functions for circuit design
To use the library:
- Import Clash.Prelude; by default clock and reset lines are implicitly routed for all the components found in Clash.Prelude. You can read more about implicit clock and reset lines in Clash.Signal
- Alternatively, if you want to explicitly route clock and reset ports, for more straightforward multi-clock designs, you can import the Clash.Explicit.Prelude module. Note that you should not import Clash.Prelude and Clash.Explicit.Prelude at the same time as they have overlapping definitions.
For now, Clash.Prelude is also the best starting point for exploring the library. A preliminary version of a tutorial can be found in Clash.Tutorial. Some circuit examples can be found in Clash.Examples.
Synopsis
- mealy :: HiddenClockReset domain gated synchronous => (s -> i -> (s, o)) -> s -> Signal domain i -> Signal domain o
- mealyB :: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) => (s -> i -> (s, o)) -> s -> Unbundled domain i -> Unbundled domain o
- (<^>) :: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) => (s -> i -> (s, o)) -> s -> Unbundled domain i -> Unbundled domain o
- moore :: HiddenClockReset domain gated synchronous => (s -> i -> s) -> (s -> o) -> s -> Signal domain i -> Signal domain o
- mooreB :: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) => (s -> i -> s) -> (s -> o) -> s -> Unbundled domain i -> Unbundled domain o
- registerB :: (HiddenClockReset domain gated synchronous, Bundle a) => a -> Unbundled domain a -> Unbundled domain a
- asyncRom :: (KnownNat n, Enum addr) => Vec n a -> addr -> a
- asyncRomPow2 :: KnownNat n => Vec (2 ^ n) a -> Unsigned n -> a
- rom :: (KnownNat n, KnownNat m, HiddenClock domain gated) => Vec n a -> Signal domain (Unsigned m) -> Signal domain a
- romPow2 :: (KnownNat n, HiddenClock domain gated) => Vec (2 ^ n) a -> Signal domain (Unsigned n) -> Signal domain a
- asyncRomFile :: (KnownNat m, Enum addr) => SNat n -> FilePath -> addr -> BitVector m
- asyncRomFilePow2 :: forall n m. (KnownNat m, KnownNat n) => FilePath -> Unsigned n -> BitVector m
- romFile :: (KnownNat m, KnownNat n, HiddenClock domain gated) => SNat n -> FilePath -> Signal domain (Unsigned n) -> Signal domain (BitVector m)
- romFilePow2 :: forall n m domain gated. (KnownNat m, KnownNat n, HiddenClock domain gated) => FilePath -> Signal domain (Unsigned n) -> Signal domain (BitVector m)
- asyncRam :: (Enum addr, HiddenClock domain gated, HasCallStack) => SNat n -> Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a
- asyncRamPow2 :: (KnownNat n, HiddenClock domain gated, HasCallStack) => Signal domain (Unsigned n) -> Signal domain (Maybe (Unsigned n, a)) -> Signal domain a
- blockRam :: (Enum addr, HiddenClock domain gated, HasCallStack) => Vec n a -> Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a
- blockRamPow2 :: (KnownNat n, HiddenClock domain gated, HasCallStack) => Vec (2 ^ n) a -> Signal domain (Unsigned n) -> Signal domain (Maybe (Unsigned n, a)) -> Signal domain a
- blockRamFile :: (KnownNat m, Enum addr, HiddenClock domain gated, HasCallStack) => SNat n -> FilePath -> Signal domain addr -> Signal domain (Maybe (addr, BitVector m)) -> Signal domain (BitVector m)
- blockRamFilePow2 :: forall domain gated n m. (KnownNat m, KnownNat n, HiddenClock domain gated, HasCallStack) => FilePath -> Signal domain (Unsigned n) -> Signal domain (Maybe (Unsigned n, BitVector m)) -> Signal domain (BitVector m)
- readNew :: (Eq addr, HiddenClockReset domain gated synchronous) => (Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a) -> Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a
- window :: (KnownNat n, Default a, HiddenClockReset domain gated synchronous) => Signal domain a -> Vec (n + 1) (Signal domain a)
- windowD :: (KnownNat n, Default a, HiddenClockReset domain gated synchronous) => Signal domain a -> Vec (n + 1) (Signal domain a)
- isRising :: (HiddenClockReset domain gated synchronous, Bounded a, Eq a) => a -> Signal domain a -> Signal domain Bool
- isFalling :: (HiddenClockReset domain gated synchronous, Bounded a, Eq a) => a -> Signal domain a -> Signal domain Bool
- riseEvery :: HiddenClockReset domain gated synchronous => SNat n -> Signal domain Bool
- oscillate :: HiddenClockReset domain gated synchronous => Bool -> SNat n -> Signal domain Bool
- module Clash.Signal
- module Clash.Signal.Delayed
- module Clash.Prelude.DataFlow
- module Clash.Sized.BitVector
- module Clash.Prelude.BitIndex
- module Clash.Prelude.BitReduction
- module Clash.Sized.Signed
- module Clash.Sized.Unsigned
- module Clash.Sized.Index
- module Clash.Sized.Fixed
- module Clash.Sized.Vector
- module Clash.Sized.RTree
- module Clash.Annotations.TopEntity
- module GHC.TypeLits
- module Clash.Promoted.Nat
- module Clash.Promoted.Nat.Literals
- module Clash.Promoted.Nat.TH
- module Clash.Promoted.Symbol
- class Lift t where
- module Clash.Class.BitPack
- module Clash.Class.Num
- module Clash.Class.Resize
- module Control.Applicative
- module Data.Bits
- module Clash.XException
- undefined :: HasCallStack => a
- module Clash.NamedTypes
- module Clash.Hidden
- seq :: a -> b -> b
- filter :: (a -> Bool) -> [a] -> [a]
- print :: Show a => a -> IO ()
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- otherwise :: Bool
- ($) :: (a -> b) -> a -> b
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- class Bounded a where
- class Enum a where
- class Eq a where
- class Fractional a => Floating a where
- class Num a => Fractional a where
- class (Real a, Enum a) => Integral a where
- class Applicative m => Monad (m :: * -> *) where
- class Functor (f :: * -> *) where
- class Num a where
- class Eq a => Ord a where
- class Read a where
- class (Num a, Ord a) => Real a where
- class (RealFrac a, Floating a) => RealFloat a where
- class (Real a, Fractional a) => RealFrac a where
- class Show a where
- class Functor f => Applicative (f :: * -> *) where
- class Foldable (t :: * -> *) where
- class (Functor t, Foldable t) => Traversable (t :: * -> *) where
- class Semigroup a where
- class Semigroup a => Monoid a where
- data Bool
- data Char
- data Double
- data Float
- data Int
- data Integer
- data Maybe a
- data Ordering
- type Rational = Ratio Integer
- data IO a
- data Word
- data Either a b
- readIO :: Read a => String -> IO a
- readLn :: Read a => IO a
- appendFile :: FilePath -> String -> IO ()
- writeFile :: FilePath -> String -> IO ()
- readFile :: FilePath -> IO String
- interact :: (String -> String) -> IO ()
- getContents :: IO String
- getLine :: IO String
- getChar :: IO Char
- putStrLn :: String -> IO ()
- putStr :: String -> IO ()
- putChar :: Char -> IO ()
- ioError :: IOError -> IO a
- type FilePath = String
- userError :: String -> IOError
- type IOError = IOException
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- or :: Foldable t => t Bool -> Bool
- and :: Foldable t => t Bool -> Bool
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- unwords :: [String] -> String
- words :: String -> [String]
- unlines :: [String] -> String
- lines :: String -> [String]
- read :: Read a => String -> a
- reads :: Read a => ReadS a
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- lex :: ReadS String
- readParen :: Bool -> ReadS a -> ReadS a
- type ReadS a = String -> [(a, String)]
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- lcm :: Integral a => a -> a -> a
- gcd :: Integral a => a -> a -> a
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- (^) :: (Num a, Integral b) => a -> b -> a
- odd :: Integral a => a -> Bool
- even :: Integral a => a -> Bool
- showParen :: Bool -> ShowS -> ShowS
- showString :: String -> ShowS
- showChar :: Char -> ShowS
- shows :: Show a => a -> ShowS
- type ShowS = String -> String
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- break :: (a -> Bool) -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- dropWhile :: (a -> Bool) -> [a] -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- cycle :: [a] -> [a]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- maybe :: b -> (a -> b) -> Maybe a -> b
- uncurry :: (a -> b -> c) -> (a, b) -> c
- curry :: ((a, b) -> c) -> a -> b -> c
- subtract :: Num a => a -> a -> a
- asTypeOf :: a -> a -> a
- until :: (a -> Bool) -> (a -> a) -> a -> a
- ($!) :: (a -> b) -> a -> b
- flip :: (a -> b -> c) -> b -> a -> c
- (.) :: (b -> c) -> (a -> b) -> a -> c
- const :: a -> b -> a
- id :: a -> a
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- type String = [Char]
- errorWithoutStackTrace :: [Char] -> a
- error :: HasCallStack => [Char] -> a
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
Creating synchronous sequential circuits
Arguments
:: HiddenClockReset domain gated synchronous | |
=> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> s | Initial state |
-> Signal domain i -> Signal domain o | Synchronous sequential function with input and output matching that of the mealy machine |
Create a synchronous function from a combinational function describing a mealy machine
macT :: Int -- Current state -> (Int,Int) -- Input -> (Int,Int) -- (Updated state, output) macT s (x,y) = (s',s) where s' = x * y + s mac :: HiddenClockReset domain gated synchronous =>Signal
domain (Int, Int) ->Signal
domain Int mac =mealy
macT 0
>>>
simulate mac [(1,1),(2,2),(3,3),(4,4)]
[0,1,5,14... ...
Synchronous sequential functions can be composed just like their combinational counterpart:
dualMac :: HiddenClockReset domain gated synchronous => (Signal
domain Int,Signal
domain Int) -> (Signal
domain Int,Signal
domain Int) ->Signal
domain Int dualMac (a,b) (x,y) = s1 + s2 where s1 =mealy
mac 0 (bundle
(a,x)) s2 =mealy
mac 0 (bundle
(b,y))
Arguments
:: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) | |
=> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> s | Initial state |
-> Unbundled domain i -> Unbundled domain o | Synchronous sequential function with input and output matching that of the mealy machine |
A version of mealy
that does automatic Bundle
ing
Given a function f
of type:
f :: Int -> (Bool, Int) -> (Int, (Int, Bool))
When we want to make compositions of f
in g
using mealy
, we have to
write:
g a b c = (b1,b2,i2) where (i1,b1) =unbundle
(mealy
f 0 (bundle
(a,b))) (i2,b2) =unbundle
(mealy
f 3 (bundle
(i1,c)))
Using mealyB
however we can write:
g a b c = (b1,b2,i2) where (i1,b1) =mealyB
f 0 (a,b) (i2,b2) =mealyB
f 3 (i1,c)
Arguments
:: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) | |
=> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> s | Initial state |
-> Unbundled domain i -> Unbundled domain o | Synchronous sequential function with input and output matching that of the mealy machine |
Infix version of mealyB
Arguments
:: HiddenClockReset domain gated synchronous | |
=> (s -> i -> s) | Transfer function in moore machine form:
|
-> (s -> o) | Output function in moore machine form:
|
-> s | Initial state |
-> Signal domain i -> Signal domain o | Synchronous sequential function with input and output matching that of the moore machine |
Create a synchronous function from a combinational function describing a moore machine
macT :: Int -- Current state -> (Int,Int) -- Input -> Int -- Updated state macT s (x,y) = x * y + s mac :: HiddenClockReset domain gated synchronous =>Signal
domain (Int, Int) ->Signal
domain Int mac =moore
mac id 0
>>>
simulate mac [(1,1),(2,2),(3,3),(4,4)]
[0,1,5,14... ...
Synchronous sequential functions can be composed just like their combinational counterpart:
dualMac :: HiddenClockReset domain gated synchronous => (Signal
domain Int,Signal
domain Int) -> (Signal
domain Int,Signal
domain Int) ->Signal
domain Int dualMac (a,b) (x,y) = s1 + s2 where s1 =moore
mac id 0 (bundle
(a,x)) s2 =moore
mac id 0 (bundle
(b,y))
Arguments
:: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) | |
=> (s -> i -> s) | Transfer function in moore machine form:
|
-> (s -> o) | Output function in moore machine form:
|
-> s | Initial state |
-> Unbundled domain i -> Unbundled domain o | Synchronous sequential function with input and output matching that of the moore machine |
A version of moore
that does automatic Bundle
ing
Given a functions t
and o
of types:
t :: Int -> (Bool, Int) -> Int o :: Int -> (Int, Bool)
When we want to make compositions of t
and o
in g
using moore
, we have to
write:
g a b c = (b1,b2,i2) where (i1,b1) =unbundle
(moore
t o 0 (bundle
(a,b))) (i2,b2) =unbundle
(moore
t o 3 (bundle
(i1,c)))
Using mooreB
however we can write:
g a b c = (b1,b2,i2) where (i1,b1) =mooreB
t o 0 (a,b) (i2,b2) =mooreB
t o 3 (i1,c)
registerB :: (HiddenClockReset domain gated synchronous, Bundle a) => a -> Unbundled domain a -> Unbundled domain a infixr 3 Source #
Create a register
function for product-type like signals (e.g. '(Signal a, Signal b)')
rP :: HiddenClockReset domain gated synchronous => (Signal domain Int, Signal domain Int) -> (Signal domain Int, Signal domain Int) rP = registerB (8,8)
>>>
simulateB rP [(1,1),(2,2),(3,3)] :: [(Int,Int)]
[(8,8),(1,1),(2,2),(3,3)... ...
ROMs
Arguments
:: (KnownNat n, Enum addr) | |
=> Vec n a | ROM content NB: must be a constant |
-> addr | Read address |
-> a | The value of the ROM at address |
An asynchronous/combinational ROM with space for n
elements
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Prelude.BlockRam for ideas on how to use ROMs and RAMs
Arguments
:: KnownNat n | |
=> Vec (2 ^ n) a | ROM content NB: must be a constant |
-> Unsigned n | Read address |
-> a | The value of the ROM at address |
An asynchronous/combinational ROM with space for 2^n
elements
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Prelude.BlockRam for ideas on how to use ROMs and RAMs
Arguments
:: (KnownNat n, KnownNat m, HiddenClock domain gated) | |
=> Vec n a | ROM content NB: must be a constant |
-> Signal domain (Unsigned m) | Read address |
-> Signal domain a | The value of the ROM at address |
A ROM with a synchronous read port, with space for n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Prelude.BlockRam for ideas on how to use ROMs and RAMs
Arguments
:: (KnownNat n, HiddenClock domain gated) | |
=> Vec (2 ^ n) a | ROM content NB: must be a constant |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain a | The value of the ROM at address |
A ROM with a synchronous read port, with space for 2^n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Prelude.BlockRam for ideas on how to use ROMs and RAMs
ROMs initialised with a data file
Arguments
:: (KnownNat m, Enum addr) | |
=> SNat n | Size of the ROM |
-> FilePath | File describing the content of the ROM |
-> addr | Read address |
-> BitVector m | The value of the ROM at address |
An asynchronous/combinational ROM with space for n
elements
NB: This function might not work for specific combinations of code-generation backends and hardware targets. Please check the support table below:
| VHDL | Verilog | SystemVerilog | ===============+==========+==========+===============+ Altera/Quartus | Broken | Works | Works | Xilinx/ISE | Works | Works | Works | ASIC | Untested | Untested | Untested | ===============+==========+==========+===============+
Additional helpful information:
- See Clash.Prelude.ROM.File for more information on how to instantiate a ROM with the contents of a data file.
- See Clash.Sized.Fixed for ideas on how to create your own data files.
When you notice that
asyncRomFile
is significantly slowing down your simulation, give it a monomorphic type signature. So instead of leaving the type to be inferred:myRomData = asyncRomFile d512 "memory.bin"
or giving it a polymorphic type signature:
myRomData :: Enum addr => addr -> BitVector 16 myRomData = asyncRomFile d512 "memory.bin"
you should give it a monomorphic type signature:
myRomData :: Unsigned 9 -> BitVector 16 myRomData = asyncRomFile d512 "memory.bin"
Arguments
:: (KnownNat m, KnownNat n) | |
=> FilePath | File describing the content of the ROM |
-> Unsigned n | Read address |
-> BitVector m | The value of the ROM at address |
An asynchronous/combinational ROM with space for 2^n
elements
NB: This function might not work for specific combinations of code-generation backends and hardware targets. Please check the support table below:
| VHDL | Verilog | SystemVerilog | ===============+==========+==========+===============+ Altera/Quartus | Broken | Works | Works | Xilinx/ISE | Works | Works | Works | ASIC | Untested | Untested | Untested | ===============+==========+==========+===============+
Additional helpful information:
- See Clash.Prelude.ROM.File for more information on how to instantiate a ROM with the contents of a data file.
- See Clash.Sized.Fixed for ideas on how to create your own data files.
When you notice that
asyncRomFilePow2
is significantly slowing down your simulation, give it a monomorphic type signature. So instead of leaving the type to be inferred:myRomData = asyncRomFilePow2 "memory.bin"
you should give it a monomorphic type signature:
myRomData :: Unsigned 9 -> BitVector 16 myRomData = asyncRomFilePow2 "memory.bin"
Arguments
:: (KnownNat m, KnownNat n, HiddenClock domain gated) | |
=> SNat n | Size of the ROM |
-> FilePath | File describing the content of the ROM |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain (BitVector m) | The value of the ROM at address |
A ROM with a synchronous read port, with space for n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
NB: This function might not work for specific combinations of code-generation backends and hardware targets. Please check the support table below:
| VHDL | Verilog | SystemVerilog | ===============+==========+==========+===============+ Altera/Quartus | Broken | Works | Works | Xilinx/ISE | Works | Works | Works | ASIC | Untested | Untested | Untested | ===============+==========+==========+===============+
Additional helpful information:
- See Clash.Prelude.ROM.File for more information on how to instantiate a ROM with the contents of a data file.
- See Clash.Sized.Fixed for ideas on how to create your own data files.
Arguments
:: (KnownNat m, KnownNat n, HiddenClock domain gated) | |
=> FilePath | File describing the content of the ROM |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain (BitVector m) | The value of the ROM at address |
A ROM with a synchronous read port, with space for 2^n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
NB: This function might not work for specific combinations of code-generation backends and hardware targets. Please check the support table below:
| VHDL | Verilog | SystemVerilog | ===============+==========+==========+===============+ Altera/Quartus | Broken | Works | Works | Xilinx/ISE | Works | Works | Works | ASIC | Untested | Untested | Untested | ===============+==========+==========+===============+
Additional helpful information:
- See Clash.Prelude.ROM.File for more information on how to instantiate a ROM with the contents of a data file.
- See Clash.Sized.Fixed for ideas on how to create your own data files.
RAM primitives with a combinational read port
Arguments
:: (Enum addr, HiddenClock domain gated, HasCallStack) | |
=> SNat n | Size |
-> Signal domain addr | Read address |
-> Signal domain (Maybe (addr, a)) | (write address |
-> Signal domain a | Value of the |
Create a RAM with space for n
elements.
- NB: Initial content of the RAM is
undefined
Additional helpful information:
- See Clash.Prelude.BlockRam for more information on how to use a RAM.
Arguments
:: (KnownNat n, HiddenClock domain gated, HasCallStack) | |
=> Signal domain (Unsigned n) | Read address |
-> Signal domain (Maybe (Unsigned n, a)) | (write address |
-> Signal domain a | Value of the |
Create a RAM with space for 2^n
elements
- NB: Initial content of the RAM is
undefined
Additional helpful information:
- See Clash.Prelude.BlockRam for more information on how to use a RAM.
BlockRAM primitives
Arguments
:: (Enum addr, HiddenClock domain gated, HasCallStack) | |
=> Vec n a | Initial content of the BRAM, also
determines the size, NB: MUST be a constant. |
-> Signal domain addr | Read address |
-> Signal domain (Maybe (addr, a)) | (write address |
-> Signal domain a | Value of the |
Create a blockRAM with space for n
elements.
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
bram40 ::HiddenClock
domain =>Signal
domain (Unsigned
6) ->Signal
domain (Maybe (Unsigned
6,Bit
)) ->Signal
domainBit
bram40 =blockRam
(replicate
d40 1)
Additional helpful information:
- See Clash.Prelude.BlockRam for more information on how to use a Block RAM.
- Use the adapter
readNew
for obtaining write-before-read semantics like this:readNew (blockRam inits) rd wrM
.
Arguments
:: (KnownNat n, HiddenClock domain gated, HasCallStack) | |
=> Vec (2 ^ n) a | Initial content of the BRAM, also
determines the size, NB: MUST be a constant. |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain (Maybe (Unsigned n, a)) | (write address |
-> Signal domain a | Value of the |
Create a blockRAM with space for 2^n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
bram32 ::HiddenClock
domain =>Signal
domain (Unsigned
5) ->Signal
domain (Maybe (Unsigned
5,Bit
)) ->Signal
domainBit
bram32 =blockRamPow2
(replicate
d32 1)
Additional helpful information:
- See Clash.Prelude.BlockRam for more information on how to use a Block RAM.
- Use the adapter
readNew
for obtaining write-before-read semantics like this:readNew (blockRamPow2 inits) rd wrM
.
BlockRAM primitives initialised with a data file
Arguments
:: (KnownNat m, Enum addr, HiddenClock domain gated, HasCallStack) | |
=> SNat n | Size of the blockRAM |
-> FilePath | File describing the initial content of the blockRAM |
-> Signal domain addr | Read address |
-> Signal domain (Maybe (addr, BitVector m)) | (write address |
-> Signal domain (BitVector m) | Value of the |
Create a blockRAM with space for n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
NB: This function might not work for specific combinations of code-generation backends and hardware targets. Please check the support table below:
| VHDL | Verilog | SystemVerilog | ===============+==========+==========+===============+ Altera/Quartus | Broken | Works | Works | Xilinx/ISE | Works | Works | Works | ASIC | Untested | Untested | Untested | ===============+==========+==========+===============+
Additional helpful information:
- See Clash.Prelude.BlockRam for more information on how to use a Block RAM.
- Use the adapter
readNew'
for obtaining write-before-read semantics like this:readNew' clk (blockRamFile' clk size file) rd wrM
. - See Clash.Prelude.BlockRam.File for more information on how to instantiate a Block RAM with the contents of a data file.
- See Clash.Sized.Fixed for ideas on how to create your own data files.
Arguments
:: (KnownNat m, KnownNat n, HiddenClock domain gated, HasCallStack) | |
=> FilePath | File describing the initial content of the blockRAM |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain (Maybe (Unsigned n, BitVector m)) | (write address |
-> Signal domain (BitVector m) | Value of the |
Create a blockRAM with space for 2^n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
NB: This function might not work for specific combinations of code-generation backends and hardware targets. Please check the support table below:
| VHDL | Verilog | SystemVerilog | ===============+==========+==========+===============+ Altera/Quartus | Broken | Works | Works | Xilinx/ISE | Works | Works | Works | ASIC | Untested | Untested | Untested | ===============+==========+==========+===============+
Additional helpful information:
- See Clash.Prelude.BlockRam for more information on how to use a Block RAM.
- Use the adapter
readNew'
for obtaining write-before-read semantics like this:readNew' clk (blockRamFilePow2' clk file) rd wrM
. - See Clash.Prelude.BlockRam.File for more information on how to instantiate a Block RAM with the contents of a data file.
- See Clash.Sized.Fixed for ideas on how to create your own data files.
BlockRAM read/write conflict resolution
Arguments
:: (Eq addr, HiddenClockReset domain gated synchronous) | |
=> (Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a) | The |
-> Signal domain addr | Read address |
-> Signal domain (Maybe (addr, a)) | (Write address |
-> Signal domain a | Value of the |
Create read-after-write blockRAM from a read-before-write one (synchronised to system clock)
>>>
import Clash.Prelude
>>>
:t readNew (blockRam (0 :> 1 :> Nil))
readNew (blockRam (0 :> 1 :> Nil)) :: ... ... => Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a
Utility functions
Arguments
:: (KnownNat n, Default a, HiddenClockReset domain gated synchronous) | |
=> Signal domain a | Signal to create a window over |
-> Vec (n + 1) (Signal domain a) | Window of at least size 1 |
Give a window over a Signal
window4 :: HiddenClockReset domain gated synchronous => Signal domain Int -> Vec 4 (Signal domain Int) window4 = window
>>>
simulateB window4 [1::Int,2,3,4,5] :: [Vec 4 Int]
[<1,0,0,0>,<2,1,0,0>,<3,2,1,0>,<4,3,2,1>,<5,4,3,2>... ...
Arguments
:: (KnownNat n, Default a, HiddenClockReset domain gated synchronous) | |
=> Signal domain a | Signal to create a window over |
-> Vec (n + 1) (Signal domain a) | Window of at least size 1 |
Give a delayed window over a Signal
windowD3 :: HiddenClockReset domain gated synchronous => Signal domain Int -> Vec 3 (Signal domain Int) windowD3 = windowD
>>>
simulateB windowD3 [1::Int,2,3,4] :: [Vec 3 Int]
[<0,0,0>,<1,0,0>,<2,1,0>,<3,2,1>,<4,3,2>... ...
riseEvery :: HiddenClockReset domain gated synchronous => SNat n -> Signal domain Bool Source #
Give a pulse every n
clock cycles. This is a useful helper function when
combined with functions like
or regEn
,
in order to delay a register by a known amount.mux
To be precise: the given signal will be
for the next False
n-1
cycles,
followed by a single
value:True
>>>
Prelude.last (sampleN 1024 (riseEvery d1024)) == True
True>>>
Prelude.or (sampleN 1023 (riseEvery d1024)) == False
True
For example, to update a counter once every 10 million cycles:
counter =regEn
0 (riseEvery
(SNat
::SNat
10000000)) (counter + 1)
oscillate :: HiddenClockReset domain gated synchronous => Bool -> SNat n -> Signal domain Bool Source #
Oscillate a
for a given number of cycles. This is a convenient
function when combined with something like Bool
, as it allows you to
easily hold a register value for a given number of cycles. The input regEn
determines what the initial value is.Bool
To oscillate on an interval of 5 cycles:
>>>
sampleN 10 (oscillate False d5)
[False,False,False,False,False,True,True,True,True,True]
To oscillate between
and True
:False
>>>
sampleN 10 (oscillate False d1)
[False,True,False,True,False,True,False,True,False,True]
An alternative definition for the above could be:
>>>
let osc' = register False (not <$> osc')
>>>
let sample' = sampleN 200
>>>
sample' (oscillate False d1) == sample' osc'
True
Exported modules
Synchronous signals
module Clash.Signal
module Clash.Signal.Delayed
DataFlow interface
module Clash.Prelude.DataFlow
Datatypes
Bit vectors
module Clash.Sized.BitVector
module Clash.Prelude.BitIndex
module Clash.Prelude.BitReduction
Arbitrary-width numbers
module Clash.Sized.Signed
module Clash.Sized.Unsigned
module Clash.Sized.Index
Fixed point numbers
module Clash.Sized.Fixed
Fixed size vectors
module Clash.Sized.Vector
Perfect depth trees
module Clash.Sized.RTree
Annotations
module Clash.Annotations.TopEntity
Type-level natural numbers
module GHC.TypeLits
module Clash.Promoted.Nat
module Clash.Promoted.Nat.Literals
module Clash.Promoted.Nat.TH
Type-level strings
module Clash.Promoted.Symbol
Template Haskell
A Lift
instance can have any of its values turned into a Template
Haskell expression. This is needed when a value used within a Template
Haskell quotation is bound outside the Oxford brackets ([| ... |]
) but not
at the top level. As an example:
add1 :: Int -> Q Exp add1 x = [| x + 1 |]
Template Haskell has no way of knowing what value x
will take on at
splice-time, so it requires the type of x
to be an instance of Lift
.
A Lift
instance must satisfy $(lift x) ≡ x
for all x
, where $(...)
is a Template Haskell splice.
Lift
instances can be derived automatically by use of the -XDeriveLift
GHC language extension:
{-# LANGUAGE DeriveLift #-} module Foo where import Language.Haskell.TH.Syntax data Bar a = Bar1 a (Bar a) | Bar2 String deriving Lift
Methods
Turn a value into a Template Haskell expression, suitable for use in a splice.
Instances
Type classes
Clash
module Clash.Class.BitPack
module Clash.Class.Num
module Clash.Class.Resize
Other
module Control.Applicative
module Data.Bits
Exceptions
module Clash.XException
undefined :: HasCallStack => a Source #
Named types
module Clash.NamedTypes
Hidden arguments
module Clash.Hidden
Haskell Prelude
Clash.Prelude re-exports most of the Haskell Prelude with the exception of the following: (++), (!!), concat, drop, foldl, foldl1, foldr, foldr1, head, init, iterate, last, length, map, repeat, replicate, reverse, scanl, scanr, splitAt, tail, take, unzip, unzip3, zip, zip3, zipWith, zipWith3.
It instead exports the identically named functions defined in terms of
Vec
at Clash.Sized.Vector.
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. In other words, it evaluates the first
argument a
to weak head normal form (WHNF). seq
is usually
introduced to improve performance by avoiding unneeded laziness.
A note on evaluation order: the expression seq a b
does
not guarantee that a
will be evaluated before b
.
The only guarantee given by seq
is that the both a
and b
will be evaluated before seq
returns a value.
In particular, this means that b
may be evaluated before
a
. If you need to guarantee a specific order of evaluation,
you must use the function pseq
from the "parallel" package.
filter :: (a -> Bool) -> [a] -> [a] #
filter
, applied to a predicate and a list, returns the list of
those elements that satisfy the predicate; i.e.,
filter p xs = [ x | x <- xs, p x]
print :: Show a => a -> IO () #
The print
function outputs a value of any printable type to the
standard output device.
Printable types are those that are instances of class Show
; print
converts values to strings for output using the show
operation and
adds a newline.
For example, a program to print the first 20 integers and their powers of 2 could be written as:
main = print ([(n, 2^n) | n <- [0..19]])
($) :: (a -> b) -> a -> b infixr 0 #
Application operator. This operator is redundant, since ordinary
application (f x)
means the same as (f
. However, $
x)$
has
low, right-associative binding precedence, so it sometimes allows
parentheses to be omitted; for example:
f $ g $ h x = f (g (h x))
It is also useful in higher-order situations, such as
,
or map
($
0) xs
.zipWith
($
) fs xs
fromIntegral :: (Integral a, Num b) => a -> b #
general coercion from integral types
realToFrac :: (Real a, Fractional b) => a -> b #
general coercion to fractional types
The Bounded
class is used to name the upper and lower limits of a
type. Ord
is not a superclass of Bounded
since types that are not
totally ordered may also have upper and lower bounds.
The Bounded
class may be derived for any enumeration type;
minBound
is the first constructor listed in the data
declaration
and maxBound
is the last.
Bounded
may also be derived for single-constructor datatypes whose
constituent types are in Bounded
.
Instances
Class Enum
defines operations on sequentially ordered types.
The enumFrom
... methods are used in Haskell's translation of
arithmetic sequences.
Instances of Enum
may be derived for any enumeration type (types
whose constructors have no fields). The nullary constructors are
assumed to be numbered left-to-right by fromEnum
from 0
through n-1
.
See Chapter 10 of the Haskell Report for more details.
For any type that is an instance of class Bounded
as well as Enum
,
the following should hold:
- The calls
andsucc
maxBound
should result in a runtime error.pred
minBound
fromEnum
andtoEnum
should give a runtime error if the result value is not representable in the result type. For example,
is an error.toEnum
7 ::Bool
enumFrom
andenumFromThen
should be defined with an implicit bound, thus:
enumFrom x = enumFromTo x maxBound enumFromThen x y = enumFromThenTo x y bound where bound | fromEnum y >= fromEnum x = maxBound | otherwise = minBound
Methods
the successor of a value. For numeric types, succ
adds 1.
the predecessor of a value. For numeric types, pred
subtracts 1.
Convert from an Int
.
Convert to an Int
.
It is implementation-dependent what fromEnum
returns when
applied to a value that is too large to fit in an Int
.
Used in Haskell's translation of [n..]
.
enumFromThen :: a -> a -> [a] #
Used in Haskell's translation of [n,n'..]
.
enumFromTo :: a -> a -> [a] #
Used in Haskell's translation of [n..m]
.
enumFromThenTo :: a -> a -> a -> [a] #
Used in Haskell's translation of [n,n'..m]
.
Instances
The Eq
class defines equality (==
) and inequality (/=
).
All the basic datatypes exported by the Prelude are instances of Eq
,
and Eq
may be derived for any datatype whose constituents are also
instances of Eq
.
Instances
Eq Bool | |
Eq Char | |
Eq Double | |
Eq Float | |
Eq Int | |
Eq Int8 | Since: 2.1 |
Eq Int16 | Since: 2.1 |
Eq Int32 | Since: 2.1 |
Eq Int64 | Since: 2.1 |
Eq Integer | |
Eq Natural | |
Eq Ordering | |
Eq Word | |
Eq Word8 | Since: 2.1 |
Eq Word16 | Since: 2.1 |
Eq Word32 | Since: 2.1 |
Eq Word64 | Since: 2.1 |
Eq SomeTypeRep | |
Eq Exp | |
Eq Match | |
Eq Clause | |
Eq Pat | |
Eq Type | |
Eq Dec | |
Eq Name | |
Eq FunDep | |
Eq InjectivityAnn | |
Methods (==) :: InjectivityAnn -> InjectivityAnn -> Bool # (/=) :: InjectivityAnn -> InjectivityAnn -> Bool # | |
Eq Overlap | |
Eq DerivStrategy | |
Methods (==) :: DerivStrategy -> DerivStrategy -> Bool # (/=) :: DerivStrategy -> DerivStrategy -> Bool # | |
Eq () | |
Eq TyCon | |
Eq Module | |
Eq TrName | |
Eq BigNat | |
Eq Void | Since: 4.8.0.0 |
Eq SpecConstrAnnotation | |
Methods (==) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool # (/=) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool # | |
Eq Constr | Equality of constructors Since: 4.0.0.0 |
Eq DataRep | |
Eq ConstrRep | |
Eq Fixity | |
Eq Unique | |
Eq Version | Since: 2.1 |
Eq ThreadId | Since: 4.2.0.0 |
Eq BlockReason | |
Eq ThreadStatus | |
Eq AsyncException | |
Methods (==) :: AsyncException -> AsyncException -> Bool # (/=) :: AsyncException -> AsyncException -> Bool # | |
Eq ArrayException | |
Methods (==) :: ArrayException -> ArrayException -> Bool # (/=) :: ArrayException -> ArrayException -> Bool # | |
Eq ExitCode | |
Eq IOErrorType | Since: 4.1.0.0 |
Eq MaskingState | |
Eq IOException | Since: 4.1.0.0 |
Eq ErrorCall | |
Eq ArithException | |
Methods (==) :: ArithException -> ArithException -> Bool # (/=) :: ArithException -> ArithException -> Bool # | |
Eq All | |
Eq Any | |
Eq Fixity | |
Eq Associativity | |
Methods (==) :: Associativity -> Associativity -> Bool # (/=) :: Associativity -> Associativity -> Bool # | |
Eq SourceUnpackedness | |
Methods (==) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (/=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # | |
Eq SourceStrictness | |
Methods (==) :: SourceStrictness -> SourceStrictness -> Bool # (/=) :: SourceStrictness -> SourceStrictness -> Bool # | |
Eq DecidedStrictness | |
Methods (==) :: DecidedStrictness -> DecidedStrictness -> Bool # (/=) :: DecidedStrictness -> DecidedStrictness -> Bool # | |
Eq SomeSymbol | Since: 4.7.0.0 |
Eq SomeNat | Since: 4.7.0.0 |
Eq CChar | |
Eq CSChar | |
Eq CUChar | |
Eq CShort | |
Eq CUShort | |
Eq CInt | |
Eq CUInt | |
Eq CLong | |
Eq CULong | |
Eq CLLong | |
Eq CULLong | |
Eq CBool | |
Eq CFloat | |
Eq CDouble | |
Eq CPtrdiff | |
Eq CSize | |
Eq CWchar | |
Eq CSigAtomic | |
Eq CClock | |
Eq CTime | |
Eq CUSeconds | |
Eq CSUSeconds | |
Eq CIntPtr | |
Eq CUIntPtr | |
Eq CIntMax | |
Eq CUIntMax | |
Eq Fingerprint | |
Eq Lexeme | |
Eq Number | |
Eq GeneralCategory | |
Methods (==) :: GeneralCategory -> GeneralCategory -> Bool # (/=) :: GeneralCategory -> GeneralCategory -> Bool # | |
Eq SrcLoc | |
Eq ByteString | |
Eq ByteString | |
Eq IntSet | |
Eq TyVarBndr | |
Eq Extension | |
Eq ForeignSrcLang | |
Methods (==) :: ForeignSrcLang -> ForeignSrcLang -> Bool # (/=) :: ForeignSrcLang -> ForeignSrcLang -> Bool # | |
Eq Doc | |
Eq TextDetails | |
Eq Style | |
Eq Mode | |
Eq ModName | |
Eq PkgName | |
Eq Module | |
Eq OccName | |
Eq NameFlavour | |
Eq NameSpace | |
Eq Loc | |
Eq Info | |
Eq ModuleInfo | |
Eq Fixity | |
Eq FixityDirection | |
Methods (==) :: FixityDirection -> FixityDirection -> Bool # (/=) :: FixityDirection -> FixityDirection -> Bool # | |
Eq Lit | |
Eq Body | |
Eq Guard | |
Eq Stmt | |
Eq Range | |
Eq DerivClause | |
Eq TypeFamilyHead | |
Methods (==) :: TypeFamilyHead -> TypeFamilyHead -> Bool # (/=) :: TypeFamilyHead -> TypeFamilyHead -> Bool # | |
Eq TySynEqn | |
Eq Foreign | |
Eq Callconv | |
Eq Safety | |
Eq Pragma | |
Eq Inline | |
Eq RuleMatch | |
Eq Phases | |
Eq RuleBndr | |
Eq AnnTarget | |
Eq SourceUnpackedness | |
Methods (==) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (/=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # | |
Eq SourceStrictness | |
Methods (==) :: SourceStrictness -> SourceStrictness -> Bool # (/=) :: SourceStrictness -> SourceStrictness -> Bool # | |
Eq DecidedStrictness | |
Methods (==) :: DecidedStrictness -> DecidedStrictness -> Bool # (/=) :: DecidedStrictness -> DecidedStrictness -> Bool # | |
Eq Con | |
Eq Bang | |
Eq PatSynDir | |
Eq PatSynArgs | |
Eq FamilyResultSig | |
Methods (==) :: FamilyResultSig -> FamilyResultSig -> Bool # (/=) :: FamilyResultSig -> FamilyResultSig -> Bool # | |
Eq TyLit | |
Eq Role | |
Eq AnnLookup | |
Eq LocalTime | |
Eq UniversalTime | |
Methods (==) :: UniversalTime -> UniversalTime -> Bool # (/=) :: UniversalTime -> UniversalTime -> Bool # | |
Eq UTCTime | |
Eq Day | |
Eq HDL # | |
Eq SaturationMode # | |
Methods (==) :: SaturationMode -> SaturationMode -> Bool # (/=) :: SaturationMode -> SaturationMode -> Bool # | |
Eq Bit # | |
Eq DefName | |
Eq TimeLocale | |
Eq ByteArray | |
Eq Addr | |
Eq ConstructorInfo | |
Eq ConstructorVariant | |
Eq DatatypeInfo | |
Eq DatatypeVariant | |
Eq FieldStrictness | |
Eq Strictness | |
Eq Unpackedness | |
Eq Half | |
Eq ResetKind # | |
Eq ClockKind # | |
Eq NewOrData | |
() :=> (Eq Bool) | |
() :=> (Eq Double) | |
() :=> (Eq Float) | |
() :=> (Eq Int) | |
() :=> (Eq Integer) | |
() :=> (Eq Natural) | |
() :=> (Eq Word) | |
() :=> (Eq ()) | |
() :=> (Eq (a :- b)) | |
() :=> (Eq (Dict a)) | |
Class () (Eq a) | |
Eq a => Eq [a] | |
Eq a => Eq (Maybe a) | |
Eq a => Eq (Ratio a) | |
Eq (Ptr a) | |
Eq (FunPtr a) | |
Eq p => Eq (Par1 p) | |
Eq a => Eq (Complex a) | |
Eq (Fixed a) | |
Eq a => Eq (Min a) | |
Eq a => Eq (Max a) | |
Eq a => Eq (First a) | |
Eq a => Eq (Last a) | |
Eq m => Eq (WrappedMonoid m) | |
Methods (==) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (/=) :: WrappedMonoid m -> WrappedMonoid m -> Bool # | |
Eq a => Eq (Option a) | |
Eq (StableName a) | Since: 2.1 |
Eq a => Eq (ZipList a) | |
Eq a => Eq (Identity a) | |
Eq (TVar a) | Since: 4.8.0.0 |
Eq (IORef a) | Pointer equality. Since: 4.1.0.0 |
Eq a => Eq (First a) | |
Eq a => Eq (Last a) | |
Eq a => Eq (Dual a) | |
Eq a => Eq (Sum a) | |
Eq a => Eq (Product a) | |
Eq a => Eq (Down a) | |
Eq (MVar a) | Since: 4.1.0.0 |
Eq a => Eq (NonEmpty a) | |
Eq a => Eq (IntMap a) | |
Eq a => Eq (Tree a) | |
Eq a => Eq (Seq a) | |
Eq a => Eq (ViewL a) | |
Eq a => Eq (ViewR a) | |
Eq a => Eq (Set a) | |
Eq (Doc a) | |
Eq a => Eq (AnnotDetails a) | |
Methods (==) :: AnnotDetails a -> AnnotDetails a -> Bool # (/=) :: AnnotDetails a -> AnnotDetails a -> Bool # | |
Eq a => Eq (Span a) | |
Eq (BitVector n) # | |
Eq (Index n) # | |
Eq a => Eq (Bounds a) | |
Eq a => Eq (DList a) | |
Eq a => Eq (HashSet a) | |
(Storable a, Eq a) => Eq (Vector a) | |
(Prim a, Eq a) => Eq (Vector a) | |
Eq a => Eq (Vector a) | |
Eq a => Eq (Array a) | |
Eq (Unsigned n) # | |
Eq (Signed n) # | |
Eq (Dict a) | |
(Eq a) :=> (Eq [a]) | |
(Eq a) :=> (Eq (Maybe a)) | |
(Eq a) :=> (Eq (Complex a)) | |
(Eq a) :=> (Eq (Ratio a)) | |
(Eq a) :=> (Eq (Identity a)) | |
(Eq a) :=> (Eq (Const a b)) | |
Class (Eq a) (Ord a) | |
Class (Eq a) (Bits a) | |
(Eq a, Eq b) => Eq (Either a b) | |
Eq (V1 p) | Since: 4.9.0.0 |
Eq (U1 p) | Since: 4.9.0.0 |
Eq (TypeRep a) | Since: 2.1 |
(Eq a, Eq b) => Eq (a, b) | |
(Ix i, Eq e) => Eq (Array i e) | Since: 2.1 |
Eq a => Eq (Arg a b) | Since: 4.9.0.0 |
Eq (Proxy s) | Since: 4.7.0.0 |
Eq (STRef s a) | Pointer equality. Since: 2.1 |
(Eq k, Eq a) => Eq (Map k a) | |
(KnownNat n, Eq a) => Eq (Vec n a) # | |
(Eq i, Eq a) => Eq (Level i a) | |
(Eq1 f, Eq a) => Eq (Cofree f a) | |
(Eq1 f, Eq a) => Eq (Free f a) | |
(Eq1 f, Eq a) => Eq (Yoneda f a) | |
(Eq k, Eq v) => Eq (HashMap k v) | |
Eq (MutableArray s a) | |
(Eq k, Eq v) => Eq (Leaf k v) | |
(KnownNat d, Eq a) => Eq (RTree d a) # | |
Eq (a :- b) | |
(Eq a, Eq b) :=> (Eq (a, b)) | |
(Eq a, Eq b) :=> (Eq (Either a b)) | |
Eq (f p) => Eq (Rec1 f p) | |
Eq (URec (Ptr ()) p) | |
Eq (URec Char p) | |
Eq (URec Double p) | |
Eq (URec Float p) | |
Eq (URec Int p) | |
Eq (URec Word p) | |
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |
Eq (STArray s i e) | Since: 2.1 |
Eq a => Eq (Const a b) | |
Eq (f a) => Eq (Alt f a) | |
Eq (a :~: b) | |
(Eq e, Eq1 m, Eq a) => Eq (ErrorT e m a) | |
Eq a => Eq (Constant a b) | |
Eq b => Eq (Tagged s b) | |
Eq (p (Fix p a) a) => Eq (Fix p a) | |
Eq (p a a) => Eq (Join p a) | |
(Eq a, Eq (f b)) => Eq (CofreeF f a b) | |
Eq (w (CofreeF f a (CofreeT f w a))) => Eq (CofreeT f w a) | |
(Eq1 f, Eq1 m, Eq a) => Eq (FreeT f m a) | |
(Eq a, Eq (f b)) => Eq (FreeF f a b) | |
Eq (rep (int + frac)) => Eq (Fixed rep int frac) # | |
Eq c => Eq (K1 i c p) | |
(Eq (f p), Eq (g p)) => Eq ((f :+: g) p) | |
(Eq (f p), Eq (g p)) => Eq ((f :*: g) p) | |
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) | |
(Eq1 f, Eq1 g, Eq a) => Eq (Product f g a) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a) | Since: 4.9.0.0 |
Eq (a :~~: b) | Since: 4.10.0.0 |
Eq (f p) => Eq (M1 i c f p) | |
Eq (f (g p)) => Eq ((f :.: g) p) | |
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) | |
(Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) | Since: 4.9.0.0 |
Eq (f a) => Eq (Clown f a b) | |
Eq (p b a) => Eq (Flip p a b) | |
Eq (g b) => Eq (Joker g a b) | |
Eq (p a b) => Eq (WrappedBifunctor p a b) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) | |
(Eq (f a b), Eq (g a b)) => Eq (Product f g a b) | |
(Eq (p a b), Eq (q a b)) => Eq (Sum p q a b) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) | |
Eq (f (p a b)) => Eq (Tannen f p a b) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) | |
Eq (p (f a) (g b)) => Eq (Biff p f g a b) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
class Fractional a => Floating a where #
Trigonometric and hyperbolic functions and related functions.
Minimal complete definition
pi, exp, log, sin, cos, asin, acos, atan, sinh, cosh, asinh, acosh, atanh
Instances
Floating Double | Since: 2.1 |
Floating Float | Since: 2.1 |
Floating CFloat | |
Floating CDouble | |
Floating Half | |
() :=> (Floating Double) | |
() :=> (Floating Float) | |
RealFloat a => Floating (Complex a) | Since: 2.1 |
Methods exp :: Complex a -> Complex a # log :: Complex a -> Complex a # sqrt :: Complex a -> Complex a # (**) :: Complex a -> Complex a -> Complex a # logBase :: Complex a -> Complex a -> Complex a # sin :: Complex a -> Complex a # cos :: Complex a -> Complex a # tan :: Complex a -> Complex a # asin :: Complex a -> Complex a # acos :: Complex a -> Complex a # atan :: Complex a -> Complex a # sinh :: Complex a -> Complex a # cosh :: Complex a -> Complex a # tanh :: Complex a -> Complex a # asinh :: Complex a -> Complex a # acosh :: Complex a -> Complex a # atanh :: Complex a -> Complex a # log1p :: Complex a -> Complex a # expm1 :: Complex a -> Complex a # | |
Floating a => Floating (Identity a) | |
Methods exp :: Identity a -> Identity a # log :: Identity a -> Identity a # sqrt :: Identity a -> Identity a # (**) :: Identity a -> Identity a -> Identity a # logBase :: Identity a -> Identity a -> Identity a # sin :: Identity a -> Identity a # cos :: Identity a -> Identity a # tan :: Identity a -> Identity a # asin :: Identity a -> Identity a # acos :: Identity a -> Identity a # atan :: Identity a -> Identity a # sinh :: Identity a -> Identity a # cosh :: Identity a -> Identity a # tanh :: Identity a -> Identity a # asinh :: Identity a -> Identity a # acosh :: Identity a -> Identity a # atanh :: Identity a -> Identity a # log1p :: Identity a -> Identity a # expm1 :: Identity a -> Identity a # | |
(Floating a) :=> (Floating (Identity a)) | |
(Floating a) :=> (Floating (Const a b)) | |
(RealFloat a) :=> (Floating (Complex a)) | |
Class (Fractional a) (Floating a) | |
Methods cls :: Floating a :- Fractional a | |
Floating a => Floating (Op a b) | |
Class (RealFrac a, Floating a) (RealFloat a) | |
Floating a => Floating (Const a b) | |
Methods exp :: Const a b -> Const a b # log :: Const a b -> Const a b # sqrt :: Const a b -> Const a b # (**) :: Const a b -> Const a b -> Const a b # logBase :: Const a b -> Const a b -> Const a b # sin :: Const a b -> Const a b # cos :: Const a b -> Const a b # tan :: Const a b -> Const a b # asin :: Const a b -> Const a b # acos :: Const a b -> Const a b # atan :: Const a b -> Const a b # sinh :: Const a b -> Const a b # cosh :: Const a b -> Const a b # tanh :: Const a b -> Const a b # asinh :: Const a b -> Const a b # acosh :: Const a b -> Const a b # atanh :: Const a b -> Const a b # log1p :: Const a b -> Const a b # expm1 :: Const a b -> Const a b # | |
Floating a => Floating (Tagged s a) | |
Methods exp :: Tagged s a -> Tagged s a # log :: Tagged s a -> Tagged s a # sqrt :: Tagged s a -> Tagged s a # (**) :: Tagged s a -> Tagged s a -> Tagged s a # logBase :: Tagged s a -> Tagged s a -> Tagged s a # sin :: Tagged s a -> Tagged s a # cos :: Tagged s a -> Tagged s a # tan :: Tagged s a -> Tagged s a # asin :: Tagged s a -> Tagged s a # acos :: Tagged s a -> Tagged s a # atan :: Tagged s a -> Tagged s a # sinh :: Tagged s a -> Tagged s a # cosh :: Tagged s a -> Tagged s a # tanh :: Tagged s a -> Tagged s a # asinh :: Tagged s a -> Tagged s a # acosh :: Tagged s a -> Tagged s a # atanh :: Tagged s a -> Tagged s a # log1p :: Tagged s a -> Tagged s a # expm1 :: Tagged s a -> Tagged s a # |
class Num a => Fractional a where #
Fractional numbers, supporting real division.
Minimal complete definition
fromRational, (recip | (/))
Methods
fractional division
reciprocal fraction
fromRational :: Rational -> a #
Conversion from a Rational
(that is
).
A floating literal stands for an application of Ratio
Integer
fromRational
to a value of type Rational
, so such literals have type
(
.Fractional
a) => a
Instances
Fractional CFloat | |
Fractional CDouble | |
Fractional Half | |
() :=> (Fractional Double) | |
Methods ins :: () :- Fractional Double | |
() :=> (Fractional Float) | |
Methods ins :: () :- Fractional Float | |
Integral a => Fractional (Ratio a) | Since: 2.0.1 |
RealFloat a => Fractional (Complex a) | Since: 2.1 |
HasResolution a => Fractional (Fixed a) | Since: 2.1 |
Fractional a => Fractional (Identity a) | |
(Fractional a) :=> (Fractional (Identity a)) | |
Methods ins :: Fractional a :- Fractional (Identity a) | |
(Fractional a) :=> (Fractional (Const a b)) | |
Methods ins :: Fractional a :- Fractional (Const a b) | |
(Integral a) :=> (Fractional (Ratio a)) | |
Methods ins :: Integral a :- Fractional (Ratio a) | |
(RealFloat a) :=> (Fractional (Complex a)) | |
Methods ins :: RealFloat a :- Fractional (Complex a) | |
Class (Fractional a) (Floating a) | |
Methods cls :: Floating a :- Fractional a | |
Class (Num a) (Fractional a) | |
Methods cls :: Fractional a :- Num a | |
Fractional a => Fractional (Op a b) | |
Fractional a => Fractional (Signal domain a) # | |
Class (Real a, Fractional a) (RealFrac a) | |
Methods cls :: RealFrac a :- (Real a, Fractional a) | |
Fractional a => Fractional (Const a b) | |
Fractional a => Fractional (Tagged s a) | |
FracFixedC rep int frac => Fractional (Fixed rep int frac) # | The operators of this instance saturate on overflow, and use truncation as the rounding method. When used in a polymorphic setting, use the following Constraint synonyms for less verbose type signatures:
|
Fractional a => Fractional (DSignal domain delay a) # | |
class (Real a, Enum a) => Integral a where #
Integral numbers, supporting integer division.
Methods
quot :: a -> a -> a infixl 7 #
integer division truncated toward zero
integer remainder, satisfying
(x `quot` y)*y + (x `rem` y) == x
integer division truncated toward negative infinity
integer modulus, satisfying
(x `div` y)*y + (x `mod` y) == x
conversion to Integer
Instances
class Applicative m => Monad (m :: * -> *) where #
The Monad
class defines the basic operations over a monad,
a concept from a branch of mathematics known as category theory.
From the perspective of a Haskell programmer, however, it is best to
think of a monad as an abstract datatype of actions.
Haskell's do
expressions provide a convenient syntax for writing
monadic expressions.
Instances of Monad
should satisfy the following laws:
Furthermore, the Monad
and Applicative
operations should relate as follows:
The above laws imply:
and that pure
and (<*>
) satisfy the applicative functor laws.
The instances of Monad
for lists, Maybe
and IO
defined in the Prelude satisfy these laws.
Minimal complete definition
Methods
(>>=) :: m a -> (a -> m b) -> m b infixl 1 #
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
(>>) :: m a -> m b -> m b infixl 1 #
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
Inject a value into the monadic type.
Fail with a message. This operation is not part of the
mathematical definition of a monad, but is invoked on pattern-match
failure in a do
expression.
As part of the MonadFail proposal (MFP), this function is moved
to its own class MonadFail
(see Control.Monad.Fail for more
details). The definition here will be removed in a future
release.
Instances
Monad [] | Since: 2.1 |
Monad Maybe | Since: 2.1 |
Monad IO | Since: 2.1 |
Monad Par1 | Since: 4.9.0.0 |
Monad Q | |
Monad Complex | Since: 4.9.0.0 |
Monad Min | Since: 4.9.0.0 |
Monad Max | Since: 4.9.0.0 |
Monad First | Since: 4.9.0.0 |
Monad Last | Since: 4.9.0.0 |
Monad Option | Since: 4.9.0.0 |
Monad Identity | Since: 4.8.0.0 |
Monad STM | Since: 4.3.0.0 |
Monad First | |
Monad Last | |
Monad Dual | Since: 4.8.0.0 |
Monad Sum | Since: 4.8.0.0 |
Monad Product | Since: 4.8.0.0 |
Monad Down | Since: 4.11.0.0 |
Monad ReadPrec | Since: 2.1 |
Monad ReadP | Since: 2.1 |
Monad NonEmpty | Since: 4.9.0.0 |
Monad Tree | |
Monad Seq | |
Monad P | Since: 2.1 |
Monad Gen | |
Monad Id | |
Monad Box | |
Monad DList | |
Monad Vector | |
Monad Array | |
Monad Rose | |
() :=> (Monad ((->) a :: * -> *)) | |
() :=> (Monad []) | |
() :=> (Monad IO) | |
() :=> (Monad (Either a)) | |
() :=> (Monad Identity) | |
Monad (Either e) | Since: 4.4.0.0 |
Monad (U1 :: * -> *) | Since: 4.9.0.0 |
Monoid a => Monad ((,) a) | Since: 4.9.0.0 |
Monad (ST s) | Since: 2.1 |
Monad m => Monad (WrappedMonad m) | |
Methods (>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b # (>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # return :: a -> WrappedMonad m a # fail :: String -> WrappedMonad m a # | |
ArrowApply a => Monad (ArrowMonad a) | Since: 2.1 |
Methods (>>=) :: ArrowMonad a a0 -> (a0 -> ArrowMonad a b) -> ArrowMonad a b # (>>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # return :: a0 -> ArrowMonad a a0 # fail :: String -> ArrowMonad a a0 # | |
Monad (Proxy :: * -> *) | Since: 4.7.0.0 |
Monad (ReifiedFold s) | |
Monad (ReifiedGetter s) | |
Representable f => Monad (Co f) | |
Alternative f => Monad (Cofree f) | |
Functor f => Monad (Free f) | |
Monad m => Monad (Yoneda m) | |
(Monad (Rep p), Representable p) => Monad (Prep p) | |
(Monad m) :=> (Functor (WrappedMonad m)) | |
Methods ins :: Monad m :- Functor (WrappedMonad m) | |
(Monad m) :=> (Applicative (WrappedMonad m)) | |
Methods ins :: Monad m :- Applicative (WrappedMonad m) | |
Class (Applicative f) (Monad f) | |
Methods cls :: Monad f :- Applicative f | |
Monad f => Monad (Rec1 f) | Since: 4.9.0.0 |
Monad f => Monad (Alt f) | |
(Applicative f, Monad f) => Monad (WhenMissing f x) | Equivalent to Since: 0.5.9 |
Methods (>>=) :: WhenMissing f x a -> (a -> WhenMissing f x b) -> WhenMissing f x b # (>>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b # return :: a -> WhenMissing f x a # fail :: String -> WhenMissing f x a # | |
(Monad m, Error e) => Monad (ErrorT e m) | |
Monad m => Monad (StateT s m) | |
Monad (Indexed i a) | |
Monad (Tagged s) | |
(Alternative f, Monad w) => Monad (CofreeT f w) | |
(Functor f, Monad m) => Monad (FreeT f m) | |
Class (Monad f, Alternative f) (MonadPlus f) | |
Methods cls :: MonadPlus f :- (Monad f, Alternative f) | |
Monad ((->) r :: * -> *) | Since: 2.1 |
(Monad f, Monad g) => Monad (f :*: g) | Since: 4.9.0.0 |
(Monad f, Monad g) => Monad (Product f g) | Since: 4.9.0.0 |
(Monad f, Applicative f) => Monad (WhenMatched f x y) | Equivalent to Since: 0.5.9 |
Methods (>>=) :: WhenMatched f x y a -> (a -> WhenMatched f x y b) -> WhenMatched f x y b # (>>) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y b # return :: a -> WhenMatched f x y a # fail :: String -> WhenMatched f x y a # | |
(Applicative f, Monad f) => Monad (WhenMissing f k x) | Equivalent to Since: 0.5.9 |
Methods (>>=) :: WhenMissing f k x a -> (a -> WhenMissing f k x b) -> WhenMissing f k x b # (>>) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x b # return :: a -> WhenMissing f k x a # fail :: String -> WhenMissing f k x a # | |
Monad f => Monad (M1 i c f) | Since: 4.9.0.0 |
(Monad f, Applicative f) => Monad (WhenMatched f k x y) | Equivalent to Since: 0.5.9 |
Methods (>>=) :: WhenMatched f k x y a -> (a -> WhenMatched f k x y b) -> WhenMatched f k x y b # (>>) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y b # return :: a -> WhenMatched f k x y a # fail :: String -> WhenMatched f k x y a # |
class Functor (f :: * -> *) where #
The Functor
class is used for types that can be mapped over.
Instances of Functor
should satisfy the following laws:
fmap id == id fmap (f . g) == fmap f . fmap g
The instances of Functor
for lists, Maybe
and IO
satisfy these laws.
Minimal complete definition
Instances
Functor [] | Since: 2.1 |
Functor Maybe | Since: 2.1 |
Functor IO | Since: 2.1 |
Functor Par1 | |
Functor Q | |
Functor Complex | |
Functor Min | Since: 4.9.0.0 |
Functor Max | Since: 4.9.0.0 |
Functor First | Since: 4.9.0.0 |
Functor Last | Since: 4.9.0.0 |
Functor Option | Since: 4.9.0.0 |
Functor ZipList | |
Functor Identity | Since: 4.8.0.0 |
Functor Handler | Since: 4.6.0.0 |
Functor STM | Since: 4.3.0.0 |
Functor First | |
Functor Last | |
Functor Dual | Since: 4.8.0.0 |
Functor Sum | Since: 4.8.0.0 |
Functor Product | Since: 4.8.0.0 |
Functor Down | Since: 4.11.0.0 |
Functor ReadPrec | Since: 2.1 |
Functor ReadP | Since: 2.1 |
Functor NonEmpty | Since: 4.9.0.0 |
Functor IntMap | |
Functor Tree | |
Functor Seq | |
Functor FingerTree | |
Methods fmap :: (a -> b) -> FingerTree a -> FingerTree b # (<$) :: a -> FingerTree b -> FingerTree a # | |
Functor Digit | |
Functor Node | |
Functor Elem | |
Functor ViewL | |
Functor ViewR | |
Functor Doc | |
Functor AnnotDetails | |
Methods fmap :: (a -> b) -> AnnotDetails a -> AnnotDetails b # (<$) :: a -> AnnotDetails b -> AnnotDetails a # | |
Functor Span | |
Functor P | |
Functor Gen | |
Functor Id | |
Functor Box | |
Functor DList | |
Functor Vector | |
Functor Array | |
Functor Rose | |
() :=> (Functor ((->) a :: * -> *)) | |
() :=> (Functor []) | |
() :=> (Functor Maybe) | |
() :=> (Functor IO) | |
() :=> (Functor (Either a)) | |
() :=> (Functor ((,) a)) | |
() :=> (Functor Identity) | |
() :=> (Functor (Const a :: * -> *)) | |
Class () (Functor f) | |
Functor (Either a) | Since: 3.0 |
Functor (V1 :: * -> *) | Since: 4.9.0.0 |
Functor (U1 :: * -> *) | Since: 4.9.0.0 |
Functor ((,) a) | Since: 2.1 |
Functor (ST s) | Since: 2.1 |
Functor (Array i) | Since: 2.1 |
Functor (Arg a) | Since: 4.9.0.0 |
Monad m => Functor (WrappedMonad m) | Since: 2.1 |
Methods fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b # (<$) :: a -> WrappedMonad m b -> WrappedMonad m a # | |
Arrow a => Functor (ArrowMonad a) | Since: 4.6.0.0 |
Methods fmap :: (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b # (<$) :: a0 -> ArrowMonad a b -> ArrowMonad a a0 # | |
Functor (Proxy :: * -> *) | Since: 4.7.0.0 |
Functor (Map k) | |
Functor (Vec n) # | |
Functor (Level i) | |
Functor (ReifiedFold s) | |
Functor (ReifiedGetter s) | |
Functor f => Functor (Co f) | |
Functor f => Functor (Cofree f) | |
Functor f => Functor (Free f) | |
Functor (Yoneda f) | |
Functor (HashMap k) | |
Functor f => Functor (Indexing f) | |
Functor f => Functor (Indexing64 f) | |
Profunctor p => Functor (Coprep p) | |
Profunctor p => Functor (Prep p) | |
Functor (Signal domain) # | |
KnownNat d => Functor (RTree d) # | |
(Monad m) :=> (Functor (WrappedMonad m)) | |
Methods ins :: Monad m :- Functor (WrappedMonad m) | |
Class (Functor f) (Applicative f) | |
Methods cls :: Applicative f :- Functor f | |
Functor f => Functor (Rec1 f) | |
Functor (URec Char :: * -> *) | |
Functor (URec Double :: * -> *) | |
Functor (URec Float :: * -> *) | |
Functor (URec Int :: * -> *) | |
Functor (URec Word :: * -> *) | |
Functor (URec (Ptr ()) :: * -> *) | |
Arrow a => Functor (WrappedArrow a b) | Since: 2.1 |
Methods fmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # (<$) :: a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |
Functor (Const m :: * -> *) | Since: 2.1 |
Functor f => Functor (Alt f) | |
(Applicative f, Monad f) => Functor (WhenMissing f x) | Since: 0.5.9 |
Methods fmap :: (a -> b) -> WhenMissing f x a -> WhenMissing f x b # (<$) :: a -> WhenMissing f x b -> WhenMissing f x a # | |
Functor m => Functor (ErrorT e m) | |
Functor m => Functor (StateT s m) | |
Functor (Constant a :: * -> *) | |
Functor (Context a b) | |
Functor (Indexed i a) | |
Functor (ReifiedIndexedFold i s) | |
Functor (ReifiedIndexedGetter i s) | |
Monad m => Functor (Bundle m v) | |
Functor (Tagged s) | |
Bifunctor p => Functor (Fix p) | |
Bifunctor p => Functor (Join p) | |
Functor f => Functor (CofreeF f a) | |
(Functor f, Functor w) => Functor (CofreeT f w) | |
(Functor f, Monad m) => Functor (FreeT f m) | |
Functor f => Functor (FreeF f a) | |
Functor (Day f g) | |
Functor (DSignal domain delay) # | |
Functor (Flows i b) | |
Functor (Mafic a b) | |
Functor (Holes t m) | |
Functor (CotambaraSum p a) | |
Profunctor p => Functor (TambaraSum p a) | |
Functor ((->) r :: * -> *) | Since: 2.1 |
Functor (K1 i c :: * -> *) | |
(Functor f, Functor g) => Functor (f :+: g) | |
(Functor f, Functor g) => Functor (f :*: g) | |
(Functor f, Functor g) => Functor (Product f g) | Since: 4.9.0.0 |
(Functor f, Functor g) => Functor (Sum f g) | Since: 4.9.0.0 |
Functor f => Functor (WhenMatched f x y) | Since: 0.5.9 |
Methods fmap :: (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b # (<$) :: a -> WhenMatched f x y b -> WhenMatched f x y a # | |
(Applicative f, Monad f) => Functor (WhenMissing f k x) | Since: 0.5.9 |
Methods fmap :: (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b # (<$) :: a -> WhenMissing f k x b -> WhenMissing f k x a # | |
Functor (Bazaar p a b) | |
Functor (Bazaar1 p a b) | |
Functor (Magma i t b) | |
Profunctor p => Functor (Procompose p q a) | |
Functor (Exchange a b s) | |
Profunctor p => Functor (Rift p q a) | |
Functor (Pretext p a b) | |
Functor (Molten i a b) | |
Functor f => Functor (M1 i c f) | |
(Functor f, Functor g) => Functor (f :.: g) | |
(Functor f, Functor g) => Functor (Compose f g) | Since: 4.9.0.0 |
Functor f => Functor (WhenMatched f k x y) | Since: 0.5.9 |
Methods fmap :: (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b # (<$) :: a -> WhenMatched f k x y b -> WhenMatched f k x y a # | |
Reifies s (ReifiedApplicative f) => Functor (ReflectedApplicative f s) | |
Functor (Clown f a :: * -> *) | |
Bifunctor p => Functor (Flip p a) | |
Functor g => Functor (Joker g a) | |
Bifunctor p => Functor (WrappedBifunctor p a) | |
Functor (BazaarT p g a b) | |
Functor (BazaarT1 p g a b) | |
Functor (PretextT p g a b) | |
Functor (TakingWhile p f a b) | |
(Functor f, Bifunctor p) => Functor (Tannen f p a) | |
(Bifunctor p, Functor g) => Functor (Biff p f g a) | |
Basic numeric class.
Methods
Unary negation.
Absolute value.
Sign of a number.
The functions abs
and signum
should satisfy the law:
abs x * signum x == x
For real numbers, the signum
is either -1
(negative), 0
(zero)
or 1
(positive).
fromInteger :: Integer -> a #
Conversion from an Integer
.
An integer literal represents the application of the function
fromInteger
to the appropriate value of type Integer
,
so such literals have type (
.Num
a) => a
Instances
Num Int | Since: 2.1 |
Num Int8 | Since: 2.1 |
Num Int16 | Since: 2.1 |
Num Int32 | Since: 2.1 |
Num Int64 | Since: 2.1 |
Num Integer | Since: 2.1 |
Num Natural | Since: 4.8.0.0 |
Num Word | Since: 2.1 |
Num Word8 | Since: 2.1 |
Num Word16 | Since: 2.1 |
Num Word32 | Since: 2.1 |
Num Word64 | Since: 2.1 |
Num CChar | |
Num CSChar | |
Num CUChar | |
Num CShort | |
Num CUShort | |
Num CInt | |
Num CUInt | |
Num CLong | |
Num CULong | |
Num CLLong | |
Num CULLong | |
Num CBool | |
Num CFloat | |
Num CDouble | |
Num CPtrdiff | |
Num CSize | |
Num CWchar | |
Num CSigAtomic | |
Methods (+) :: CSigAtomic -> CSigAtomic -> CSigAtomic # (-) :: CSigAtomic -> CSigAtomic -> CSigAtomic # (*) :: CSigAtomic -> CSigAtomic -> CSigAtomic # negate :: CSigAtomic -> CSigAtomic # abs :: CSigAtomic -> CSigAtomic # signum :: CSigAtomic -> CSigAtomic # fromInteger :: Integer -> CSigAtomic # | |
Num CClock | |
Num CTime | |
Num CUSeconds | |
Num CSUSeconds | |
Methods (+) :: CSUSeconds -> CSUSeconds -> CSUSeconds # (-) :: CSUSeconds -> CSUSeconds -> CSUSeconds # (*) :: CSUSeconds -> CSUSeconds -> CSUSeconds # negate :: CSUSeconds -> CSUSeconds # abs :: CSUSeconds -> CSUSeconds # signum :: CSUSeconds -> CSUSeconds # fromInteger :: Integer -> CSUSeconds # | |
Num CIntPtr | |
Num CUIntPtr | |
Num CIntMax | |
Num CUIntMax | |
Num Bit # | |
Num Half | |
() :=> (Num Double) | |
() :=> (Num Float) | |
() :=> (Num Int) | |
() :=> (Num Integer) | |
() :=> (Num Natural) | |
() :=> (Num Word) | |
Class () (Num a) | |
Integral a => Num (Ratio a) | Since: 2.0.1 |
RealFloat a => Num (Complex a) | Since: 2.1 |
HasResolution a => Num (Fixed a) | Since: 2.1 |
Num a => Num (Min a) | Since: 4.9.0.0 |
Num a => Num (Max a) | Since: 4.9.0.0 |
Num a => Num (Identity a) | |
Num a => Num (Sum a) | |
Num a => Num (Product a) | |
Num a => Num (Down a) | Since: 4.11.0.0 |
KnownNat n => Num (BitVector n) # | |
Methods (+) :: BitVector n -> BitVector n -> BitVector n # (-) :: BitVector n -> BitVector n -> BitVector n # (*) :: BitVector n -> BitVector n -> BitVector n # negate :: BitVector n -> BitVector n # abs :: BitVector n -> BitVector n # signum :: BitVector n -> BitVector n # fromInteger :: Integer -> BitVector n # | |
KnownNat n => Num (Index n) # | Operators report an error on overflow and underflow |
Num a => Num (Bounds a) | |
KnownNat n => Num (Unsigned n) # | |
KnownNat n => Num (Signed n) # | Operators do |
(Integral a) :=> (Num (Ratio a)) | |
(Num a) :=> (Num (Identity a)) | |
(Num a) :=> (Num (Const a b)) | |
(RealFloat a) :=> (Num (Complex a)) | |
Class (Num a) (Fractional a) | |
Methods cls :: Fractional a :- Num a | |
Num a => Num (Op a b) | |
Num a => Num (Signal domain a) # | |
Methods (+) :: Signal domain a -> Signal domain a -> Signal domain a # (-) :: Signal domain a -> Signal domain a -> Signal domain a # (*) :: Signal domain a -> Signal domain a -> Signal domain a # negate :: Signal domain a -> Signal domain a # abs :: Signal domain a -> Signal domain a # signum :: Signal domain a -> Signal domain a # fromInteger :: Integer -> Signal domain a # | |
Class (Num a, Ord a) (Real a) | |
Num a => Num (Const a b) | |
Num (f a) => Num (Alt f a) | |
Num a => Num (Tagged s a) | |
NumFixedC rep int frac => Num (Fixed rep int frac) # | The operators of this instance saturate on overflow, and use truncation as the rounding method. When used in a polymorphic setting, use the following Constraint synonyms for less verbose type signatures:
|
Methods (+) :: Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac # (-) :: Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac # (*) :: Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac # negate :: Fixed rep int frac -> Fixed rep int frac # abs :: Fixed rep int frac -> Fixed rep int frac # signum :: Fixed rep int frac -> Fixed rep int frac # fromInteger :: Integer -> Fixed rep int frac # | |
Num a => Num (DSignal domain delay a) # | |
Methods (+) :: DSignal domain delay a -> DSignal domain delay a -> DSignal domain delay a # (-) :: DSignal domain delay a -> DSignal domain delay a -> DSignal domain delay a # (*) :: DSignal domain delay a -> DSignal domain delay a -> DSignal domain delay a # negate :: DSignal domain delay a -> DSignal domain delay a # abs :: DSignal domain delay a -> DSignal domain delay a # signum :: DSignal domain delay a -> DSignal domain delay a # fromInteger :: Integer -> DSignal domain delay a # |
The Ord
class is used for totally ordered datatypes.
Instances of Ord
can be derived for any user-defined
datatype whose constituent types are in Ord
. The declared order
of the constructors in the data declaration determines the ordering
in derived Ord
instances. The Ordering
datatype allows a single
comparison to determine the precise ordering of two objects.
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
Methods
compare :: a -> a -> Ordering #
(<) :: a -> a -> Bool infix 4 #
(<=) :: a -> a -> Bool infix 4 #
(>) :: a -> a -> Bool infix 4 #
Instances
Ord Bool | |
Ord Char | |
Ord Double | |
Ord Float | |
Ord Int | |
Ord Int8 | Since: 2.1 |
Ord Int16 | Since: 2.1 |
Ord Int32 | Since: 2.1 |
Ord Int64 | Since: 2.1 |
Ord Integer | |
Ord Natural | |
Ord Ordering | |
Ord Word | |
Ord Word8 | Since: 2.1 |
Ord Word16 | Since: 2.1 |
Ord Word32 | Since: 2.1 |
Ord Word64 | Since: 2.1 |
Ord SomeTypeRep | |
Methods compare :: SomeTypeRep -> SomeTypeRep -> Ordering # (<) :: SomeTypeRep -> SomeTypeRep -> Bool # (<=) :: SomeTypeRep -> SomeTypeRep -> Bool # (>) :: SomeTypeRep -> SomeTypeRep -> Bool # (>=) :: SomeTypeRep -> SomeTypeRep -> Bool # max :: SomeTypeRep -> SomeTypeRep -> SomeTypeRep # min :: SomeTypeRep -> SomeTypeRep -> SomeTypeRep # | |
Ord Exp | |
Ord Match | |
Ord Clause | |
Ord Pat | |
Ord Type | |
Ord Dec | |
Ord Name | |
Ord FunDep | |
Ord InjectivityAnn | |
Methods compare :: InjectivityAnn -> InjectivityAnn -> Ordering # (<) :: InjectivityAnn -> InjectivityAnn -> Bool # (<=) :: InjectivityAnn -> InjectivityAnn -> Bool # (>) :: InjectivityAnn -> InjectivityAnn -> Bool # (>=) :: InjectivityAnn -> InjectivityAnn -> Bool # max :: InjectivityAnn -> InjectivityAnn -> InjectivityAnn # min :: InjectivityAnn -> InjectivityAnn -> InjectivityAnn # | |
Ord Overlap | |
Ord DerivStrategy | |
Methods compare :: DerivStrategy -> DerivStrategy -> Ordering # (<) :: DerivStrategy -> DerivStrategy -> Bool # (<=) :: DerivStrategy -> DerivStrategy -> Bool # (>) :: DerivStrategy -> DerivStrategy -> Bool # (>=) :: DerivStrategy -> DerivStrategy -> Bool # max :: DerivStrategy -> DerivStrategy -> DerivStrategy # min :: DerivStrategy -> DerivStrategy -> DerivStrategy # | |
Ord () | |
Ord TyCon | |
Ord BigNat | |
Ord Void | Since: 4.8.0.0 |
Ord Unique | |
Ord Version | Since: 2.1 |
Ord ThreadId | Since: 4.2.0.0 |
Ord BlockReason | |
Methods compare :: BlockReason -> BlockReason -> Ordering # (<) :: BlockReason -> BlockReason -> Bool # (<=) :: BlockReason -> BlockReason -> Bool # (>) :: BlockReason -> BlockReason -> Bool # (>=) :: BlockReason -> BlockReason -> Bool # max :: BlockReason -> BlockReason -> BlockReason # min :: BlockReason -> BlockReason -> BlockReason # | |
Ord ThreadStatus | |
Methods compare :: ThreadStatus -> ThreadStatus -> Ordering # (<) :: ThreadStatus -> ThreadStatus -> Bool # (<=) :: ThreadStatus -> ThreadStatus -> Bool # (>) :: ThreadStatus -> ThreadStatus -> Bool # (>=) :: ThreadStatus -> ThreadStatus -> Bool # max :: ThreadStatus -> ThreadStatus -> ThreadStatus # min :: ThreadStatus -> ThreadStatus -> ThreadStatus # | |
Ord AsyncException | |
Methods compare :: AsyncException -> AsyncException -> Ordering # (<) :: AsyncException -> AsyncException -> Bool # (<=) :: AsyncException -> AsyncException -> Bool # (>) :: AsyncException -> AsyncException -> Bool # (>=) :: AsyncException -> AsyncException -> Bool # max :: AsyncException -> AsyncException -> AsyncException # min :: AsyncException -> AsyncException -> AsyncException # | |
Ord ArrayException | |
Methods compare :: ArrayException -> ArrayException -> Ordering # (<) :: ArrayException -> ArrayException -> Bool # (<=) :: ArrayException -> ArrayException -> Bool # (>) :: ArrayException -> ArrayException -> Bool # (>=) :: ArrayException -> ArrayException -> Bool # max :: ArrayException -> ArrayException -> ArrayException # min :: ArrayException -> ArrayException -> ArrayException # | |
Ord ExitCode | |
Ord ErrorCall | |
Ord ArithException | |
Methods compare :: ArithException -> ArithException -> Ordering # (<) :: ArithException -> ArithException -> Bool # (<=) :: ArithException -> ArithException -> Bool # (>) :: ArithException -> ArithException -> Bool # (>=) :: ArithException -> ArithException -> Bool # max :: ArithException -> ArithException -> ArithException # min :: ArithException -> ArithException -> ArithException # | |
Ord All | |
Ord Any | |
Ord Fixity | |
Ord Associativity | |
Methods compare :: Associativity -> Associativity -> Ordering # (<) :: Associativity -> Associativity -> Bool # (<=) :: Associativity -> Associativity -> Bool # (>) :: Associativity -> Associativity -> Bool # (>=) :: Associativity -> Associativity -> Bool # max :: Associativity -> Associativity -> Associativity # min :: Associativity -> Associativity -> Associativity # | |
Ord SourceUnpackedness | |
Methods compare :: SourceUnpackedness -> SourceUnpackedness -> Ordering # (<) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (<=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (>) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (>=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # max :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness # min :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness # | |
Ord SourceStrictness | |
Methods compare :: SourceStrictness -> SourceStrictness -> Ordering # (<) :: SourceStrictness -> SourceStrictness -> Bool # (<=) :: SourceStrictness -> SourceStrictness -> Bool # (>) :: SourceStrictness -> SourceStrictness -> Bool # (>=) :: SourceStrictness -> SourceStrictness -> Bool # max :: SourceStrictness -> SourceStrictness -> SourceStrictness # min :: SourceStrictness -> SourceStrictness -> SourceStrictness # | |
Ord DecidedStrictness | |
Methods compare :: DecidedStrictness -> DecidedStrictness -> Ordering # (<) :: DecidedStrictness -> DecidedStrictness -> Bool # (<=) :: DecidedStrictness -> DecidedStrictness -> Bool # (>) :: DecidedStrictness -> DecidedStrictness -> Bool # (>=) :: DecidedStrictness -> DecidedStrictness -> Bool # max :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness # min :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness # | |
Ord SomeSymbol | Since: 4.7.0.0 |
Methods compare :: SomeSymbol -> SomeSymbol -> Ordering # (<) :: SomeSymbol -> SomeSymbol -> Bool # (<=) :: SomeSymbol -> SomeSymbol -> Bool # (>) :: SomeSymbol -> SomeSymbol -> Bool # (>=) :: SomeSymbol -> SomeSymbol -> Bool # max :: SomeSymbol -> SomeSymbol -> SomeSymbol # min :: SomeSymbol -> SomeSymbol -> SomeSymbol # | |
Ord SomeNat | Since: 4.7.0.0 |
Ord CChar | |
Ord CSChar | |
Ord CUChar | |
Ord CShort | |
Ord CUShort | |
Ord CInt | |
Ord CUInt | |
Ord CLong | |
Ord CULong | |
Ord CLLong | |
Ord CULLong | |
Ord CBool | |
Ord CFloat | |
Ord CDouble | |
Ord CPtrdiff | |
Ord CSize | |
Ord CWchar | |
Ord CSigAtomic | |
Methods compare :: CSigAtomic -> CSigAtomic -> Ordering # (<) :: CSigAtomic -> CSigAtomic -> Bool # (<=) :: CSigAtomic -> CSigAtomic -> Bool # (>) :: CSigAtomic -> CSigAtomic -> Bool # (>=) :: CSigAtomic -> CSigAtomic -> Bool # max :: CSigAtomic -> CSigAtomic -> CSigAtomic # min :: CSigAtomic -> CSigAtomic -> CSigAtomic # | |
Ord CClock | |
Ord CTime | |
Ord CUSeconds | |
Ord CSUSeconds | |
Methods compare :: CSUSeconds -> CSUSeconds -> Ordering # (<) :: CSUSeconds -> CSUSeconds -> Bool # (<=) :: CSUSeconds -> CSUSeconds -> Bool # (>) :: CSUSeconds -> CSUSeconds -> Bool # (>=) :: CSUSeconds -> CSUSeconds -> Bool # max :: CSUSeconds -> CSUSeconds -> CSUSeconds # min :: CSUSeconds -> CSUSeconds -> CSUSeconds # | |
Ord CIntPtr | |
Ord CUIntPtr | |
Ord CIntMax | |
Ord CUIntMax | |
Ord Fingerprint | |
Methods compare :: Fingerprint -> Fingerprint -> Ordering # (<) :: Fingerprint -> Fingerprint -> Bool # (<=) :: Fingerprint -> Fingerprint -> Bool # (>) :: Fingerprint -> Fingerprint -> Bool # (>=) :: Fingerprint -> Fingerprint -> Bool # max :: Fingerprint -> Fingerprint -> Fingerprint # min :: Fingerprint -> Fingerprint -> Fingerprint # | |
Ord GeneralCategory | |
Methods compare :: GeneralCategory -> GeneralCategory -> Ordering # (<) :: GeneralCategory -> GeneralCategory -> Bool # (<=) :: GeneralCategory -> GeneralCategory -> Bool # (>) :: GeneralCategory -> GeneralCategory -> Bool # (>=) :: GeneralCategory -> GeneralCategory -> Bool # max :: GeneralCategory -> GeneralCategory -> GeneralCategory # min :: GeneralCategory -> GeneralCategory -> GeneralCategory # | |
Ord ByteString | |
Methods compare :: ByteString -> ByteString -> Ordering # (<) :: ByteString -> ByteString -> Bool # (<=) :: ByteString -> ByteString -> Bool # (>) :: ByteString -> ByteString -> Bool # (>=) :: ByteString -> ByteString -> Bool # max :: ByteString -> ByteString -> ByteString # min :: ByteString -> ByteString -> ByteString # | |
Ord ByteString | |
Methods compare :: ByteString -> ByteString -> Ordering # (<) :: ByteString -> ByteString -> Bool # (<=) :: ByteString -> ByteString -> Bool # (>) :: ByteString -> ByteString -> Bool # (>=) :: ByteString -> ByteString -> Bool # max :: ByteString -> ByteString -> ByteString # min :: ByteString -> ByteString -> ByteString # | |
Ord IntSet | |
Ord TyVarBndr | |
Ord ModName | |
Ord PkgName | |
Ord Module | |
Ord OccName | |
Ord NameFlavour | |
Methods compare :: NameFlavour -> NameFlavour -> Ordering # (<) :: NameFlavour -> NameFlavour -> Bool # (<=) :: NameFlavour -> NameFlavour -> Bool # (>) :: NameFlavour -> NameFlavour -> Bool # (>=) :: NameFlavour -> NameFlavour -> Bool # max :: NameFlavour -> NameFlavour -> NameFlavour # min :: NameFlavour -> NameFlavour -> NameFlavour # | |
Ord NameSpace | |
Ord Loc | |
Ord Info | |
Ord ModuleInfo | |
Methods compare :: ModuleInfo -> ModuleInfo -> Ordering # (<) :: ModuleInfo -> ModuleInfo -> Bool # (<=) :: ModuleInfo -> ModuleInfo -> Bool # (>) :: ModuleInfo -> ModuleInfo -> Bool # (>=) :: ModuleInfo -> ModuleInfo -> Bool # max :: ModuleInfo -> ModuleInfo -> ModuleInfo # min :: ModuleInfo -> ModuleInfo -> ModuleInfo # | |
Ord Fixity | |
Ord FixityDirection | |
Methods compare :: FixityDirection -> FixityDirection -> Ordering # (<) :: FixityDirection -> FixityDirection -> Bool # (<=) :: FixityDirection -> FixityDirection -> Bool # (>) :: FixityDirection -> FixityDirection -> Bool # (>=) :: FixityDirection -> FixityDirection -> Bool # max :: FixityDirection -> FixityDirection -> FixityDirection # min :: FixityDirection -> FixityDirection -> FixityDirection # | |
Ord Lit | |
Ord Body | |
Ord Guard | |
Ord Stmt | |
Ord Range | |
Ord DerivClause | |
Methods compare :: DerivClause -> DerivClause -> Ordering # (<) :: DerivClause -> DerivClause -> Bool # (<=) :: DerivClause -> DerivClause -> Bool # (>) :: DerivClause -> DerivClause -> Bool # (>=) :: DerivClause -> DerivClause -> Bool # max :: DerivClause -> DerivClause -> DerivClause # min :: DerivClause -> DerivClause -> DerivClause # | |
Ord TypeFamilyHead | |
Methods compare :: TypeFamilyHead -> TypeFamilyHead -> Ordering # (<) :: TypeFamilyHead -> TypeFamilyHead -> Bool # (<=) :: TypeFamilyHead -> TypeFamilyHead -> Bool # (>) :: TypeFamilyHead -> TypeFamilyHead -> Bool # (>=) :: TypeFamilyHead -> TypeFamilyHead -> Bool # max :: TypeFamilyHead -> TypeFamilyHead -> TypeFamilyHead # min :: TypeFamilyHead -> TypeFamilyHead -> TypeFamilyHead # | |
Ord TySynEqn | |
Ord Foreign | |
Ord Callconv | |
Ord Safety | |
Ord Pragma | |
Ord Inline | |
Ord RuleMatch | |
Ord Phases | |
Ord RuleBndr | |
Ord AnnTarget | |
Ord SourceUnpackedness | |
Methods compare :: SourceUnpackedness -> SourceUnpackedness -> Ordering # (<) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (<=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (>) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (>=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # max :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness # min :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness # | |
Ord SourceStrictness | |
Methods compare :: SourceStrictness -> SourceStrictness -> Ordering # (<) :: SourceStrictness -> SourceStrictness -> Bool # (<=) :: SourceStrictness -> SourceStrictness -> Bool # (>) :: SourceStrictness -> SourceStrictness -> Bool # (>=) :: SourceStrictness -> SourceStrictness -> Bool # max :: SourceStrictness -> SourceStrictness -> SourceStrictness # min :: SourceStrictness -> SourceStrictness -> SourceStrictness # | |
Ord DecidedStrictness | |
Methods compare :: DecidedStrictness -> DecidedStrictness -> Ordering # (<) :: DecidedStrictness -> DecidedStrictness -> Bool # (<=) :: DecidedStrictness -> DecidedStrictness -> Bool # (>) :: DecidedStrictness -> DecidedStrictness -> Bool # (>=) :: DecidedStrictness -> DecidedStrictness -> Bool # max :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness # min :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness # | |
Ord Con | |
Ord Bang | |
Ord PatSynDir | |
Ord PatSynArgs | |
Methods compare :: PatSynArgs -> PatSynArgs -> Ordering # (<) :: PatSynArgs -> PatSynArgs -> Bool # (<=) :: PatSynArgs -> PatSynArgs -> Bool # (>) :: PatSynArgs -> PatSynArgs -> Bool # (>=) :: PatSynArgs -> PatSynArgs -> Bool # max :: PatSynArgs -> PatSynArgs -> PatSynArgs # min :: PatSynArgs -> PatSynArgs -> PatSynArgs # | |
Ord FamilyResultSig | |
Methods compare :: FamilyResultSig -> FamilyResultSig -> Ordering # (<) :: FamilyResultSig -> FamilyResultSig -> Bool # (<=) :: FamilyResultSig -> FamilyResultSig -> Bool # (>) :: FamilyResultSig -> FamilyResultSig -> Bool # (>=) :: FamilyResultSig -> FamilyResultSig -> Bool # max :: FamilyResultSig -> FamilyResultSig -> FamilyResultSig # min :: FamilyResultSig -> FamilyResultSig -> FamilyResultSig # | |
Ord TyLit | |
Ord Role | |
Ord AnnLookup | |
Ord LocalTime | |
Ord UniversalTime | |
Methods compare :: UniversalTime -> UniversalTime -> Ordering # (<) :: UniversalTime -> UniversalTime -> Bool # (<=) :: UniversalTime -> UniversalTime -> Bool # (>) :: UniversalTime -> UniversalTime -> Bool # (>=) :: UniversalTime -> UniversalTime -> Bool # max :: UniversalTime -> UniversalTime -> UniversalTime # min :: UniversalTime -> UniversalTime -> UniversalTime # | |
Ord UTCTime | |
Ord Day | |
Ord Bit # | |
Ord DefName | |
Ord TimeLocale | |
Ord ByteArray | |
Ord Addr | |
Ord ConstructorVariant | |
Methods compare :: ConstructorVariant -> ConstructorVariant -> Ordering # (<) :: ConstructorVariant -> ConstructorVariant -> Bool # (<=) :: ConstructorVariant -> ConstructorVariant -> Bool # (>) :: ConstructorVariant -> ConstructorVariant -> Bool # (>=) :: ConstructorVariant -> ConstructorVariant -> Bool # max :: ConstructorVariant -> ConstructorVariant -> ConstructorVariant # min :: ConstructorVariant -> ConstructorVariant -> ConstructorVariant # | |
Ord DatatypeVariant | |
Methods compare :: DatatypeVariant -> DatatypeVariant -> Ordering # (<) :: DatatypeVariant -> DatatypeVariant -> Bool # (<=) :: DatatypeVariant -> DatatypeVariant -> Bool # (>) :: DatatypeVariant -> DatatypeVariant -> Bool # (>=) :: DatatypeVariant -> DatatypeVariant -> Bool # max :: DatatypeVariant -> DatatypeVariant -> DatatypeVariant # min :: DatatypeVariant -> DatatypeVariant -> DatatypeVariant # | |
Ord FieldStrictness | |
Methods compare :: FieldStrictness -> FieldStrictness -> Ordering # (<) :: FieldStrictness -> FieldStrictness -> Bool # (<=) :: FieldStrictness -> FieldStrictness -> Bool # (>) :: FieldStrictness -> FieldStrictness -> Bool # (>=) :: FieldStrictness -> FieldStrictness -> Bool # max :: FieldStrictness -> FieldStrictness -> FieldStrictness # min :: FieldStrictness -> FieldStrictness -> FieldStrictness # | |
Ord Strictness | |
Ord Unpackedness | |
Ord Half | |
Ord ResetKind # | |
Ord ClockKind # | |
() :=> (Ord Bool) | |
() :=> (Ord Char) | |
() :=> (Ord Double) | |
() :=> (Ord Float) | |
() :=> (Ord Int) | |
() :=> (Ord Integer) | |
() :=> (Ord Natural) | |
() :=> (Ord Word) | |
() :=> (Ord ()) | |
() :=> (Ord (a :- b)) | |
() :=> (Ord (Dict a)) | |
Ord a => Ord [a] | |
Ord a => Ord (Maybe a) | |
Integral a => Ord (Ratio a) | Since: 2.0.1 |
Ord (Ptr a) | |
Ord (FunPtr a) | |
Ord p => Ord (Par1 p) | |
Ord (Fixed a) | |
Ord a => Ord (Min a) | |
Ord a => Ord (Max a) | |
Ord a => Ord (First a) | |
Ord a => Ord (Last a) | |
Ord m => Ord (WrappedMonoid m) | |
Methods compare :: WrappedMonoid m -> WrappedMonoid m -> Ordering # (<) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (<=) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (>) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (>=) :: WrappedMonoid m -> WrappedMonoid m -> Bool # max :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # min :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # | |
Ord a => Ord (Option a) | |
Ord a => Ord (ZipList a) | |
Ord a => Ord (Identity a) | |
Ord a => Ord (First a) | |
Ord a => Ord (Last a) | |
Ord a => Ord (Dual a) | |
Ord a => Ord (Sum a) | |
Ord a => Ord (Product a) | |
Ord a => Ord (Down a) | Since: 4.6.0.0 |
Ord a => Ord (NonEmpty a) | |
Ord a => Ord (IntMap a) | |
Ord a => Ord (Seq a) | |
Ord a => Ord (ViewL a) | |
Ord a => Ord (ViewR a) | |
Ord a => Ord (Set a) | |
Ord (BitVector n) # | |
Ord (Index n) # | |
Ord a => Ord (Bounds a) | |
Ord a => Ord (DList a) | |
Ord a => Ord (HashSet a) | |
(Storable a, Ord a) => Ord (Vector a) | |
(Prim a, Ord a) => Ord (Vector a) | |
Ord a => Ord (Vector a) | |
Ord a => Ord (Array a) | |
Ord (Unsigned n) # | |
Ord (Signed n) # | |
Ord (Dict a) | |
(Integral a) :=> (Ord (Ratio a)) | |
(Ord a) :=> (Ord (Maybe a)) | |
(Ord a) :=> (Ord [a]) | |
(Ord a) :=> (Ord (Identity a)) | |
(Ord a) :=> (Ord (Const a b)) | |
Class (Eq a) (Ord a) | |
(Ord a, Ord b) => Ord (Either a b) | |
Ord (V1 p) | Since: 4.9.0.0 |
Ord (U1 p) | Since: 4.9.0.0 |
Ord (TypeRep a) | Since: 4.4.0.0 |
(Ord a, Ord b) => Ord (a, b) | |
(Ix i, Ord e) => Ord (Array i e) | Since: 2.1 |
Ord a => Ord (Arg a b) | Since: 4.9.0.0 |
Ord (Proxy s) | Since: 4.7.0.0 |
(Ord k, Ord v) => Ord (Map k v) | |
(KnownNat n, Ord a) => Ord (Vec n a) # | |
(Ord i, Ord a) => Ord (Level i a) | |
(Ord1 f, Ord a) => Ord (Cofree f a) | |
(Ord1 f, Ord a) => Ord (Free f a) | |
(Ord1 f, Ord a) => Ord (Yoneda f a) | |
(Ord k, Ord v) => Ord (HashMap k v) | |
(KnownNat d, Ord a) => Ord (RTree d a) # | |
Ord (a :- b) | |
(Ord a, Ord b) :=> (Ord (a, b)) | |
(Ord a, Ord b) :=> (Ord (Either a b)) | |
Class (Num a, Ord a) (Real a) | |
Ord (f p) => Ord (Rec1 f p) | |
Ord (URec (Ptr ()) p) | |
Methods compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # | |
Ord (URec Char p) | |
Ord (URec Double p) | |
Methods compare :: URec Double p -> URec Double p -> Ordering # (<) :: URec Double p -> URec Double p -> Bool # (<=) :: URec Double p -> URec Double p -> Bool # (>) :: URec Double p -> URec Double p -> Bool # (>=) :: URec Double p -> URec Double p -> Bool # | |
Ord (URec Float p) | |
Ord (URec Int p) | |
Ord (URec Word p) | |
(Ord a, Ord b, Ord c) => Ord (a, b, c) | |
Ord a => Ord (Const a b) | |
Ord (f a) => Ord (Alt f a) | |
Ord (a :~: b) | |
(Ord e, Ord1 m, Ord a) => Ord (ErrorT e m a) | |
Ord a => Ord (Constant a b) | |
Ord b => Ord (Tagged s b) | |
Ord (p (Fix p a) a) => Ord (Fix p a) | |
Ord (p a a) => Ord (Join p a) | |
(Ord a, Ord (f b)) => Ord (CofreeF f a b) | |
Methods compare :: CofreeF f a b -> CofreeF f a b -> Ordering # (<) :: CofreeF f a b -> CofreeF f a b -> Bool # (<=) :: CofreeF f a b -> CofreeF f a b -> Bool # (>) :: CofreeF f a b -> CofreeF f a b -> Bool # (>=) :: CofreeF f a b -> CofreeF f a b -> Bool # | |
Ord (w (CofreeF f a (CofreeT f w a))) => Ord (CofreeT f w a) | |
Methods compare :: CofreeT f w a -> CofreeT f w a -> Ordering # (<) :: CofreeT f w a -> CofreeT f w a -> Bool # (<=) :: CofreeT f w a -> CofreeT f w a -> Bool # (>) :: CofreeT f w a -> CofreeT f w a -> Bool # (>=) :: CofreeT f w a -> CofreeT f w a -> Bool # | |
(Ord1 f, Ord1 m, Ord a) => Ord (FreeT f m a) | |
(Ord a, Ord (f b)) => Ord (FreeF f a b) | |
Ord (rep (int + frac)) => Ord (Fixed rep int frac) # | |
Methods compare :: Fixed rep int frac -> Fixed rep int frac -> Ordering # (<) :: Fixed rep int frac -> Fixed rep int frac -> Bool # (<=) :: Fixed rep int frac -> Fixed rep int frac -> Bool # (>) :: Fixed rep int frac -> Fixed rep int frac -> Bool # (>=) :: Fixed rep int frac -> Fixed rep int frac -> Bool # max :: Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac # min :: Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac # | |
Ord c => Ord (K1 i c p) | |
(Ord (f p), Ord (g p)) => Ord ((f :+: g) p) | |
(Ord (f p), Ord (g p)) => Ord ((f :*: g) p) | |
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |
(Ord1 f, Ord1 g, Ord a) => Ord (Product f g a) | Since: 4.9.0.0 |
Methods compare :: Product f g a -> Product f g a -> Ordering # (<) :: Product f g a -> Product f g a -> Bool # (<=) :: Product f g a -> Product f g a -> Bool # (>) :: Product f g a -> Product f g a -> Bool # (>=) :: Product f g a -> Product f g a -> Bool # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a) | Since: 4.9.0.0 |
Ord (a :~~: b) | Since: 4.10.0.0 |
Ord (f p) => Ord (M1 i c f p) | |
Ord (f (g p)) => Ord ((f :.: g) p) | |
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) | |
Methods compare :: (a, b, c, d, e) -> (a, b, c, d, e) -> Ordering # (<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (<=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # max :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) # min :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Compose f g a) | Since: 4.9.0.0 |
Methods compare :: Compose f g a -> Compose f g a -> Ordering # (<) :: Compose f g a -> Compose f g a -> Bool # (<=) :: Compose f g a -> Compose f g a -> Bool # (>) :: Compose f g a -> Compose f g a -> Bool # (>=) :: Compose f g a -> Compose f g a -> Bool # | |
Ord (f a) => Ord (Clown f a b) | |
Ord (p b a) => Ord (Flip p a b) | |
Ord (g b) => Ord (Joker g a b) | |
Ord (p a b) => Ord (WrappedBifunctor p a b) | |
Methods compare :: WrappedBifunctor p a b -> WrappedBifunctor p a b -> Ordering # (<) :: WrappedBifunctor p a b -> WrappedBifunctor p a b -> Bool # (<=) :: WrappedBifunctor p a b -> WrappedBifunctor p a b -> Bool # (>) :: WrappedBifunctor p a b -> WrappedBifunctor p a b -> Bool # (>=) :: WrappedBifunctor p a b -> WrappedBifunctor p a b -> Bool # max :: WrappedBifunctor p a b -> WrappedBifunctor p a b -> WrappedBifunctor p a b # min :: WrappedBifunctor p a b -> WrappedBifunctor p a b -> WrappedBifunctor p a b # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) | |
Methods compare :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Ordering # (<) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (>) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # max :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) # min :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) # | |
(Ord (f a b), Ord (g a b)) => Ord (Product f g a b) | |
Methods compare :: Product f g a b -> Product f g a b -> Ordering # (<) :: Product f g a b -> Product f g a b -> Bool # (<=) :: Product f g a b -> Product f g a b -> Bool # (>) :: Product f g a b -> Product f g a b -> Bool # (>=) :: Product f g a b -> Product f g a b -> Bool # max :: Product f g a b -> Product f g a b -> Product f g a b # min :: Product f g a b -> Product f g a b -> Product f g a b # | |
(Ord (p a b), Ord (q a b)) => Ord (Sum p q a b) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) | |
Methods compare :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Ordering # (<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (>) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # max :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) # min :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) # | |
Ord (f (p a b)) => Ord (Tannen f p a b) | |
Methods compare :: Tannen f p a b -> Tannen f p a b -> Ordering # (<) :: Tannen f p a b -> Tannen f p a b -> Bool # (<=) :: Tannen f p a b -> Tannen f p a b -> Bool # (>) :: Tannen f p a b -> Tannen f p a b -> Bool # (>=) :: Tannen f p a b -> Tannen f p a b -> Bool # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) | |
Methods compare :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Ordering # (<) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (<=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (>) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (>=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # max :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) # min :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) | |
Methods compare :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # max :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) # min :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) # | |
Ord (p (f a) (g b)) => Ord (Biff p f g a b) | |
Methods compare :: Biff p f g a b -> Biff p f g a b -> Ordering # (<) :: Biff p f g a b -> Biff p f g a b -> Bool # (<=) :: Biff p f g a b -> Biff p f g a b -> Bool # (>) :: Biff p f g a b -> Biff p f g a b -> Bool # (>=) :: Biff p f g a b -> Biff p f g a b -> Bool # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) | |
Methods compare :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) # min :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) | |
Methods compare :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) # min :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) | |
Methods compare :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) # min :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
Methods compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
Methods compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
Methods compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Ordering # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) # |
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
Methods
Arguments
:: 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 Bool | Since: 2.1 |
Read Char | Since: 2.1 |
Read Double | Since: 2.1 |
Read Float | Since: 2.1 |
Read Int | Since: 2.1 |
Read Int8 | Since: 2.1 |
Read Int16 | Since: 2.1 |
Read Int32 | Since: 2.1 |
Read Int64 | Since: 2.1 |
Read Integer | Since: 2.1 |
Read Natural | Since: 4.8.0.0 |
Read Ordering | Since: 2.1 |
Read Word | Since: 4.5.0.0 |
Read Word8 | Since: 2.1 |
Read Word16 | Since: 2.1 |
Read Word32 | Since: 2.1 |
Read Word64 | Since: 2.1 |
Read () | Since: 2.1 |
Read Void | Reading a Since: 4.8.0.0 |
Read Version | |
Read ExitCode | |
Read All | |
Read Any | |
Read Fixity | |
Read Associativity | |
Methods readsPrec :: Int -> ReadS Associativity # readList :: ReadS [Associativity] # | |
Read SourceUnpackedness | |
Methods readsPrec :: Int -> ReadS SourceUnpackedness # readList :: ReadS [SourceUnpackedness] # | |
Read SourceStrictness | |
Methods readsPrec :: Int -> ReadS SourceStrictness # readList :: ReadS [SourceStrictness] # | |
Read DecidedStrictness | |
Methods readsPrec :: Int -> ReadS DecidedStrictness # readList :: ReadS [DecidedStrictness] # | |
Read SomeSymbol | Since: 4.7.0.0 |
Methods readsPrec :: Int -> ReadS SomeSymbol # readList :: ReadS [SomeSymbol] # readPrec :: ReadPrec SomeSymbol # readListPrec :: ReadPrec [SomeSymbol] # | |
Read SomeNat | Since: 4.7.0.0 |
Read CChar | |
Read CSChar | |
Read CUChar | |
Read CShort | |
Read CUShort | |
Read CInt | |
Read CUInt | |
Read CLong | |
Read CULong | |
Read CLLong | |
Read CULLong | |
Read CBool | |
Read CFloat | |
Read CDouble | |
Read CPtrdiff | |
Read CSize | |
Read CWchar | |
Read CSigAtomic | |
Methods readsPrec :: Int -> ReadS CSigAtomic # readList :: ReadS [CSigAtomic] # readPrec :: ReadPrec CSigAtomic # readListPrec :: ReadPrec [CSigAtomic] # | |
Read CClock | |
Read CTime | |
Read CUSeconds | |
Read CSUSeconds | |
Methods readsPrec :: Int -> ReadS CSUSeconds # readList :: ReadS [CSUSeconds] # readPrec :: ReadPrec CSUSeconds # readListPrec :: ReadPrec [CSUSeconds] # | |
Read CIntPtr | |
Read CUIntPtr | |
Read CIntMax | |
Read CUIntMax | |
Read Lexeme | Since: 2.1 |
Read GeneralCategory | |
Methods readsPrec :: Int -> ReadS GeneralCategory # readList :: ReadS [GeneralCategory] # | |
Read ByteString | |
Methods readsPrec :: Int -> ReadS ByteString # readList :: ReadS [ByteString] # readPrec :: ReadPrec ByteString # readListPrec :: ReadPrec [ByteString] # | |
Read ByteString | |
Methods readsPrec :: Int -> ReadS ByteString # readList :: ReadS [ByteString] # readPrec :: ReadPrec ByteString # readListPrec :: ReadPrec [ByteString] # | |
Read IntSet | |
Read Primitive # | |
Read HDL # | |
Read QCGen | |
Read DatatypeVariant | |
Read Half | |
a :=> (Read (Dict a)) | |
() :=> (Read Bool) | |
() :=> (Read Char) | |
() :=> (Read Int) | |
() :=> (Read Natural) | |
() :=> (Read Ordering) | |
() :=> (Read Word) | |
() :=> (Read ()) | |
Class () (Read a) | |
Read a => Read [a] | Since: 2.1 |
Read a => Read (Maybe a) | Since: 2.1 |
(Integral a, Read a) => Read (Ratio a) | Since: 2.1 |
Read p => Read (Par1 p) | |
Read a => Read (Complex a) | |
HasResolution a => Read (Fixed a) | Since: 4.3.0.0 |
Read a => Read (Min a) | |
Read a => Read (Max a) | |
Read a => Read (First a) | |
Read a => Read (Last a) | |
Read m => Read (WrappedMonoid m) | |
Methods readsPrec :: Int -> ReadS (WrappedMonoid m) # readList :: ReadS [WrappedMonoid m] # readPrec :: ReadPrec (WrappedMonoid m) # readListPrec :: ReadPrec [WrappedMonoid m] # | |
Read a => Read (Option a) | |
Read a => Read (ZipList a) | |
Read a => Read (Identity a) | This instance would be equivalent to the derived instances of the
Since: 4.8.0.0 |
Read a => Read (First a) | |
Read a => Read (Last a) | |
Read a => Read (Dual a) | |
Read a => Read (Sum a) | |
Read a => Read (Product a) | |
Read a => Read (Down a) | Since: 4.7.0.0 |
Read a => Read (NonEmpty a) | |
Read e => Read (IntMap e) | |
Read a => Read (Tree a) | |
Read a => Read (Seq a) | |
Read a => Read (ViewL a) | |
Read a => Read (ViewR a) | |
(Read a, Ord a) => Read (Set a) | |
KnownNat n => Read (Index n) # | None of the |
Read a => Read (DList a) | |
(Eq a, Hashable a, Read a) => Read (HashSet a) | |
(Read a, Storable a) => Read (Vector a) | |
(Read a, Prim a) => Read (Vector a) | |
Read a => Read (Vector a) | |
Read a => Read (Array a) | |
KnownNat n => Read (Unsigned n) # | None of the |
KnownNat n => Read (Signed n) # | None of the |
a => Read (Dict a) | |
(Read a) :=> (Read (Complex a)) | |
(Read a) :=> (Read [a]) | |
(Read a) :=> (Read (Maybe a)) | |
(Read a) :=> (Read (Identity a)) | |
(Read a) :=> (Read (Const a b)) | |
(Read a, Read b) => Read (Either a b) | |
Read (V1 p) | Since: 4.9.0.0 |
Read (U1 p) | Since: 4.9.0.0 |
(Read a, Read b) => Read (a, b) | Since: 2.1 |
(Ix a, Read a, Read b) => Read (Array a b) | Since: 2.1 |
(Read a, Read b) => Read (Arg a b) | |
Read (Proxy t) | Since: 4.7.0.0 |
(Ord k, Read k, Read e) => Read (Map k e) | |
(Read i, Read a) => Read (Level i a) | |
(Read1 f, Read a) => Read (Cofree f a) | |
(Read1 f, Read a) => Read (Free f a) | |
(Functor f, Read (f a)) => Read (Yoneda f a) | |
(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) | |
(Integral a, Read a) :=> (Read (Ratio a)) | |
(Read a, Read b) :=> (Read (a, b)) | |
(Read a, Read b) :=> (Read (Either a b)) | |
Read (f p) => Read (Rec1 f p) | |
(Read a, Read b, Read c) => Read (a, b, c) | Since: 2.1 |
Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: 4.8.0.0 |
Read (f a) => Read (Alt f a) | |
a ~ b => Read (a :~: b) | Since: 4.7.0.0 |
(Read e, Read1 m, Read a) => Read (ErrorT e m a) | |
Read a => Read (Constant a b) | |
Read b => Read (Tagged s b) | |
Read (p (Fix p a) a) => Read (Fix p a) | |
Read (p a a) => Read (Join p a) | |
(Read a, Read (f b)) => Read (CofreeF f a b) | |
Read (w (CofreeF f a (CofreeT f w a))) => Read (CofreeT f w a) | |
(Read1 f, Read1 m, Read a) => Read (FreeT f m a) | |
(Read a, Read (f b)) => Read (FreeF f a b) | |
(size ~ (int + frac), KnownNat frac, Bounded (rep size), Integral (rep size)) => Read (Fixed rep int frac) # | None of the |
Read c => Read (K1 i c p) | |
(Read (f p), Read (g p)) => Read ((f :+: g) p) | |
(Read (f p), Read (g p)) => Read ((f :*: g) p) | |
(Read a, Read b, Read c, Read d) => Read (a, b, c, d) | Since: 2.1 |
(Read1 f, Read1 g, Read a) => Read (Product f g a) | Since: 4.9.0.0 |
(Read1 f, Read1 g, Read a) => Read (Sum f g a) | Since: 4.9.0.0 |
a ~~ b => Read (a :~~: b) | Since: 4.10.0.0 |
Read (f p) => Read (M1 i c f p) | |
Read (f (g p)) => Read ((f :.: g) p) | |
(Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) | Since: 2.1 |
(Read1 f, Read1 g, Read a) => Read (Compose f g a) | Since: 4.9.0.0 |
Read (f a) => Read (Clown f a b) | |
Read (p b a) => Read (Flip p a b) | |
Read (g b) => Read (Joker g a b) | |
Read (p a b) => Read (WrappedBifunctor p a b) | |
(Read a, Read b, Read c, Read d, Read e, Read f) => Read (a, b, c, d, e, f) | Since: 2.1 |
(Read (f a b), Read (g a b)) => Read (Product f g a b) | |
(Read (p a b), Read (q a b)) => Read (Sum p q a b) | |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g) => Read (a, b, c, d, e, f, g) | Since: 2.1 |
Read (f (p a b)) => Read (Tannen f p a b) | |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) => Read (a, b, c, d, e, f, g, h) | Since: 2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i) => Read (a, b, c, d, e, f, g, h, i) | Since: 2.1 |
Read (p (f a) (g b)) => Read (Biff p f g a b) | |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j) => Read (a, b, c, d, e, f, g, h, i, j) | Since: 2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k) => Read (a, b, c, d, e, f, g, h, i, j, k) | Since: 2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l) => Read (a, b, c, d, e, f, g, h, i, j, k, l) | Since: 2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m) | Since: 2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | Since: 2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n, Read o) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | Since: 2.1 |
class (Num a, Ord a) => Real a where #
Minimal complete definition
Methods
toRational :: a -> Rational #
the rational equivalent of its real argument with full precision
Instances
class (RealFrac a, Floating a) => RealFloat a where #
Efficient, machine-independent access to the components of a floating-point number.
Minimal complete definition
floatRadix, floatDigits, floatRange, decodeFloat, encodeFloat, isNaN, isInfinite, isDenormalized, isNegativeZero, isIEEE
Methods
floatRadix :: a -> Integer #
a constant function, returning the radix of the representation
(often 2
)
floatDigits :: a -> Int #
a constant function, returning the number of digits of
floatRadix
in the significand
floatRange :: a -> (Int, Int) #
a constant function, returning the lowest and highest values the exponent may assume
decodeFloat :: a -> (Integer, Int) #
The function decodeFloat
applied to a real floating-point
number returns the significand expressed as an Integer
and an
appropriately scaled exponent (an Int
). If
yields decodeFloat
x(m,n)
, then x
is equal in value to m*b^^n
, where b
is the floating-point radix, and furthermore, either m
and n
are both zero or else b^(d-1) <=
, where abs
m < b^dd
is
the value of
.
In particular, floatDigits
x
. If the type
contains a negative zero, also decodeFloat
0 = (0,0)
.
The result of decodeFloat
(-0.0) = (0,0)
is unspecified if either of
decodeFloat
x
or isNaN
x
is isInfinite
xTrue
.
encodeFloat :: Integer -> Int -> a #
encodeFloat
performs the inverse of decodeFloat
in the
sense that for finite x
with the exception of -0.0
,
.
uncurry
encodeFloat
(decodeFloat
x) = x
is one of the two closest representable
floating-point numbers to encodeFloat
m nm*b^^n
(or ±Infinity
if overflow
occurs); usually the closer, but if m
contains too many bits,
the result may be rounded in the wrong direction.
exponent
corresponds to the second component of decodeFloat
.
and for finite nonzero exponent
0 = 0x
,
.
If exponent
x = snd (decodeFloat
x) + floatDigits
xx
is a finite floating-point number, it is equal in value to
, where significand
x * b ^^ exponent
xb
is the
floating-point radix.
The behaviour is unspecified on infinite or NaN
values.
significand :: a -> a #
The first component of decodeFloat
, scaled to lie in the open
interval (-1
,1
), either 0.0
or of absolute value >= 1/b
,
where b
is the floating-point radix.
The behaviour is unspecified on infinite or NaN
values.
scaleFloat :: Int -> a -> a #
multiplies a floating-point number by an integer power of the radix
True
if the argument is an IEEE "not-a-number" (NaN) value
isInfinite :: a -> Bool #
True
if the argument is an IEEE infinity or negative infinity
isDenormalized :: a -> Bool #
True
if the argument is too small to be represented in
normalized format
isNegativeZero :: a -> Bool #
True
if the argument is an IEEE negative zero
True
if the argument is an IEEE floating point number
a version of arctangent taking two real floating-point arguments.
For real floating x
and y
,
computes the angle
(from the positive x-axis) of the vector from the origin to the
point atan2
y x(x,y)
.
returns a value in the range [atan2
y x-pi
,
pi
]. It follows the Common Lisp semantics for the origin when
signed zeroes are supported.
, with atan2
y 1y
in a type
that is RealFloat
, should return the same value as
.
A default definition of atan
yatan2
is provided, but implementors
can provide a more accurate implementation.
Instances
class (Real a, Fractional a) => RealFrac a where #
Extracting components of fractions.
Minimal complete definition
Methods
properFraction :: Integral b => a -> (b, a) #
The function properFraction
takes a real fractional number x
and returns a pair (n,f)
such that x = n+f
, and:
n
is an integral number with the same sign asx
; andf
is a fraction with the same type and sign asx
, and with absolute value less than1
.
The default definitions of the ceiling
, floor
, truncate
and round
functions are in terms of properFraction
.
truncate :: Integral b => a -> b #
returns the integer nearest truncate
xx
between zero and x
round :: Integral b => a -> b #
returns the nearest integer to round
xx
;
the even integer if x
is equidistant between two integers
ceiling :: Integral b => a -> b #
returns the least integer not less than ceiling
xx
floor :: Integral b => a -> b #
returns the greatest integer not greater than floor
xx
Instances
RealFrac CFloat | |
RealFrac CDouble | |
RealFrac Half | |
() :=> (RealFrac Double) | |
() :=> (RealFrac Float) | |
Integral a => RealFrac (Ratio a) | Since: 2.0.1 |
HasResolution a => RealFrac (Fixed a) | Since: 2.1 |
RealFrac a => RealFrac (Identity a) | |
(Integral a) :=> (RealFrac (Ratio a)) | |
(RealFrac a) :=> (RealFrac (Identity a)) | |
(RealFrac a) :=> (RealFrac (Const a b)) | |
Class (Real a, Fractional a) (RealFrac a) | |
Methods cls :: RealFrac a :- (Real a, Fractional a) | |
Class (RealFrac a, Floating a) (RealFloat a) | |
RealFrac a => RealFrac (Const a b) | |
RealFrac a => RealFrac (Tagged s a) | |
Conversion of values to readable String
s.
Derived instances of Show
have the following properties, which
are compatible with derived instances of Read
:
- The result of
show
is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used. - If the constructor is defined to be an infix operator, then
showsPrec
will produce infix applications of the constructor. - the representation will be enclosed in parentheses if the
precedence of the top-level constructor in
x
is less thand
(associativity is ignored). Thus, ifd
is0
then the result is never surrounded in parentheses; ifd
is11
it is always surrounded in parentheses, unless it is an atomic expression. - If the constructor is defined using record syntax, then
show
will produce the record-syntax form, with the fields given in the same order as the original declaration.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Show
is equivalent to
instance (Show a) => Show (Tree a) where showsPrec d (Leaf m) = showParen (d > app_prec) $ showString "Leaf " . showsPrec (app_prec+1) m where app_prec = 10 showsPrec d (u :^: v) = showParen (d > up_prec) $ showsPrec (up_prec+1) u . showString " :^: " . showsPrec (up_prec+1) v where up_prec = 5
Note that right-associativity of :^:
is ignored. For example,
produces the stringshow
(Leaf 1 :^: Leaf 2 :^: Leaf 3)"Leaf 1 :^: (Leaf 2 :^: Leaf 3)"
.
Methods
Arguments
:: Int | the operator precedence of the enclosing
context (a number from |
-> a | the value to be converted to a |
-> ShowS |
Convert a value to a readable String
.
showsPrec
should satisfy the law
showsPrec d x r ++ s == showsPrec d x (r ++ s)
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
class Functor f => Applicative (f :: * -> *) where #
A functor with application, providing operations to
A minimal complete definition must include implementations of pure
and of either <*>
or liftA2
. If it defines both, then they must behave
the same as their default definitions:
(<*>
) =liftA2
id
liftA2
f x y = f<$>
x<*>
y
Further, any definition must satisfy the following:
- identity
pure
id
<*>
v = v- composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- homomorphism
pure
f<*>
pure
x =pure
(f x)- interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
It may be useful to note that supposing
forall x y. p (q x y) = f x . g y
it follows from the above that
liftA2
p (liftA2
q u v) =liftA2
f u .liftA2
g v
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Methods
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*>
that is more
efficient than the default one.
(*>) :: f a -> f b -> f b infixl 4 #
Sequence actions, discarding the value of the first argument.
(<*) :: f a -> f b -> f a infixl 4 #
Sequence actions, discarding the value of the second argument.
Instances
Applicative [] | Since: 2.1 |
Applicative Maybe | Since: 2.1 |
Applicative IO | Since: 2.1 |
Applicative Par1 | Since: 4.9.0.0 |
Applicative Q | |
Applicative Complex | Since: 4.9.0.0 |
Applicative Min | Since: 4.9.0.0 |
Applicative Max | Since: 4.9.0.0 |
Applicative First | Since: 4.9.0.0 |
Applicative Last | Since: 4.9.0.0 |
Applicative Option | Since: 4.9.0.0 |
Applicative ZipList | f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsN = 'ZipList' (zipWithN f xs1 ... xsN) where (\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..] = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..]) = ZipList {getZipList = ["a5","b6b6","c7c7c7"]} Since: 2.1 |
Applicative Identity | Since: 4.8.0.0 |
Applicative STM | Since: 4.8.0.0 |
Applicative First | |
Applicative Last | |
Applicative Dual | Since: 4.8.0.0 |
Applicative Sum | Since: 4.8.0.0 |
Applicative Product | Since: 4.8.0.0 |
Applicative Down | Since: 4.11.0.0 |
Applicative ReadPrec | Since: 4.6.0.0 |
Applicative ReadP | Since: 4.6.0.0 |
Applicative NonEmpty | Since: 4.9.0.0 |
Applicative Tree | |
Applicative Seq | Since: 0.5.4 |
Applicative P | Since: 4.5.0.0 |
Applicative Gen | |
Applicative Id | |
Applicative Box | |
Applicative DList | |
Applicative Vector | |
Applicative Array | |
Applicative Rose | |
() :=> (Applicative ((->) a :: * -> *)) | |
Methods ins :: () :- Applicative ((->) a) | |
() :=> (Applicative []) | |
Methods ins :: () :- Applicative [] | |
() :=> (Applicative Maybe) | |
Methods ins :: () :- Applicative Maybe | |
() :=> (Applicative IO) | |
Methods ins :: () :- Applicative IO | |
() :=> (Applicative (Either a)) | |
Methods ins :: () :- Applicative (Either a) | |
Applicative (Either e) | Since: 3.0 |
Applicative (U1 :: * -> *) | Since: 4.9.0.0 |
Monoid a => Applicative ((,) a) | For tuples, the ("hello ", (+15)) <*> ("world!", 2002) ("hello world!",2017) Since: 2.1 |
Applicative (ST s) | Since: 4.4.0.0 |
Monad m => Applicative (WrappedMonad m) | Since: 2.1 |
Methods pure :: a -> WrappedMonad m a # (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b # liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c # (*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # (<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a # | |
Arrow a => Applicative (ArrowMonad a) | Since: 4.6.0.0 |
Methods pure :: a0 -> ArrowMonad a a0 # (<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b # liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c # (*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # (<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 # | |
Applicative (Proxy :: * -> *) | Since: 4.7.0.0 |
KnownNat n => Applicative (Vec n) # | |
Applicative (ReifiedFold s) | |
Methods pure :: a -> ReifiedFold s a # (<*>) :: ReifiedFold s (a -> b) -> ReifiedFold s a -> ReifiedFold s b # liftA2 :: (a -> b -> c) -> ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s c # (*>) :: ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s b # (<*) :: ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s a # | |
Applicative (ReifiedGetter s) | |
Methods pure :: a -> ReifiedGetter s a # (<*>) :: ReifiedGetter s (a -> b) -> ReifiedGetter s a -> ReifiedGetter s b # liftA2 :: (a -> b -> c) -> ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s c # (*>) :: ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s b # (<*) :: ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s a # | |
Representable f => Applicative (Co f) | |
Alternative f => Applicative (Cofree f) | |
Functor f => Applicative (Free f) | |
Applicative f => Applicative (Yoneda f) | |
Applicative f => Applicative (Indexing f) | |
Applicative f => Applicative (Indexing64 f) | |
(Applicative (Rep p), Representable p) => Applicative (Prep p) | |
Applicative (Signal domain) # | |
Methods pure :: a -> Signal domain a # (<*>) :: Signal domain (a -> b) -> Signal domain a -> Signal domain b # liftA2 :: (a -> b -> c) -> Signal domain a -> Signal domain b -> Signal domain c # (*>) :: Signal domain a -> Signal domain b -> Signal domain b # (<*) :: Signal domain a -> Signal domain b -> Signal domain a # | |
KnownNat d => Applicative (RTree d) # | |
(Monad m) :=> (Applicative (WrappedMonad m)) | |
Methods ins :: Monad m :- Applicative (WrappedMonad m) | |
(Monoid a) :=> (Applicative ((,) a)) | |
Methods ins :: Monoid a :- Applicative ((,) a) | |
(Monoid a) :=> (Applicative (Const a :: * -> *)) | |
Methods ins :: Monoid a :- Applicative (Const a) | |
Class (Functor f) (Applicative f) | |
Methods cls :: Applicative f :- Functor f | |
Class (Applicative f) (Monad f) | |
Methods cls :: Monad f :- Applicative f | |
Class (Applicative f) (Alternative f) | |
Methods cls :: Alternative f :- Applicative f | |
Applicative f => Applicative (Rec1 f) | Since: 4.9.0.0 |
Arrow a => Applicative (WrappedArrow a b) | Since: 2.1 |
Methods pure :: a0 -> WrappedArrow a b a0 # (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c # (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 # (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |
Monoid m => Applicative (Const m :: * -> *) | Since: 2.0.1 |
Applicative f => Applicative (Alt f) | |
(Applicative f, Monad f) => Applicative (WhenMissing f x) | Equivalent to Since: 0.5.9 |
Methods pure :: a -> WhenMissing f x a # (<*>) :: WhenMissing f x (a -> b) -> WhenMissing f x a -> WhenMissing f x b # liftA2 :: (a -> b -> c) -> WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x c # (*>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b # (<*) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x a # | |
(Functor m, Monad m) => Applicative (ErrorT e m) | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Monoid a => Applicative (Constant a :: * -> *) | |
Applicative (Indexed i a) | |
Applicative (Tagged s) | |
Biapplicative p => Applicative (Fix p) | |
Biapplicative p => Applicative (Join p) | |
(Alternative f, Applicative w) => Applicative (CofreeT f w) | |
(Functor f, Monad m) => Applicative (FreeT f m) | |
(Applicative f, Applicative g) => Applicative (Day f g) | |
Applicative (DSignal domain delay) # | |
Methods pure :: a -> DSignal domain delay a # (<*>) :: DSignal domain delay (a -> b) -> DSignal domain delay a -> DSignal domain delay b # liftA2 :: (a -> b -> c) -> DSignal domain delay a -> DSignal domain delay b -> DSignal domain delay c # (*>) :: DSignal domain delay a -> DSignal domain delay b -> DSignal domain delay b # (<*) :: DSignal domain delay a -> DSignal domain delay b -> DSignal domain delay a # | |
Applicative (Flows i b) | |
Applicative (Mafic a b) | |
Monoid m => Applicative (Holes t m) | |
Applicative ((->) a :: * -> *) | Since: 2.1 |
(Applicative f, Applicative g) => Applicative (f :*: g) | Since: 4.9.0.0 |
(Applicative f, Applicative g) => Applicative (Product f g) | Since: 4.9.0.0 |
(Monad f, Applicative f) => Applicative (WhenMatched f x y) | Equivalent to Since: 0.5.9 |
Methods pure :: a -> WhenMatched f x y a # (<*>) :: WhenMatched f x y (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b # liftA2 :: (a -> b -> c) -> WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y c # (*>) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y b # (<*) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y a # | |
(Applicative f, Monad f) => Applicative (WhenMissing f k x) | Equivalent to Since: 0.5.9 |
Methods pure :: a -> WhenMissing f k x a # (<*>) :: WhenMissing f k x (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b # liftA2 :: (a -> b -> c) -> WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x c # (*>) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x b # (<*) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x a # | |
Applicative (Bazaar p a b) | |
Methods pure :: a0 -> Bazaar p a b a0 # (<*>) :: Bazaar p a b (a0 -> b0) -> Bazaar p a b a0 -> Bazaar p a b b0 # liftA2 :: (a0 -> b0 -> c) -> Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b c # (*>) :: Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b b0 # (<*) :: Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b a0 # | |
Applicative (Molten i a b) | |
Methods pure :: a0 -> Molten i a b a0 # (<*>) :: Molten i a b (a0 -> b0) -> Molten i a b a0 -> Molten i a b b0 # liftA2 :: (a0 -> b0 -> c) -> Molten i a b a0 -> Molten i a b b0 -> Molten i a b c # (*>) :: Molten i a b a0 -> Molten i a b b0 -> Molten i a b b0 # (<*) :: Molten i a b a0 -> Molten i a b b0 -> Molten i a b a0 # | |
Applicative f => Applicative (M1 i c f) | Since: 4.9.0.0 |
(Applicative f, Applicative g) => Applicative (f :.: g) | Since: 4.9.0.0 |
(Applicative f, Applicative g) => Applicative (Compose f g) | Since: 4.9.0.0 |
(Monad f, Applicative f) => Applicative (WhenMatched f k x y) | Equivalent to Since: 0.5.9 |
Methods pure :: a -> WhenMatched f k x y a # (<*>) :: WhenMatched f k x y (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b # liftA2 :: (a -> b -> c) -> WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y c # (*>) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y b # (<*) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y a # | |
Reifies s (ReifiedApplicative f) => Applicative (ReflectedApplicative f s) | |
Methods pure :: a -> ReflectedApplicative f s a # (<*>) :: ReflectedApplicative f s (a -> b) -> ReflectedApplicative f s a -> ReflectedApplicative f s b # liftA2 :: (a -> b -> c) -> ReflectedApplicative f s a -> ReflectedApplicative f s b -> ReflectedApplicative f s c # (*>) :: ReflectedApplicative f s a -> ReflectedApplicative f s b -> ReflectedApplicative f s b # (<*) :: ReflectedApplicative f s a -> ReflectedApplicative f s b -> ReflectedApplicative f s a # | |
Applicative (BazaarT p g a b) | |
Methods pure :: a0 -> BazaarT p g a b a0 # (<*>) :: BazaarT p g a b (a0 -> b0) -> BazaarT p g a b a0 -> BazaarT p g a b b0 # liftA2 :: (a0 -> b0 -> c) -> BazaarT p g a b a0 -> BazaarT p g a b b0 -> BazaarT p g a b c # (*>) :: BazaarT p g a b a0 -> BazaarT p g a b b0 -> BazaarT p g a b b0 # (<*) :: BazaarT p g a b a0 -> BazaarT p g a b b0 -> BazaarT p g a b a0 # | |
Applicative (TakingWhile p f a b) | |
Methods pure :: a0 -> TakingWhile p f a b a0 # (<*>) :: TakingWhile p f a b (a0 -> b0) -> TakingWhile p f a b a0 -> TakingWhile p f a b b0 # liftA2 :: (a0 -> b0 -> c) -> TakingWhile p f a b a0 -> TakingWhile p f a b b0 -> TakingWhile p f a b c # (*>) :: TakingWhile p f a b a0 -> TakingWhile p f a b b0 -> TakingWhile p f a b b0 # (<*) :: TakingWhile p f a b a0 -> TakingWhile p f a b b0 -> TakingWhile p f a b a0 # |
class Foldable (t :: * -> *) where #
Data structures that can be folded.
For example, given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Foldable Tree where foldMap f Empty = mempty foldMap f (Leaf x) = f x foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
This is suitable even for abstract types, as the monoid is assumed
to satisfy the monoid laws. Alternatively, one could define foldr
:
instance Foldable Tree where foldr f z Empty = z foldr f z (Leaf x) = f x z foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
Foldable
instances are expected to satisfy the following laws:
foldr f z t = appEndo (foldMap (Endo . f) t ) z
foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
fold = foldMap id
length = getSum . foldMap (Sum . const 1)
sum
, product
, maximum
, and minimum
should all be essentially
equivalent to foldMap
forms, such as
sum = getSum . foldMap Sum
but may be less defined.
If the type is also a Functor
instance, it should satisfy
foldMap f = fold . fmap f
which implies that
foldMap f . fmap g = foldMap (f . g)
Methods
foldMap :: Monoid m => (a -> m) -> t a -> m #
Map each element of the structure to a monoid, and combine the results.
Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.
elem :: Eq a => a -> t a -> Bool infix 4 #
Does the element occur in the structure?
maximum :: Ord a => t a -> a #
The largest element of a non-empty structure.
minimum :: Ord a => t a -> a #
The least element of a non-empty structure.
The sum
function computes the sum of the numbers of a structure.
product :: Num a => t a -> a #
The product
function computes the product of the numbers of a
structure.
Instances
Foldable [] | Since: 2.1 |
Methods fold :: Monoid m => [m] -> m # foldMap :: Monoid m => (a -> m) -> [a] -> m # foldr :: (a -> b -> b) -> b -> [a] -> b # foldr' :: (a -> b -> b) -> b -> [a] -> b # foldl :: (b -> a -> b) -> b -> [a] -> b # foldl' :: (b -> a -> b) -> b -> [a] -> b # foldr1 :: (a -> a -> a) -> [a] -> a # foldl1 :: (a -> a -> a) -> [a] -> a # elem :: Eq a => a -> [a] -> Bool # maximum :: Ord a => [a] -> a # | |
Foldable Maybe | Since: 2.1 |
Methods fold :: Monoid m => Maybe m -> m # foldMap :: Monoid m => (a -> m) -> Maybe a -> m # foldr :: (a -> b -> b) -> b -> Maybe a -> b # foldr' :: (a -> b -> b) -> b -> Maybe a -> b # foldl :: (b -> a -> b) -> b -> Maybe a -> b # foldl' :: (b -> a -> b) -> b -> Maybe a -> b # foldr1 :: (a -> a -> a) -> Maybe a -> a # foldl1 :: (a -> a -> a) -> Maybe a -> a # elem :: Eq a => a -> Maybe a -> Bool # maximum :: Ord a => Maybe a -> a # minimum :: Ord a => Maybe a -> a # | |
Foldable Par1 | |
Methods fold :: Monoid m => Par1 m -> m # foldMap :: Monoid m => (a -> m) -> Par1 a -> m # foldr :: (a -> b -> b) -> b -> Par1 a -> b # foldr' :: (a -> b -> b) -> b -> Par1 a -> b # foldl :: (b -> a -> b) -> b -> Par1 a -> b # foldl' :: (b -> a -> b) -> b -> Par1 a -> b # foldr1 :: (a -> a -> a) -> Par1 a -> a # foldl1 :: (a -> a -> a) -> Par1 a -> a # elem :: Eq a => a -> Par1 a -> Bool # maximum :: Ord a => Par1 a -> a # | |
Foldable Complex | |
Methods fold :: Monoid m => Complex m -> m # foldMap :: Monoid m => (a -> m) -> Complex a -> m # foldr :: (a -> b -> b) -> b -> Complex a -> b # foldr' :: (a -> b -> b) -> b -> Complex a -> b # foldl :: (b -> a -> b) -> b -> Complex a -> b # foldl' :: (b -> a -> b) -> b -> Complex a -> b # foldr1 :: (a -> a -> a) -> Complex a -> a # foldl1 :: (a -> a -> a) -> Complex a -> a # elem :: Eq a => a -> Complex a -> Bool # maximum :: Ord a => Complex a -> a # minimum :: Ord a => Complex a -> a # | |
Foldable Min | Since: 4.9.0.0 |
Methods fold :: Monoid m => Min m -> m # foldMap :: Monoid m => (a -> m) -> Min a -> m # foldr :: (a -> b -> b) -> b -> Min a -> b # foldr' :: (a -> b -> b) -> b -> Min a -> b # foldl :: (b -> a -> b) -> b -> Min a -> b # foldl' :: (b -> a -> b) -> b -> Min a -> b # foldr1 :: (a -> a -> a) -> Min a -> a # foldl1 :: (a -> a -> a) -> Min a -> a # elem :: Eq a => a -> Min a -> Bool # maximum :: Ord a => Min a -> a # | |
Foldable Max | Since: 4.9.0.0 |
Methods fold :: Monoid m => Max m -> m # foldMap :: Monoid m => (a -> m) -> Max a -> m # foldr :: (a -> b -> b) -> b -> Max a -> b # foldr' :: (a -> b -> b) -> b -> Max a -> b # foldl :: (b -> a -> b) -> b -> Max a -> b # foldl' :: (b -> a -> b) -> b -> Max a -> b # foldr1 :: (a -> a -> a) -> Max a -> a # foldl1 :: (a -> a -> a) -> Max a -> a # elem :: Eq a => a -> Max a -> Bool # maximum :: Ord a => Max a -> a # | |
Foldable First | Since: 4.9.0.0 |
Methods fold :: Monoid m => First m -> m # foldMap :: Monoid m => (a -> m) -> First a -> m # foldr :: (a -> b -> b) -> b -> First a -> b # foldr' :: (a -> b -> b) -> b -> First a -> b # foldl :: (b -> a -> b) -> b -> First a -> b # foldl' :: (b -> a -> b) -> b -> First a -> b # foldr1 :: (a -> a -> a) -> First a -> a # foldl1 :: (a -> a -> a) -> First a -> a # elem :: Eq a => a -> First a -> Bool # maximum :: Ord a => First a -> a # minimum :: Ord a => First a -> a # | |
Foldable Last | Since: 4.9.0.0 |
Methods fold :: Monoid m => Last m -> m # foldMap :: Monoid m => (a -> m) -> Last a -> m # foldr :: (a -> b -> b) -> b -> Last a -> b # foldr' :: (a -> b -> b) -> b -> Last a -> b # foldl :: (b -> a -> b) -> b -> Last a -> b # foldl' :: (b -> a -> b) -> b -> Last a -> b # foldr1 :: (a -> a -> a) -> Last a -> a # foldl1 :: (a -> a -> a) -> Last a -> a # elem :: Eq a => a -> Last a -> Bool # maximum :: Ord a => Last a -> a # | |
Foldable Option | Since: 4.9.0.0 |
Methods fold :: Monoid m => Option m -> m # foldMap :: Monoid m => (a -> m) -> Option a -> m # foldr :: (a -> b -> b) -> b -> Option a -> b # foldr' :: (a -> b -> b) -> b -> Option a -> b # foldl :: (b -> a -> b) -> b -> Option a -> b # foldl' :: (b -> a -> b) -> b -> Option a -> b # foldr1 :: (a -> a -> a) -> Option a -> a # foldl1 :: (a -> a -> a) -> Option a -> a # elem :: Eq a => a -> Option a -> Bool # maximum :: Ord a => Option a -> a # minimum :: Ord a => Option a -> a # | |
Foldable ZipList | |
Methods fold :: Monoid m => ZipList m -> m # foldMap :: Monoid m => (a -> m) -> ZipList a -> m # foldr :: (a -> b -> b) -> b -> ZipList a -> b # foldr' :: (a -> b -> b) -> b -> ZipList a -> b # foldl :: (b -> a -> b) -> b -> ZipList a -> b # foldl' :: (b -> a -> b) -> b -> ZipList a -> b # foldr1 :: (a -> a -> a) -> ZipList a -> a # foldl1 :: (a -> a -> a) -> ZipList a -> a # elem :: Eq a => a -> ZipList a -> Bool # maximum :: Ord a => ZipList a -> a # minimum :: Ord a => ZipList a -> a # | |
Foldable Identity | Since: 4.8.0.0 |
Methods fold :: Monoid m => Identity m -> m # foldMap :: Monoid m => (a -> m) -> Identity a -> m # foldr :: (a -> b -> b) -> b -> Identity a -> b # foldr' :: (a -> b -> b) -> b -> Identity a -> b # foldl :: (b -> a -> b) -> b -> Identity a -> b # foldl' :: (b -> a -> b) -> b -> Identity a -> b # foldr1 :: (a -> a -> a) -> Identity a -> a # foldl1 :: (a -> a -> a) -> Identity a -> a # elem :: Eq a => a -> Identity a -> Bool # maximum :: Ord a => Identity a -> a # minimum :: Ord a => Identity a -> a # | |
Foldable First | Since: 4.8.0.0 |
Methods fold :: Monoid m => First m -> m # foldMap :: Monoid m => (a -> m) -> First a -> m # foldr :: (a -> b -> b) -> b -> First a -> b # foldr' :: (a -> b -> b) -> b -> First a -> b # foldl :: (b -> a -> b) -> b -> First a -> b # foldl' :: (b -> a -> b) -> b -> First a -> b # foldr1 :: (a -> a -> a) -> First a -> a # foldl1 :: (a -> a -> a) -> First a -> a # elem :: Eq a => a -> First a -> Bool # maximum :: Ord a => First a -> a # minimum :: Ord a => First a -> a # | |
Foldable Last | Since: 4.8.0.0 |
Methods fold :: Monoid m => Last m -> m # foldMap :: Monoid m => (a -> m) -> Last a -> m # foldr :: (a -> b -> b) -> b -> Last a -> b # foldr' :: (a -> b -> b) -> b -> Last a -> b # foldl :: (b -> a -> b) -> b -> Last a -> b # foldl' :: (b -> a -> b) -> b -> Last a -> b # foldr1 :: (a -> a -> a) -> Last a -> a # foldl1 :: (a -> a -> a) -> Last a -> a # elem :: Eq a => a -> Last a -> Bool # maximum :: Ord a => Last a -> a # | |
Foldable Dual | Since: 4.8.0.0 |
Methods fold :: Monoid m => Dual m -> m # foldMap :: Monoid m => (a -> m) -> Dual a -> m # foldr :: (a -> b -> b) -> b -> Dual a -> b # foldr' :: (a -> b -> b) -> b -> Dual a -> b # foldl :: (b -> a -> b) -> b -> Dual a -> b # foldl' :: (b -> a -> b) -> b -> Dual a -> b # foldr1 :: (a -> a -> a) -> Dual a -> a # foldl1 :: (a -> a -> a) -> Dual a -> a # elem :: Eq a => a -> Dual a -> Bool # maximum :: Ord a => Dual a -> a # | |
Foldable Sum | Since: 4.8.0.0 |
Methods fold :: Monoid m => Sum m -> m # foldMap :: Monoid m => (a -> m) -> Sum a -> m # foldr :: (a -> b -> b) -> b -> Sum a -> b # foldr' :: (a -> b -> b) -> b -> Sum a -> b # foldl :: (b -> a -> b) -> b -> Sum a -> b # foldl' :: (b -> a -> b) -> b -> Sum a -> b # foldr1 :: (a -> a -> a) -> Sum a -> a # foldl1 :: (a -> a -> a) -> Sum a -> a # elem :: Eq a => a -> Sum a -> Bool # maximum :: Ord a => Sum a -> a # | |
Foldable Product | Since: 4.8.0.0 |
Methods fold :: Monoid m => Product m -> m # foldMap :: Monoid m => (a -> m) -> Product a -> m # foldr :: (a -> b -> b) -> b -> Product a -> b # foldr' :: (a -> b -> b) -> b -> Product a -> b # foldl :: (b -> a -> b) -> b -> Product a -> b # foldl' :: (b -> a -> b) -> b -> Product a -> b # foldr1 :: (a -> a -> a) -> Product a -> a # foldl1 :: (a -> a -> a) -> Product a -> a # elem :: Eq a => a -> Product a -> Bool # maximum :: Ord a => Product a -> a # minimum :: Ord a => Product a -> a # | |
Foldable NonEmpty | Since: 4.9.0.0 |
Methods fold :: Monoid m => NonEmpty m -> m # foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m # foldr :: (a -> b -> b) -> b -> NonEmpty a -> b # foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b # foldl :: (b -> a -> b) -> b -> NonEmpty a -> b # foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b # foldr1 :: (a -> a -> a) -> NonEmpty a -> a # foldl1 :: (a -> a -> a) -> NonEmpty a -> a # elem :: Eq a => a -> NonEmpty a -> Bool # maximum :: Ord a => NonEmpty a -> a # minimum :: Ord a => NonEmpty a -> a # | |
Foldable IntMap | |
Methods fold :: Monoid m => IntMap m -> m # foldMap :: Monoid m => (a -> m) -> IntMap a -> m # foldr :: (a -> b -> b) -> b -> IntMap a -> b # foldr' :: (a -> b -> b) -> b -> IntMap a -> b # foldl :: (b -> a -> b) -> b -> IntMap a -> b # foldl' :: (b -> a -> b) -> b -> IntMap a -> b # foldr1 :: (a -> a -> a) -> IntMap a -> a # foldl1 :: (a -> a -> a) -> IntMap a -> a # elem :: Eq a => a -> IntMap a -> Bool # maximum :: Ord a => IntMap a -> a # minimum :: Ord a => IntMap a -> a # | |
Foldable Tree | |
Methods fold :: Monoid m => Tree m -> m # foldMap :: Monoid m => (a -> m) -> Tree a -> m # foldr :: (a -> b -> b) -> b -> Tree a -> b # foldr' :: (a -> b -> b) -> b -> Tree a -> b # foldl :: (b -> a -> b) -> b -> Tree a -> b # foldl' :: (b -> a -> b) -> b -> Tree a -> b # foldr1 :: (a -> a -> a) -> Tree a -> a # foldl1 :: (a -> a -> a) -> Tree a -> a # elem :: Eq a => a -> Tree a -> Bool # maximum :: Ord a => Tree a -> a # | |
Foldable Seq | |
Methods fold :: Monoid m => Seq m -> m # foldMap :: Monoid m => (a -> m) -> Seq a -> m # foldr :: (a -> b -> b) -> b -> Seq a -> b # foldr' :: (a -> b -> b) -> b -> Seq a -> b # foldl :: (b -> a -> b) -> b -> Seq a -> b # foldl' :: (b -> a -> b) -> b -> Seq a -> b # foldr1 :: (a -> a -> a) -> Seq a -> a # foldl1 :: (a -> a -> a) -> Seq a -> a # elem :: Eq a => a -> Seq a -> Bool # maximum :: Ord a => Seq a -> a # | |
Foldable FingerTree | |
Methods fold :: Monoid m => FingerTree m -> m # foldMap :: Monoid m => (a -> m) -> FingerTree a -> m # foldr :: (a -> b -> b) -> b -> FingerTree a -> b # foldr' :: (a -> b -> b) -> b -> FingerTree a -> b # foldl :: (b -> a -> b) -> b -> FingerTree a -> b # foldl' :: (b -> a -> b) -> b -> FingerTree a -> b # foldr1 :: (a -> a -> a) -> FingerTree a -> a # foldl1 :: (a -> a -> a) -> FingerTree a -> a # toList :: FingerTree a -> [a] # null :: FingerTree a -> Bool # length :: FingerTree a -> Int # elem :: Eq a => a -> FingerTree a -> Bool # maximum :: Ord a => FingerTree a -> a # minimum :: Ord a => FingerTree a -> a # sum :: Num a => FingerTree a -> a # product :: Num a => FingerTree a -> a # | |
Foldable Digit | |
Methods fold :: Monoid m => Digit m -> m # foldMap :: Monoid m => (a -> m) -> Digit a -> m # foldr :: (a -> b -> b) -> b -> Digit a -> b # foldr' :: (a -> b -> b) -> b -> Digit a -> b # foldl :: (b -> a -> b) -> b -> Digit a -> b # foldl' :: (b -> a -> b) -> b -> Digit a -> b # foldr1 :: (a -> a -> a) -> Digit a -> a # foldl1 :: (a -> a -> a) -> Digit a -> a # elem :: Eq a => a -> Digit a -> Bool # maximum :: Ord a => Digit a -> a # minimum :: Ord a => Digit a -> a # | |
Foldable Node | |
Methods fold :: Monoid m => Node m -> m # foldMap :: Monoid m => (a -> m) -> Node a -> m # foldr :: (a -> b -> b) -> b -> Node a -> b # foldr' :: (a -> b -> b) -> b -> Node a -> b # foldl :: (b -> a -> b) -> b -> Node a -> b # foldl' :: (b -> a -> b) -> b -> Node a -> b # foldr1 :: (a -> a -> a) -> Node a -> a # foldl1 :: (a -> a -> a) -> Node a -> a # elem :: Eq a => a -> Node a -> Bool # maximum :: Ord a => Node a -> a # | |
Foldable Elem | |
Methods fold :: Monoid m => Elem m -> m # foldMap :: Monoid m => (a -> m) -> Elem a -> m # foldr :: (a -> b -> b) -> b -> Elem a -> b # foldr' :: (a -> b -> b) -> b -> Elem a -> b # foldl :: (b -> a -> b) -> b -> Elem a -> b # foldl' :: (b -> a -> b) -> b -> Elem a -> b # foldr1 :: (a -> a -> a) -> Elem a -> a # foldl1 :: (a -> a -> a) -> Elem a -> a # elem :: Eq a => a -> Elem a -> Bool # maximum :: Ord a => Elem a -> a # | |
Foldable ViewL | |
Methods fold :: Monoid m => ViewL m -> m # foldMap :: Monoid m => (a -> m) -> ViewL a -> m # foldr :: (a -> b -> b) -> b -> ViewL a -> b # foldr' :: (a -> b -> b) -> b -> ViewL a -> b # foldl :: (b -> a -> b) -> b -> ViewL a -> b # foldl' :: (b -> a -> b) -> b -> ViewL a -> b # foldr1 :: (a -> a -> a) -> ViewL a -> a # foldl1 :: (a -> a -> a) -> ViewL a -> a # elem :: Eq a => a -> ViewL a -> Bool # maximum :: Ord a => ViewL a -> a # minimum :: Ord a => ViewL a -> a # | |
Foldable ViewR | |
Methods fold :: Monoid m => ViewR m -> m # foldMap :: Monoid m => (a -> m) -> ViewR a -> m # foldr :: (a -> b -> b) -> b -> ViewR a -> b # foldr' :: (a -> b -> b) -> b -> ViewR a -> b # foldl :: (b -> a -> b) -> b -> ViewR a -> b # foldl' :: (b -> a -> b) -> b -> ViewR a -> b # foldr1 :: (a -> a -> a) -> ViewR a -> a # foldl1 :: (a -> a -> a) -> ViewR a -> a # elem :: Eq a => a -> ViewR a -> Bool # maximum :: Ord a => ViewR a -> a # minimum :: Ord a => ViewR a -> a # | |
Foldable Set | |
Methods fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
Foldable DList | |
Methods fold :: Monoid m => DList m -> m # foldMap :: Monoid m => (a -> m) -> DList a -> m # foldr :: (a -> b -> b) -> b -> DList a -> b # foldr' :: (a -> b -> b) -> b -> DList a -> b # foldl :: (b -> a -> b) -> b -> DList a -> b # foldl' :: (b -> a -> b) -> b -> DList a -> b # foldr1 :: (a -> a -> a) -> DList a -> a # foldl1 :: (a -> a -> a) -> DList a -> a # elem :: Eq a => a -> DList a -> Bool # maximum :: Ord a => DList a -> a # minimum :: Ord a => DList a -> a # | |
Foldable HashSet | |
Methods fold :: Monoid m => HashSet m -> m # foldMap :: Monoid m => (a -> m) -> HashSet a -> m # foldr :: (a -> b -> b) -> b -> HashSet a -> b # foldr' :: (a -> b -> b) -> b -> HashSet a -> b # foldl :: (b -> a -> b) -> b -> HashSet a -> b # foldl' :: (b -> a -> b) -> b -> HashSet a -> b # foldr1 :: (a -> a -> a) -> HashSet a -> a # foldl1 :: (a -> a -> a) -> HashSet a -> a # elem :: Eq a => a -> HashSet a -> Bool # maximum :: Ord a => HashSet a -> a # minimum :: Ord a => HashSet a -> a # | |
Foldable Vector | |
Methods fold :: Monoid m => Vector m -> m # foldMap :: Monoid m => (a -> m) -> Vector a -> m # foldr :: (a -> b -> b) -> b -> Vector a -> b # foldr' :: (a -> b -> b) -> b -> Vector a -> b # foldl :: (b -> a -> b) -> b -> Vector a -> b # foldl' :: (b -> a -> b) -> b -> Vector a -> b # foldr1 :: (a -> a -> a) -> Vector a -> a # foldl1 :: (a -> a -> a) -> Vector a -> a # elem :: Eq a => a -> Vector a -> Bool # maximum :: Ord a => Vector a -> a # minimum :: Ord a => Vector a -> a # | |
Foldable Array | |
Methods fold :: Monoid m => Array m -> m # foldMap :: Monoid m => (a -> m) -> Array a -> m # foldr :: (a -> b -> b) -> b -> Array a -> b # foldr' :: (a -> b -> b) -> b -> Array a -> b # foldl :: (b -> a -> b) -> b -> Array a -> b # foldl' :: (b -> a -> b) -> b -> Array a -> b # foldr1 :: (a -> a -> a) -> Array a -> a # foldl1 :: (a -> a -> a) -> Array a -> a # elem :: Eq a => a -> Array a -> Bool # maximum :: Ord a => Array a -> a # minimum :: Ord a => Array a -> a # | |
Foldable (Either a) | Since: 4.7.0.0 |
Methods fold :: Monoid m => Either a m -> 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 # | |
Foldable (V1 :: * -> *) | |
Methods fold :: Monoid m => V1 m -> m # foldMap :: Monoid m => (a -> m) -> V1 a -> m # foldr :: (a -> b -> b) -> b -> V1 a -> b # foldr' :: (a -> b -> b) -> b -> V1 a -> b # foldl :: (b -> a -> b) -> b -> V1 a -> b # foldl' :: (b -> a -> b) -> b -> V1 a -> b # foldr1 :: (a -> a -> a) -> V1 a -> a # foldl1 :: (a -> a -> a) -> V1 a -> a # elem :: Eq a => a -> V1 a -> Bool # maximum :: Ord a => V1 a -> a # | |
Foldable (U1 :: * -> *) | Since: 4.9.0.0 |
Methods fold :: Monoid m => U1 m -> m # foldMap :: Monoid m => (a -> m) -> U1 a -> m # foldr :: (a -> b -> b) -> b -> U1 a -> b # foldr' :: (a -> b -> b) -> b -> U1 a -> b # foldl :: (b -> a -> b) -> b -> U1 a -> b # foldl' :: (b -> a -> b) -> b -> U1 a -> b # foldr1 :: (a -> a -> a) -> U1 a -> a # foldl1 :: (a -> a -> a) -> U1 a -> a # elem :: Eq a => a -> U1 a -> Bool # maximum :: Ord a => U1 a -> a # | |
Foldable ((,) a) | Since: 4.7.0.0 |
Methods fold :: Monoid m => (a, m) -> m # foldMap :: Monoid m => (a0 -> m) -> (a, a0) -> m # foldr :: (a0 -> b -> b) -> b -> (a, a0) -> b # foldr' :: (a0 -> b -> b) -> b -> (a, a0) -> b # foldl :: (b -> a0 -> b) -> b -> (a, a0) -> b # foldl' :: (b -> a0 -> b) -> b -> (a, a0) -> b # foldr1 :: (a0 -> a0 -> a0) -> (a, a0) -> a0 # foldl1 :: (a0 -> a0 -> a0) -> (a, a0) -> a0 # elem :: Eq a0 => a0 -> (a, a0) -> Bool # maximum :: Ord a0 => (a, a0) -> a0 # minimum :: Ord a0 => (a, a0) -> a0 # | |
Foldable (Array i) | Since: 4.8.0.0 |
Methods fold :: Monoid m => Array i m -> m # foldMap :: Monoid m => (a -> m) -> Array i a -> m # foldr :: (a -> b -> b) -> b -> Array i a -> b # foldr' :: (a -> b -> b) -> b -> Array i a -> b # foldl :: (b -> a -> b) -> b -> Array i a -> b # foldl' :: (b -> a -> b) -> b -> Array i a -> b # foldr1 :: (a -> a -> a) -> Array i a -> a # foldl1 :: (a -> a -> a) -> Array i a -> a # elem :: Eq a => a -> Array i a -> Bool # maximum :: Ord a => Array i a -> a # minimum :: Ord a => Array i a -> a # | |
Foldable (Arg a) | Since: 4.9.0.0 |
Methods fold :: Monoid m => Arg a m -> m # foldMap :: Monoid m => (a0 -> m) -> Arg a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Arg a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Arg a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Arg a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Arg a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 # elem :: Eq a0 => a0 -> Arg a a0 -> Bool # maximum :: Ord a0 => Arg a a0 -> a0 # minimum :: Ord a0 => Arg a a0 -> a0 # | |
Foldable (Proxy :: * -> *) | Since: 4.7.0.0 |
Methods fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Foldable (Map k) | |
Methods fold :: Monoid m => Map k m -> m # foldMap :: Monoid m => (a -> m) -> Map k a -> m # foldr :: (a -> b -> b) -> b -> Map k a -> b # foldr' :: (a -> b -> b) -> b -> Map k a -> b # foldl :: (b -> a -> b) -> b -> Map k a -> b # foldl' :: (b -> a -> b) -> b -> Map k a -> b # foldr1 :: (a -> a -> a) -> Map k a -> a # foldl1 :: (a -> a -> a) -> Map k a -> a # elem :: Eq a => a -> Map k a -> Bool # maximum :: Ord a => Map k a -> a # minimum :: Ord a => Map k a -> a # | |
(KnownNat n, 1 <= n) => Foldable (Vec n) # | |
Methods fold :: Monoid m => Vec n m -> m # foldMap :: Monoid m => (a -> m) -> Vec n a -> m # foldr :: (a -> b -> b) -> b -> Vec n a -> b # foldr' :: (a -> b -> b) -> b -> Vec n a -> b # foldl :: (b -> a -> b) -> b -> Vec n a -> b # foldl' :: (b -> a -> b) -> b -> Vec n a -> b # foldr1 :: (a -> a -> a) -> Vec n a -> a # foldl1 :: (a -> a -> a) -> Vec n a -> a # elem :: Eq a => a -> Vec n a -> Bool # maximum :: Ord a => Vec n a -> a # minimum :: Ord a => Vec n a -> a # | |
Foldable (Level i) | |
Methods fold :: Monoid m => Level i m -> m # foldMap :: Monoid m => (a -> m) -> Level i a -> m # foldr :: (a -> b -> b) -> b -> Level i a -> b # foldr' :: (a -> b -> b) -> b -> Level i a -> b # foldl :: (b -> a -> b) -> b -> Level i a -> b # foldl' :: (b -> a -> b) -> b -> Level i a -> b # foldr1 :: (a -> a -> a) -> Level i a -> a # foldl1 :: (a -> a -> a) -> Level i a -> a # elem :: Eq a => a -> Level i a -> Bool # maximum :: Ord a => Level i a -> a # minimum :: Ord a => Level i a -> a # | |
Foldable f => Foldable (Cofree f) | |
Methods fold :: Monoid m => Cofree f m -> m # foldMap :: Monoid m => (a -> m) -> Cofree f a -> m # foldr :: (a -> b -> b) -> b -> Cofree f a -> b # foldr' :: (a -> b -> b) -> b -> Cofree f a -> b # foldl :: (b -> a -> b) -> b -> Cofree f a -> b # foldl' :: (b -> a -> b) -> b -> Cofree f a -> b # foldr1 :: (a -> a -> a) -> Cofree f a -> a # foldl1 :: (a -> a -> a) -> Cofree f a -> a # elem :: Eq a => a -> Cofree f a -> Bool # maximum :: Ord a => Cofree f a -> a # minimum :: Ord a => Cofree f a -> a # | |
Foldable f => Foldable (Free f) | |
Methods fold :: Monoid m => Free f m -> m # foldMap :: Monoid m => (a -> m) -> Free f a -> m # foldr :: (a -> b -> b) -> b -> Free f a -> b # foldr' :: (a -> b -> b) -> b -> Free f a -> b # foldl :: (b -> a -> b) -> b -> Free f a -> b # foldl' :: (b -> a -> b) -> b -> Free f a -> b # foldr1 :: (a -> a -> a) -> Free f a -> a # foldl1 :: (a -> a -> a) -> Free f a -> a # elem :: Eq a => a -> Free f a -> Bool # maximum :: Ord a => Free f a -> a # minimum :: Ord a => Free f a -> a # | |
Foldable f => Foldable (Yoneda f) | |
Methods fold :: Monoid m => Yoneda f m -> m # foldMap :: Monoid m => (a -> m) -> Yoneda f a -> m # foldr :: (a -> b -> b) -> b -> Yoneda f a -> b # foldr' :: (a -> b -> b) -> b -> Yoneda f a -> b # foldl :: (b -> a -> b) -> b -> Yoneda f a -> b # foldl' :: (b -> a -> b) -> b -> Yoneda f a -> b # foldr1 :: (a -> a -> a) -> Yoneda f a -> a # foldl1 :: (a -> a -> a) -> Yoneda f a -> a # elem :: Eq a => a -> Yoneda f a -> Bool # maximum :: Ord a => Yoneda f a -> a # minimum :: Ord a => Yoneda f a -> a # | |
Foldable (HashMap k) | |
Methods fold :: Monoid m => HashMap k m -> m # foldMap :: Monoid m => (a -> m) -> HashMap k a -> m # foldr :: (a -> b -> b) -> b -> HashMap k a -> b # foldr' :: (a -> b -> b) -> b -> HashMap k a -> b # foldl :: (b -> a -> b) -> b -> HashMap k a -> b # foldl' :: (b -> a -> b) -> b -> HashMap k a -> b # foldr1 :: (a -> a -> a) -> HashMap k a -> a # foldl1 :: (a -> a -> a) -> HashMap k a -> a # toList :: HashMap k a -> [a] # length :: HashMap k a -> Int # elem :: Eq a => a -> HashMap k a -> Bool # maximum :: Ord a => HashMap k a -> a # minimum :: Ord a => HashMap k a -> a # | |
Foldable (Signal domain) # | NB: Not synthesisable NB: In "
|
Methods fold :: Monoid m => Signal domain m -> m # foldMap :: Monoid m => (a -> m) -> Signal domain a -> m # foldr :: (a -> b -> b) -> b -> Signal domain a -> b # foldr' :: (a -> b -> b) -> b -> Signal domain a -> b # foldl :: (b -> a -> b) -> b -> Signal domain a -> b # foldl' :: (b -> a -> b) -> b -> Signal domain a -> b # foldr1 :: (a -> a -> a) -> Signal domain a -> a # foldl1 :: (a -> a -> a) -> Signal domain a -> a # toList :: Signal domain a -> [a] # null :: Signal domain a -> Bool # length :: Signal domain a -> Int # elem :: Eq a => a -> Signal domain a -> Bool # maximum :: Ord a => Signal domain a -> a # minimum :: Ord a => Signal domain a -> a # | |
KnownNat d => Foldable (RTree d) # | |
Methods fold :: Monoid m => RTree d m -> m # foldMap :: Monoid m => (a -> m) -> RTree d a -> m # foldr :: (a -> b -> b) -> b -> RTree d a -> b # foldr' :: (a -> b -> b) -> b -> RTree d a -> b # foldl :: (b -> a -> b) -> b -> RTree d a -> b # foldl' :: (b -> a -> b) -> b -> RTree d a -> b # foldr1 :: (a -> a -> a) -> RTree d a -> a # foldl1 :: (a -> a -> a) -> RTree d a -> a # elem :: Eq a => a -> RTree d a -> Bool # maximum :: Ord a => RTree d a -> a # minimum :: Ord a => RTree d a -> a # | |
Foldable f => Foldable (Rec1 f) | |
Methods fold :: Monoid m => Rec1 f m -> m # foldMap :: Monoid m => (a -> m) -> Rec1 f a -> m # foldr :: (a -> b -> b) -> b -> Rec1 f a -> b # foldr' :: (a -> b -> b) -> b -> Rec1 f a -> b # foldl :: (b -> a -> b) -> b -> Rec1 f a -> b # foldl' :: (b -> a -> b) -> b -> Rec1 f a -> b # foldr1 :: (a -> a -> a) -> Rec1 f a -> a # foldl1 :: (a -> a -> a) -> Rec1 f a -> a # elem :: Eq a => a -> Rec1 f a -> Bool # maximum :: Ord a => Rec1 f a -> a # minimum :: Ord a => Rec1 f a -> a # | |
Foldable (URec Char :: * -> *) | |
Methods fold :: Monoid m => URec Char m -> m # foldMap :: Monoid m => (a -> m) -> URec Char a -> m # foldr :: (a -> b -> b) -> b -> URec Char a -> b # foldr' :: (a -> b -> b) -> b -> URec Char a -> b # foldl :: (b -> a -> b) -> b -> URec Char a -> b # foldl' :: (b -> a -> b) -> b -> URec Char a -> b # foldr1 :: (a -> a -> a) -> URec Char a -> a # foldl1 :: (a -> a -> a) -> URec Char a -> a # toList :: URec Char a -> [a] # length :: URec Char a -> Int # elem :: Eq a => a -> URec Char a -> Bool # maximum :: Ord a => URec Char a -> a # minimum :: Ord a => URec Char a -> a # | |
Foldable (URec Double :: * -> *) | |
Methods fold :: Monoid m => URec Double m -> m # foldMap :: Monoid m => (a -> m) -> URec Double a -> m # foldr :: (a -> b -> b) -> b -> URec Double a -> b # foldr' :: (a -> b -> b) -> b -> URec Double a -> b # foldl :: (b -> a -> b) -> b -> URec Double a -> b # foldl' :: (b -> a -> b) -> b -> URec Double a -> b # foldr1 :: (a -> a -> a) -> URec Double a -> a # foldl1 :: (a -> a -> a) -> URec Double a -> a # toList :: URec Double a -> [a] # null :: URec Double a -> Bool # length :: URec Double a -> Int # elem :: Eq a => a -> URec Double a -> Bool # maximum :: Ord a => URec Double a -> a # minimum :: Ord a => URec Double a -> a # | |
Foldable (URec Float :: * -> *) | |
Methods fold :: Monoid m => URec Float m -> m # foldMap :: Monoid m => (a -> m) -> URec Float a -> m # foldr :: (a -> b -> b) -> b -> URec Float a -> b # foldr' :: (a -> b -> b) -> b -> URec Float a -> b # foldl :: (b -> a -> b) -> b -> URec Float a -> b # foldl' :: (b -> a -> b) -> b -> URec Float a -> b # foldr1 :: (a -> a -> a) -> URec Float a -> a # foldl1 :: (a -> a -> a) -> URec Float a -> a # toList :: URec Float a -> [a] # null :: URec Float a -> Bool # length :: URec Float a -> Int # elem :: Eq a => a -> URec Float a -> Bool # maximum :: Ord a => URec Float a -> a # minimum :: Ord a => URec Float a -> a # | |
Foldable (URec Int :: * -> *) | |
Methods fold :: Monoid m => URec Int m -> m # foldMap :: Monoid m => (a -> m) -> URec Int a -> m # foldr :: (a -> b -> b) -> b -> URec Int a -> b # foldr' :: (a -> b -> b) -> b -> URec Int a -> b # foldl :: (b -> a -> b) -> b -> URec Int a -> b # foldl' :: (b -> a -> b) -> b -> URec Int a -> b # foldr1 :: (a -> a -> a) -> URec Int a -> a # foldl1 :: (a -> a -> a) -> URec Int a -> a # elem :: Eq a => a -> URec Int a -> Bool # maximum :: Ord a => URec Int a -> a # minimum :: Ord a => URec Int a -> a # | |
Foldable (URec Word :: * -> *) | |
Methods fold :: Monoid m => URec Word m -> m # foldMap :: Monoid m => (a -> m) -> URec Word a -> m # foldr :: (a -> b -> b) -> b -> URec Word a -> b # foldr' :: (a -> b -> b) -> b -> URec Word a -> b # foldl :: (b -> a -> b) -> b -> URec Word a -> b # foldl' :: (b -> a -> b) -> b -> URec Word a -> b # foldr1 :: (a -> a -> a) -> URec Word a -> a # foldl1 :: (a -> a -> a) -> URec Word a -> a # toList :: URec Word a -> [a] # length :: URec Word a -> Int # elem :: Eq a => a -> URec Word a -> Bool # maximum :: Ord a => URec Word a -> a # minimum :: Ord a => URec Word a -> a # | |
Foldable (URec (Ptr ()) :: * -> *) | |
Methods fold :: Monoid m => URec (Ptr ()) m -> m # foldMap :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m # foldr :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b # foldr' :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b # foldl :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b # foldl' :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b # foldr1 :: (a -> a -> a) -> URec (Ptr ()) a -> a # foldl1 :: (a -> a -> a) -> URec (Ptr ()) a -> a # toList :: URec (Ptr ()) a -> [a] # null :: URec (Ptr ()) a -> Bool # length :: URec (Ptr ()) a -> Int # elem :: Eq a => a -> URec (Ptr ()) a -> Bool # maximum :: Ord a => URec (Ptr ()) a -> a # minimum :: Ord a => URec (Ptr ()) a -> a # | |
Foldable (Const m :: * -> *) | Since: 4.7.0.0 |
Methods fold :: Monoid m0 => Const m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldr :: (a -> b -> b) -> b -> Const m a -> b # foldr' :: (a -> b -> b) -> b -> Const m a -> b # foldl :: (b -> a -> b) -> b -> Const m a -> b # foldl' :: (b -> a -> b) -> b -> Const m a -> b # foldr1 :: (a -> a -> a) -> Const m a -> a # foldl1 :: (a -> a -> a) -> Const m a -> a # elem :: Eq a => a -> Const m a -> Bool # maximum :: Ord a => Const m a -> a # minimum :: Ord a => Const m a -> a # | |
Foldable f => Foldable (ErrorT e f) | |
Methods fold :: Monoid m => ErrorT e f m -> m # foldMap :: Monoid m => (a -> m) -> ErrorT e f a -> m # foldr :: (a -> b -> b) -> b -> ErrorT e f a -> b # foldr' :: (a -> b -> b) -> b -> ErrorT e f a -> b # foldl :: (b -> a -> b) -> b -> ErrorT e f a -> b # foldl' :: (b -> a -> b) -> b -> ErrorT e f a -> b # foldr1 :: (a -> a -> a) -> ErrorT e f a -> a # foldl1 :: (a -> a -> a) -> ErrorT e f a -> a # toList :: ErrorT e f a -> [a] # null :: ErrorT e f a -> Bool # length :: ErrorT e f a -> Int # elem :: Eq a => a -> ErrorT e f a -> Bool # maximum :: Ord a => ErrorT e f a -> a # minimum :: Ord a => ErrorT e f a -> a # | |
Foldable (Constant a :: * -> *) | |
Methods fold :: Monoid m => Constant a m -> m # foldMap :: Monoid m => (a0 -> m) -> Constant a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Constant a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Constant a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Constant a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Constant a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 # toList :: Constant a a0 -> [a0] # null :: Constant a a0 -> Bool # length :: Constant a a0 -> Int # elem :: Eq a0 => a0 -> Constant a a0 -> Bool # maximum :: Ord a0 => Constant a a0 -> a0 # minimum :: Ord a0 => Constant a a0 -> a0 # | |
Foldable (Tagged s) | |
Methods fold :: Monoid m => Tagged s m -> m # foldMap :: Monoid m => (a -> m) -> Tagged s a -> m # foldr :: (a -> b -> b) -> b -> Tagged s a -> b # foldr' :: (a -> b -> b) -> b -> Tagged s a -> b # foldl :: (b -> a -> b) -> b -> Tagged s a -> b # foldl' :: (b -> a -> b) -> b -> Tagged s a -> b # foldr1 :: (a -> a -> a) -> Tagged s a -> a # foldl1 :: (a -> a -> a) -> Tagged s a -> a # elem :: Eq a => a -> Tagged s a -> Bool # maximum :: Ord a => Tagged s a -> a # minimum :: Ord a => Tagged s a -> a # | |
Bifoldable p => Foldable (Fix p) | |
Methods fold :: Monoid m => Fix p m -> m # foldMap :: Monoid m => (a -> m) -> Fix p a -> m # foldr :: (a -> b -> b) -> b -> Fix p a -> b # foldr' :: (a -> b -> b) -> b -> Fix p a -> b # foldl :: (b -> a -> b) -> b -> Fix p a -> b # foldl' :: (b -> a -> b) -> b -> Fix p a -> b # foldr1 :: (a -> a -> a) -> Fix p a -> a # foldl1 :: (a -> a -> a) -> Fix p a -> a # elem :: Eq a => a -> Fix p a -> Bool # maximum :: Ord a => Fix p a -> a # minimum :: Ord a => Fix p a -> a # | |
Bifoldable p => Foldable (Join p) | |
Methods fold :: Monoid m => Join p m -> m # foldMap :: Monoid m => (a -> m) -> Join p a -> m # foldr :: (a -> b -> b) -> b -> Join p a -> b # foldr' :: (a -> b -> b) -> b -> Join p a -> b # foldl :: (b -> a -> b) -> b -> Join p a -> b # foldl' :: (b -> a -> b) -> b -> Join p a -> b # foldr1 :: (a -> a -> a) -> Join p a -> a # foldl1 :: (a -> a -> a) -> Join p a -> a # elem :: Eq a => a -> Join p a -> Bool # maximum :: Ord a => Join p a -> a # minimum :: Ord a => Join p a -> a # | |
Foldable f => Foldable (CofreeF f a) | |
Methods fold :: Monoid m => CofreeF f a m -> m # foldMap :: Monoid m => (a0 -> m) -> CofreeF f a a0 -> m # foldr :: (a0 -> b -> b) -> b -> CofreeF f a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> CofreeF f a a0 -> b # foldl :: (b -> a0 -> b) -> b -> CofreeF f a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> CofreeF f a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> CofreeF f a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> CofreeF f a a0 -> a0 # toList :: CofreeF f a a0 -> [a0] # null :: CofreeF f a a0 -> Bool # length :: CofreeF f a a0 -> Int # elem :: Eq a0 => a0 -> CofreeF f a a0 -> Bool # maximum :: Ord a0 => CofreeF f a a0 -> a0 # minimum :: Ord a0 => CofreeF f a a0 -> a0 # | |
(Foldable f, Foldable w) => Foldable (CofreeT f w) | |
Methods fold :: Monoid m => CofreeT f w m -> m # foldMap :: Monoid m => (a -> m) -> CofreeT f w a -> m # foldr :: (a -> b -> b) -> b -> CofreeT f w a -> b # foldr' :: (a -> b -> b) -> b -> CofreeT f w a -> b # foldl :: (b -> a -> b) -> b -> CofreeT f w a -> b # foldl' :: (b -> a -> b) -> b -> CofreeT f w a -> b # foldr1 :: (a -> a -> a) -> CofreeT f w a -> a # foldl1 :: (a -> a -> a) -> CofreeT f w a -> a # toList :: CofreeT f w a -> [a] # null :: CofreeT f w a -> Bool # length :: CofreeT f w a -> Int # elem :: Eq a => a -> CofreeT f w a -> Bool # maximum :: Ord a => CofreeT f w a -> a # minimum :: Ord a => CofreeT f w a -> a # | |
(Foldable m, Foldable f) => Foldable (FreeT f m) | |
Methods fold :: Monoid m0 => FreeT f m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> FreeT f m a -> m0 # foldr :: (a -> b -> b) -> b -> FreeT f m a -> b # foldr' :: (a -> b -> b) -> b -> FreeT f m a -> b # foldl :: (b -> a -> b) -> b -> FreeT f m a -> b # foldl' :: (b -> a -> b) -> b -> FreeT f m a -> b # foldr1 :: (a -> a -> a) -> FreeT f m a -> a # foldl1 :: (a -> a -> a) -> FreeT f m a -> a # toList :: FreeT f m a -> [a] # length :: FreeT f m a -> Int # elem :: Eq a => a -> FreeT f m a -> Bool # maximum :: Ord a => FreeT f m a -> a # minimum :: Ord a => FreeT f m a -> a # | |
Foldable f => Foldable (FreeF f a) | |
Methods fold :: Monoid m => FreeF f a m -> m # foldMap :: Monoid m => (a0 -> m) -> FreeF f a a0 -> m # foldr :: (a0 -> b -> b) -> b -> FreeF f a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> FreeF f a a0 -> b # foldl :: (b -> a0 -> b) -> b -> FreeF f a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> FreeF f a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> FreeF f a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> FreeF f a a0 -> a0 # toList :: FreeF f a a0 -> [a0] # null :: FreeF f a a0 -> Bool # length :: FreeF f a a0 -> Int # elem :: Eq a0 => a0 -> FreeF f a a0 -> Bool # maximum :: Ord a0 => FreeF f a a0 -> a0 # minimum :: Ord a0 => FreeF f a a0 -> a0 # | |
Foldable (DSignal domain delay) # | |
Methods fold :: Monoid m => DSignal domain delay m -> m # foldMap :: Monoid m => (a -> m) -> DSignal domain delay a -> m # foldr :: (a -> b -> b) -> b -> DSignal domain delay a -> b # foldr' :: (a -> b -> b) -> b -> DSignal domain delay a -> b # foldl :: (b -> a -> b) -> b -> DSignal domain delay a -> b # foldl' :: (b -> a -> b) -> b -> DSignal domain delay a -> b # foldr1 :: (a -> a -> a) -> DSignal domain delay a -> a # foldl1 :: (a -> a -> a) -> DSignal domain delay a -> a # toList :: DSignal domain delay a -> [a] # null :: DSignal domain delay a -> Bool # length :: DSignal domain delay a -> Int # elem :: Eq a => a -> DSignal domain delay a -> Bool # maximum :: Ord a => DSignal domain delay a -> a # minimum :: Ord a => DSignal domain delay a -> a # | |
Foldable (K1 i c :: * -> *) | |
Methods fold :: Monoid m => K1 i c m -> m # foldMap :: Monoid m => (a -> m) -> K1 i c a -> m # foldr :: (a -> b -> b) -> b -> K1 i c a -> b # foldr' :: (a -> b -> b) -> b -> K1 i c a -> b # foldl :: (b -> a -> b) -> b -> K1 i c a -> b # foldl' :: (b -> a -> b) -> b -> K1 i c a -> b # foldr1 :: (a -> a -> a) -> K1 i c a -> a # foldl1 :: (a -> a -> a) -> K1 i c a -> a # elem :: Eq a => a -> K1 i c a -> Bool # maximum :: Ord a => K1 i c a -> a # minimum :: Ord a => K1 i c a -> a # | |
(Foldable f, Foldable g) => Foldable (f :+: g) | |
Methods fold :: Monoid m => (f :+: g) m -> m # foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m # foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b # foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b # foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b # foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b # foldr1 :: (a -> a -> a) -> (f :+: g) a -> a # foldl1 :: (a -> a -> a) -> (f :+: g) a -> a # toList :: (f :+: g) a -> [a] # length :: (f :+: g) a -> Int # elem :: Eq a => a -> (f :+: g) a -> Bool # maximum :: Ord a => (f :+: g) a -> a # minimum :: Ord a => (f :+: g) a -> a # | |
(Foldable f, Foldable g) => Foldable (f :*: g) | |
Methods fold :: Monoid m => (f :*: g) m -> m # foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m # foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b # foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b # foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b # foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b # foldr1 :: (a -> a -> a) -> (f :*: g) a -> a # foldl1 :: (a -> a -> a) -> (f :*: g) a -> a # toList :: (f :*: g) a -> [a] # length :: (f :*: g) a -> Int # elem :: Eq a => a -> (f :*: g) a -> Bool # maximum :: Ord a => (f :*: g) a -> a # minimum :: Ord a => (f :*: g) a -> a # | |
(Foldable f, Foldable g) => Foldable (Product f g) | Since: 4.9.0.0 |
Methods fold :: Monoid m => Product f g m -> m # foldMap :: Monoid m => (a -> m) -> Product f g a -> m # foldr :: (a -> b -> b) -> b -> Product f g a -> b # foldr' :: (a -> b -> b) -> b -> Product f g a -> b # foldl :: (b -> a -> b) -> b -> Product f g a -> b # foldl' :: (b -> a -> b) -> b -> Product f g a -> b # foldr1 :: (a -> a -> a) -> Product f g a -> a # foldl1 :: (a -> a -> a) -> Product f g a -> a # toList :: Product f g a -> [a] # null :: Product f g a -> Bool # length :: Product f g a -> Int # elem :: Eq a => a -> Product f g a -> Bool # maximum :: Ord a => Product f g a -> a # minimum :: Ord a => Product f g a -> a # | |
(Foldable f, Foldable g) => Foldable (Sum f g) | Since: 4.9.0.0 |
Methods fold :: Monoid m => Sum f g m -> m # foldMap :: Monoid m => (a -> m) -> Sum f g a -> m # foldr :: (a -> b -> b) -> b -> Sum f g a -> b # foldr' :: (a -> b -> b) -> b -> Sum f g a -> b # foldl :: (b -> a -> b) -> b -> Sum f g a -> b # foldl' :: (b -> a -> b) -> b -> Sum f g a -> b # foldr1 :: (a -> a -> a) -> Sum f g a -> a # foldl1 :: (a -> a -> a) -> Sum f g a -> a # elem :: Eq a => a -> Sum f g a -> Bool # maximum :: Ord a => Sum f g a -> a # minimum :: Ord a => Sum f g a -> a # | |
Foldable (Magma i t b) | |
Methods fold :: Monoid m => Magma i t b m -> m # foldMap :: Monoid m => (a -> m) -> Magma i t b a -> m # foldr :: (a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # foldr' :: (a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # foldl :: (b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # foldl' :: (b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # foldr1 :: (a -> a -> a) -> Magma i t b a -> a # foldl1 :: (a -> a -> a) -> Magma i t b a -> a # toList :: Magma i t b a -> [a] # null :: Magma i t b a -> Bool # length :: Magma i t b a -> Int # elem :: Eq a => a -> Magma i t b a -> Bool # maximum :: Ord a => Magma i t b a -> a # minimum :: Ord a => Magma i t b a -> a # | |
Foldable f => Foldable (M1 i c f) | |
Methods fold :: Monoid m => M1 i c f m -> m # foldMap :: Monoid m => (a -> m) -> M1 i c f a -> m # foldr :: (a -> b -> b) -> b -> M1 i c f a -> b # foldr' :: (a -> b -> b) -> b -> M1 i c f a -> b # foldl :: (b -> a -> b) -> b -> M1 i c f a -> b # foldl' :: (b -> a -> b) -> b -> M1 i c f a -> b # foldr1 :: (a -> a -> a) -> M1 i c f a -> a # foldl1 :: (a -> a -> a) -> M1 i c f a -> a # elem :: Eq a => a -> M1 i c f a -> Bool # maximum :: Ord a => M1 i c f a -> a # minimum :: Ord a => M1 i c f a -> a # | |
(Foldable f, Foldable g) => Foldable (f :.: g) | |
Methods fold :: Monoid m => (f :.: g) m -> m # foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m # foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b # foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b # foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b # foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b # foldr1 :: (a -> a -> a) -> (f :.: g) a -> a # foldl1 :: (a -> a -> a) -> (f :.: g) a -> a # toList :: (f :.: g) a -> [a] # length :: (f :.: g) a -> Int # elem :: Eq a => a -> (f :.: g) a -> Bool # maximum :: Ord a => (f :.: g) a -> a # minimum :: Ord a => (f :.: g) a -> a # | |
(Foldable f, Foldable g) => Foldable (Compose f g) | Since: 4.9.0.0 |
Methods fold :: Monoid m => Compose f g m -> m # foldMap :: Monoid m => (a -> m) -> Compose f g a -> m # foldr :: (a -> b -> b) -> b -> Compose f g a -> b # foldr' :: (a -> b -> b) -> b -> Compose f g a -> b # foldl :: (b -> a -> b) -> b -> Compose f g a -> b # foldl' :: (b -> a -> b) -> b -> Compose f g a -> b # foldr1 :: (a -> a -> a) -> Compose f g a -> a # foldl1 :: (a -> a -> a) -> Compose f g a -> a # toList :: Compose f g a -> [a] # null :: Compose f g a -> Bool # length :: Compose f g a -> Int # elem :: Eq a => a -> Compose f g a -> Bool # maximum :: Ord a => Compose f g a -> a # minimum :: Ord a => Compose f g a -> a # | |
Foldable (Clown f a :: * -> *) | |
Methods fold :: Monoid m => Clown f a m -> m # foldMap :: Monoid m => (a0 -> m) -> Clown f a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Clown f a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Clown f a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Clown f a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Clown f a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Clown f a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Clown f a a0 -> a0 # toList :: Clown f a a0 -> [a0] # null :: Clown f a a0 -> Bool # length :: Clown f a a0 -> Int # elem :: Eq a0 => a0 -> Clown f a a0 -> Bool # maximum :: Ord a0 => Clown f a a0 -> a0 # minimum :: Ord a0 => Clown f a a0 -> a0 # | |
Bifoldable p => Foldable (Flip p a) | |
Methods fold :: Monoid m => Flip p a m -> m # foldMap :: Monoid m => (a0 -> m) -> Flip p a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Flip p a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Flip p a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Flip p a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Flip p a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Flip p a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Flip p a a0 -> a0 # toList :: Flip p a a0 -> [a0] # length :: Flip p a a0 -> Int # elem :: Eq a0 => a0 -> Flip p a a0 -> Bool # maximum :: Ord a0 => Flip p a a0 -> a0 # minimum :: Ord a0 => Flip p a a0 -> a0 # | |
Foldable g => Foldable (Joker g a) | |
Methods fold :: Monoid m => Joker g a m -> m # foldMap :: Monoid m => (a0 -> m) -> Joker g a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Joker g a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Joker g a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Joker g a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Joker g a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Joker g a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Joker g a a0 -> a0 # toList :: Joker g a a0 -> [a0] # null :: Joker g a a0 -> Bool # length :: Joker g a a0 -> Int # elem :: Eq a0 => a0 -> Joker g a a0 -> Bool # maximum :: Ord a0 => Joker g a a0 -> a0 # minimum :: Ord a0 => Joker g a a0 -> a0 # | |
Bifoldable p => Foldable (WrappedBifunctor p a) | |
Methods fold :: Monoid m => WrappedBifunctor p a m -> m # foldMap :: Monoid m => (a0 -> m) -> WrappedBifunctor p a a0 -> m # foldr :: (a0 -> b -> b) -> b -> WrappedBifunctor p a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> WrappedBifunctor p a a0 -> b # foldl :: (b -> a0 -> b) -> b -> WrappedBifunctor p a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> WrappedBifunctor p a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> WrappedBifunctor p a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> WrappedBifunctor p a a0 -> a0 # toList :: WrappedBifunctor p a a0 -> [a0] # null :: WrappedBifunctor p a a0 -> Bool # length :: WrappedBifunctor p a a0 -> Int # elem :: Eq a0 => a0 -> WrappedBifunctor p a a0 -> Bool # maximum :: Ord a0 => WrappedBifunctor p a a0 -> a0 # minimum :: Ord a0 => WrappedBifunctor p a a0 -> a0 # | |
(Foldable f, Bifoldable p) => Foldable (Tannen f p a) | |
Methods fold :: Monoid m => Tannen f p a m -> m # foldMap :: Monoid m => (a0 -> m) -> Tannen f p a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Tannen f p a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Tannen f p a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Tannen f p a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Tannen f p a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Tannen f p a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Tannen f p a a0 -> a0 # toList :: Tannen f p a a0 -> [a0] # null :: Tannen f p a a0 -> Bool # length :: Tannen f p a a0 -> Int # elem :: Eq a0 => a0 -> Tannen f p a a0 -> Bool # maximum :: Ord a0 => Tannen f p a a0 -> a0 # minimum :: Ord a0 => Tannen f p a a0 -> a0 # | |
(Bifoldable p, Foldable g) => Foldable (Biff p f g a) | |
Methods fold :: Monoid m => Biff p f g a m -> m # foldMap :: Monoid m => (a0 -> m) -> Biff p f g a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Biff p f g a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Biff p f g a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Biff p f g a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Biff p f g a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Biff p f g a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Biff p f g a a0 -> a0 # toList :: Biff p f g a a0 -> [a0] # null :: Biff p f g a a0 -> Bool # length :: Biff p f g a a0 -> Int # elem :: Eq a0 => a0 -> Biff p f g a a0 -> Bool # maximum :: Ord a0 => Biff p f g a a0 -> a0 # minimum :: Ord a0 => Biff p f g a a0 -> a0 # |
class (Functor t, Foldable t) => Traversable (t :: * -> *) where #
Functors representing data structures that can be traversed from left to right.
A definition of traverse
must satisfy the following laws:
- naturality
t .
for every applicative transformationtraverse
f =traverse
(t . f)t
- identity
traverse
Identity = Identity- composition
traverse
(Compose .fmap
g . f) = Compose .fmap
(traverse
g) .traverse
f
A definition of sequenceA
must satisfy the following laws:
- naturality
t .
for every applicative transformationsequenceA
=sequenceA
.fmap
tt
- identity
sequenceA
.fmap
Identity = Identity- composition
sequenceA
.fmap
Compose = Compose .fmap
sequenceA
.sequenceA
where an applicative transformation is a function
t :: (Applicative f, Applicative g) => f a -> g a
preserving the Applicative
operations, i.e.
and the identity functor Identity
and composition of functors Compose
are defined as
newtype Identity a = Identity a instance Functor Identity where fmap f (Identity x) = Identity (f x) instance Applicative Identity where pure x = Identity x Identity f <*> Identity x = Identity (f x) newtype Compose f g a = Compose (f (g a)) instance (Functor f, Functor g) => Functor (Compose f g) where fmap f (Compose x) = Compose (fmap (fmap f) x) instance (Applicative f, Applicative g) => Applicative (Compose f g) where pure x = Compose (pure (pure x)) Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
(The naturality law is implied by parametricity.)
Instances are similar to Functor
, e.g. given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Traversable Tree where traverse f Empty = pure Empty traverse f (Leaf x) = Leaf <$> f x traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
This is suitable even for abstract types, as the laws for <*>
imply a form of associativity.
The superclass instances should satisfy the following:
- In the
Functor
instance,fmap
should be equivalent to traversal with the identity applicative functor (fmapDefault
). - In the
Foldable
instance,foldMap
should be equivalent to traversal with a constant applicative functor (foldMapDefault
).
Methods
traverse :: Applicative f => (a -> f b) -> t a -> f (t b) #
Map each element of a structure to an action, evaluate these actions
from left to right, and collect the results. For a version that ignores
the results see traverse_
.
sequenceA :: Applicative f => t (f a) -> f (t a) #
Evaluate each action in the structure from left to right, and
and collect the results. For a version that ignores the results
see sequenceA_
.
mapM :: Monad m => (a -> m b) -> t a -> m (t b) #
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and collect the results. For
a version that ignores the results see mapM_
.
sequence :: Monad m => t (m a) -> m (t a) #
Evaluate each monadic action in the structure from left to
right, and collect the results. For a version that ignores the
results see sequence_
.
Instances
Traversable [] | Since: 2.1 |
Traversable Maybe | Since: 2.1 |
Traversable Par1 | |
Traversable Complex | |
Traversable Min | Since: 4.9.0.0 |
Traversable Max | Since: 4.9.0.0 |
Traversable First | Since: 4.9.0.0 |
Traversable Last | Since: 4.9.0.0 |
Traversable Option | Since: 4.9.0.0 |
Traversable ZipList | Since: 4.9.0.0 |
Traversable Identity | |
Traversable First | Since: 4.8.0.0 |
Traversable Last | Since: 4.8.0.0 |
Traversable Dual | Since: 4.8.0.0 |
Traversable Sum | Since: 4.8.0.0 |
Traversable Product | Since: 4.8.0.0 |
Traversable NonEmpty | Since: 4.9.0.0 |
Traversable IntMap | |
Traversable Tree | |
Traversable Seq | |
Traversable FingerTree | |
Methods traverse :: Applicative f => (a -> f b) -> FingerTree a -> f (FingerTree b) # sequenceA :: Applicative f => FingerTree (f a) -> f (FingerTree a) # mapM :: Monad m => (a -> m b) -> FingerTree a -> m (FingerTree b) # sequence :: Monad m => FingerTree (m a) -> m (FingerTree a) # | |
Traversable Digit | |
Traversable Node | |
Traversable Elem | |
Traversable ViewL | |
Traversable ViewR | |
Traversable Vector | |
Traversable Array | |
Traversable (Either a) | Since: 4.7.0.0 |
Traversable (V1 :: * -> *) | |
Traversable (U1 :: * -> *) | Since: 4.9.0.0 |
Traversable ((,) a) | Since: 4.7.0.0 |
Ix i => Traversable (Array i) | Since: 2.1 |
Traversable (Arg a) | Since: 4.9.0.0 |
Traversable (Proxy :: * -> *) | Since: 4.7.0.0 |
Traversable (Map k) | |
(KnownNat n, 1 <= n) => Traversable (Vec n) # | |
Traversable (Level i) | |
Traversable f => Traversable (Cofree f) | |
Traversable f => Traversable (Free f) | |
Traversable f => Traversable (Yoneda f) | |
Traversable (HashMap k) | |
Traversable (Signal domain) # | |
Methods traverse :: Applicative f => (a -> f b) -> Signal domain a -> f (Signal domain b) # sequenceA :: Applicative f => Signal domain (f a) -> f (Signal domain a) # mapM :: Monad m => (a -> m b) -> Signal domain a -> m (Signal domain b) # sequence :: Monad m => Signal domain (m a) -> m (Signal domain a) # | |
KnownNat d => Traversable (RTree d) # | |
Traversable f => Traversable (Rec1 f) | |
Traversable (URec Char :: * -> *) | |
Traversable (URec Double :: * -> *) | |
Traversable (URec Float :: * -> *) | |
Traversable (URec Int :: * -> *) | |
Traversable (URec Word :: * -> *) | |
Traversable (URec (Ptr ()) :: * -> *) | |
Methods traverse :: Applicative f => (a -> f b) -> URec (Ptr ()) a -> f (URec (Ptr ()) b) # sequenceA :: Applicative f => URec (Ptr ()) (f a) -> f (URec (Ptr ()) a) # mapM :: Monad m => (a -> m b) -> URec (Ptr ()) a -> m (URec (Ptr ()) b) # sequence :: Monad m => URec (Ptr ()) (m a) -> m (URec (Ptr ()) a) # | |
Traversable (Const m :: * -> *) | Since: 4.7.0.0 |
Traversable f => Traversable (ErrorT e f) | |
Traversable (Constant a :: * -> *) | |
Traversable (Tagged s) | |
Bitraversable p => Traversable (Fix p) | |
Bitraversable p => Traversable (Join p) | |
Traversable f => Traversable (CofreeF f a) | |
Methods traverse :: Applicative f0 => (a0 -> f0 b) -> CofreeF f a a0 -> f0 (CofreeF f a b) # sequenceA :: Applicative f0 => CofreeF f a (f0 a0) -> f0 (CofreeF f a a0) # mapM :: Monad m => (a0 -> m b) -> CofreeF f a a0 -> m (CofreeF f a b) # sequence :: Monad m => CofreeF f a (m a0) -> m (CofreeF f a a0) # | |
(Traversable f, Traversable w) => Traversable (CofreeT f w) | |
(Monad m, Traversable m, Traversable f) => Traversable (FreeT f m) | |
Traversable f => Traversable (FreeF f a) | |
Traversable (DSignal domain delay) # | |
Methods traverse :: Applicative f => (a -> f b) -> DSignal domain delay a -> f (DSignal domain delay b) # sequenceA :: Applicative f => DSignal domain delay (f a) -> f (DSignal domain delay a) # mapM :: Monad m => (a -> m b) -> DSignal domain delay a -> m (DSignal domain delay b) # sequence :: Monad m => DSignal domain delay (m a) -> m (DSignal domain delay a) # | |
Traversable (K1 i c :: * -> *) | |
(Traversable f, Traversable g) => Traversable (f :+: g) | |
(Traversable f, Traversable g) => Traversable (f :*: g) | |
(Traversable f, Traversable g) => Traversable (Product f g) | Since: 4.9.0.0 |
(Traversable f, Traversable g) => Traversable (Sum f g) | Since: 4.9.0.0 |
Traversable (Magma i t b) | |
Traversable f => Traversable (M1 i c f) | |
(Traversable f, Traversable g) => Traversable (f :.: g) | |
(Traversable f, Traversable g) => Traversable (Compose f g) | Since: 4.9.0.0 |
Traversable (Clown f a :: * -> *) | |
Bitraversable p => Traversable (Flip p a) | |
Traversable g => Traversable (Joker g a) | |
Bitraversable p => Traversable (WrappedBifunctor p a) | |
Methods traverse :: Applicative f => (a0 -> f b) -> WrappedBifunctor p a a0 -> f (WrappedBifunctor p a b) # sequenceA :: Applicative f => WrappedBifunctor p a (f a0) -> f (WrappedBifunctor p a a0) # mapM :: Monad m => (a0 -> m b) -> WrappedBifunctor p a a0 -> m (WrappedBifunctor p a b) # sequence :: Monad m => WrappedBifunctor p a (m a0) -> m (WrappedBifunctor p a a0) # | |
(Traversable f, Bitraversable p) => Traversable (Tannen f p a) | |
Methods traverse :: Applicative f0 => (a0 -> f0 b) -> Tannen f p a a0 -> f0 (Tannen f p a b) # sequenceA :: Applicative f0 => Tannen f p a (f0 a0) -> f0 (Tannen f p a a0) # mapM :: Monad m => (a0 -> m b) -> Tannen f p a a0 -> m (Tannen f p a b) # sequence :: Monad m => Tannen f p a (m a0) -> m (Tannen f p a a0) # | |
(Bitraversable p, Traversable g) => Traversable (Biff p f g a) | |
Methods traverse :: Applicative f0 => (a0 -> f0 b) -> Biff p f g a a0 -> f0 (Biff p f g a b) # sequenceA :: Applicative f0 => Biff p f g a (f0 a0) -> f0 (Biff p f g a a0) # mapM :: Monad m => (a0 -> m b) -> Biff p f g a a0 -> m (Biff p f g a b) # sequence :: Monad m => Biff p f g a (m a0) -> m (Biff p f g a a0) # |
The class of semigroups (types with an associative binary operation).
Instances should satisfy the associativity law:
Since: 4.9.0.0
Minimal complete definition
Instances
Semigroup Ordering | Since: 4.9.0.0 |
Semigroup () | Since: 4.9.0.0 |
Semigroup Void | Since: 4.9.0.0 |
Semigroup All | Since: 4.9.0.0 |
Semigroup Any | Since: 4.9.0.0 |
Semigroup ByteString | |
Methods (<>) :: ByteString -> ByteString -> ByteString # sconcat :: NonEmpty ByteString -> ByteString # stimes :: Integral b => b -> ByteString -> ByteString # | |
Semigroup ByteString | |
Methods (<>) :: ByteString -> ByteString -> ByteString # sconcat :: NonEmpty ByteString -> ByteString # stimes :: Integral b => b -> ByteString -> ByteString # | |
Semigroup IntSet | Since: 0.5.7 |
Semigroup Doc | |
Semigroup ULetDecEnv | |
() :=> (Semigroup [a]) | |
() :=> (Semigroup Ordering) | |
() :=> (Semigroup ()) | |
() :=> (Semigroup (Dict a)) | |
Class () (Semigroup a) | |
Semigroup [a] | Since: 4.9.0.0 |
Semigroup a => Semigroup (Maybe a) | Since: 4.9.0.0 |
Semigroup a => Semigroup (IO a) | Since: 4.10.0.0 |
Ord a => Semigroup (Min a) | Since: 4.9.0.0 |
Ord a => Semigroup (Max a) | Since: 4.9.0.0 |
Semigroup (First a) | Since: 4.9.0.0 |
Semigroup (Last a) | Since: 4.9.0.0 |
Monoid m => Semigroup (WrappedMonoid m) | Since: 4.9.0.0 |
Methods (<>) :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # sconcat :: NonEmpty (WrappedMonoid m) -> WrappedMonoid m # stimes :: Integral b => b -> WrappedMonoid m -> WrappedMonoid m # | |
Semigroup a => Semigroup (Option a) | Since: 4.9.0.0 |
Semigroup a => Semigroup (Identity a) | |
Semigroup (First a) | Since: 4.9.0.0 |
Semigroup (Last a) | Since: 4.9.0.0 |
Semigroup a => Semigroup (Dual a) | Since: 4.9.0.0 |
Semigroup (Endo a) | Since: 4.9.0.0 |
Num a => Semigroup (Sum a) | Since: 4.9.0.0 |
Num a => Semigroup (Product a) | Since: 4.9.0.0 |
Semigroup a => Semigroup (Down a) | Since: 4.11.0.0 |
Semigroup (NonEmpty a) | Since: 4.9.0.0 |
Semigroup (IntMap a) | Since: 0.5.7 |
Semigroup (Seq a) | Since: 0.5.7 |
Ord a => Semigroup (Set a) | Since: 0.5.7 |
Semigroup (Doc a) | |
Semigroup (Leftmost a) | |
Semigroup (Rightmost a) | |
Semigroup (DList a) | |
Semigroup (MergeSet a) | |
(Hashable a, Eq a) => Semigroup (HashSet a) | |
Storable a => Semigroup (Vector a) | |
Prim a => Semigroup (Vector a) | |
Semigroup (Vector a) | |
Semigroup (Comparison a) | |
Semigroup (Equivalence a) | |
Semigroup (Predicate a) | |
Semigroup (Array a) | |
Semigroup (Dict a) | |
Ord a => Semigroup (Max a) | |
Ord a => Semigroup (Min a) | |
Semigroup (NonEmptyDList a) | |
(Semigroup a) :=> (Semigroup (Maybe a)) | |
(Semigroup a) :=> (Semigroup (Const a b)) | |
(Semigroup a) :=> (Semigroup (Identity a)) | |
(Semigroup a) :=> (Semigroup (IO a)) | |
Class (Semigroup a) (Monoid a) | |
Semigroup b => Semigroup (a -> b) | Since: 4.9.0.0 |
Semigroup (Either a b) | Since: 4.9.0.0 |
(Semigroup a, Semigroup b) => Semigroup (a, b) | Since: 4.9.0.0 |
Semigroup a => Semigroup (ST s a) | Since: 4.11.0.0 |
Semigroup (Proxy s) | Since: 4.9.0.0 |
Ord k => Semigroup (Map k v) | |
Monad m => Semigroup (Sequenced a m) | |
Applicative f => Semigroup (Traversed a f) | |
Semigroup (ReifiedFold s a) | |
(Eq k, Hashable k) => Semigroup (HashMap k v) | |
Semigroup (f a) => Semigroup (Indexing f a) | |
Semigroup a => Semigroup (Op a b) | |
(Contravariant f, Applicative f) => Semigroup (Folding f a) | |
Apply f => Semigroup (TraversedF a f) | |
Semigroup (Deepening i a) | |
(Semigroup a, Semigroup b) :=> (Semigroup (a, b)) | |
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) | Since: 4.9.0.0 |
Semigroup a => Semigroup (Const a b) | |
Alternative f => Semigroup (Alt f a) | Since: 4.9.0.0 |
Semigroup a => Semigroup (Constant a b) | |
Semigroup (ReifiedIndexedFold i s a) | |
Reifies s (ReifiedMonoid a) => Semigroup (ReflectedMonoid a s) | |
Semigroup a => Semigroup (Tagged s a) | |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) | Since: 4.9.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) | Since: 4.9.0.0 |
Contravariant g => Semigroup (BazaarT p g a b t) | |
Contravariant g => Semigroup (BazaarT1 p g a b t) | |
class Semigroup a => Monoid a where #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
x
<>
mempty
= xmempty
<>
x = xx
(<>
(y<>
z) = (x<>
y)<>
zSemigroup
law)mconcat
=foldr
'(<>)'mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
NOTE: Semigroup
is a superclass of Monoid
since base-4.11.0.0.
Minimal complete definition
Methods
Identity of mappend
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.mappend
= '(<>)'
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
Instances
Monoid Ordering | Since: 2.1 |
Monoid () | Since: 2.1 |
Monoid All | Since: 2.1 |
Monoid Any | Since: 2.1 |
Monoid ByteString | |
Methods mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
Monoid ByteString | |
Methods mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
Monoid IntSet | |
Monoid Doc | |
Monoid ULetDecEnv | |
a :=> (Monoid (Dict a)) | |
() :=> (Monoid [a]) | |
() :=> (Monoid Ordering) | |
() :=> (Monoid ()) | |
Monoid [a] | Since: 2.1 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: 2.1 |
Monoid a => Monoid (IO a) | Since: 4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a) | Since: 4.9.0.0 |
(Ord a, Bounded a) => Monoid (Max a) | Since: 4.9.0.0 |
Monoid m => Monoid (WrappedMonoid m) | Since: 4.9.0.0 |
Methods mempty :: WrappedMonoid m # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # mconcat :: [WrappedMonoid m] -> WrappedMonoid m # | |
Semigroup a => Monoid (Option a) | Since: 4.9.0.0 |
Monoid a => Monoid (Identity a) | |
Monoid (First a) | Since: 2.1 |
Monoid (Last a) | Since: 2.1 |
Monoid a => Monoid (Dual a) | Since: 2.1 |
Monoid (Endo a) | Since: 2.1 |
Num a => Monoid (Sum a) | Since: 2.1 |
Num a => Monoid (Product a) | Since: 2.1 |
Monoid a => Monoid (Down a) | Since: 4.11.0.0 |
Monoid (IntMap a) | |
Monoid (Seq a) | |
Ord a => Monoid (Set a) | |
Monoid (Doc a) | |
Monoid (Leftmost a) | |
Monoid (Rightmost a) | |
Monoid (DList a) | |
Monoid (MergeSet a) | |
(Hashable a, Eq a) => Monoid (HashSet a) | |
Storable a => Monoid (Vector a) | |
Prim a => Monoid (Vector a) | |
Monoid (Vector a) | |
Monoid (Comparison a) | |
Monoid (Equivalence a) | |
Monoid (Predicate a) | |
Monoid (Array a) | |
a => Monoid (Dict a) | |
Ord a => Monoid (Max a) | |
Ord a => Monoid (Min a) | |
(Monoid a) :=> (Monoid (Maybe a)) | |
(Monoid a) :=> (Monoid (Const a b)) | |
(Monoid a) :=> (Monoid (Identity a)) | |
(Monoid a) :=> (Monoid (IO a)) | |
(Monoid a) :=> (Applicative ((,) a)) | |
Methods ins :: Monoid a :- Applicative ((,) a) | |
(Monoid a) :=> (Applicative (Const a :: * -> *)) | |
Methods ins :: Monoid a :- Applicative (Const a) | |
Class (Semigroup a) (Monoid a) | |
Monoid b => Monoid (a -> b) | Since: 2.1 |
(Monoid a, Monoid b) => Monoid (a, b) | Since: 2.1 |
Monoid a => Monoid (ST s a) | Since: 4.11.0.0 |
Monoid (Proxy s) | Since: 4.7.0.0 |
Ord k => Monoid (Map k v) | |
Monad m => Monoid (Sequenced a m) | |
Applicative f => Monoid (Traversed a f) | |
Monoid (ReifiedFold s a) | |
(Eq k, Hashable k) => Monoid (HashMap k v) | |
Monoid (f a) => Monoid (Indexing f a) | |
Monoid a => Monoid (Op a b) | |
(Contravariant f, Applicative f) => Monoid (Folding f a) | |
(Apply f, Applicative f) => Monoid (TraversedF a f) | |
Monoid (Deepening i a) | |
(Monoid a, Monoid b) :=> (Monoid (a, b)) | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | Since: 2.1 |
Monoid a => Monoid (Const a b) | |
Alternative f => Monoid (Alt f a) | Since: 4.8.0.0 |
Monoid a => Monoid (Constant a b) | |
Monoid (ReifiedIndexedFold i s a) | |
Reifies s (ReifiedMonoid a) => Monoid (ReflectedMonoid a s) | |
(Semigroup a, Monoid a) => Monoid (Tagged s a) | |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | Since: 2.1 |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | Since: 2.1 |
Contravariant g => Monoid (BazaarT p g a b t) | |
Instances
Bounded Bool | Since: 2.1 |
Enum Bool | Since: 2.1 |
Eq Bool | |
Data Bool | Since: 4.0.0.0 |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bool -> c Bool # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool # dataTypeOf :: Bool -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bool) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) # gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r # gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool # | |
Ord Bool | |
Read Bool | Since: 2.1 |
Show Bool | |
Ix Bool | Since: 2.1 |
Generic Bool | |
Lift Bool | |
SingKind Bool | Since: 4.9.0.0 |
Storable Bool | Since: 2.1 |
Bits Bool | Interpret Since: 4.7.0.0 |
Methods (.&.) :: Bool -> Bool -> Bool # (.|.) :: Bool -> Bool -> Bool # complement :: Bool -> Bool # shift :: Bool -> Int -> Bool # rotate :: Bool -> Int -> Bool # setBit :: Bool -> Int -> Bool # clearBit :: Bool -> Int -> Bool # complementBit :: Bool -> Int -> Bool # testBit :: Bool -> Int -> Bool # bitSizeMaybe :: Bool -> Maybe Int # shiftL :: Bool -> Int -> Bool # unsafeShiftL :: Bool -> Int -> Bool # shiftR :: Bool -> Int -> Bool # unsafeShiftR :: Bool -> Int -> Bool # rotateL :: Bool -> Int -> Bool # | |
FiniteBits Bool | Since: 4.7.0.0 |
Methods finiteBitSize :: Bool -> Int # countLeadingZeros :: Bool -> Int # countTrailingZeros :: Bool -> Int # | |
NFData Bool | |
ShowX Bool Source # | |
Arbitrary Bool | |
CoArbitrary Bool | |
Methods coarbitrary :: Bool -> Gen b -> Gen b | |
Unbox Bool | |
BitPack Bool Source # | |
Testable Bool | |
PBounded Bool | |
Associated Types type MinBound :: a type MaxBound :: a | |
PEnum Bool | |
Associated Types type Succ arg :: a type Pred arg :: a type ToEnum arg :: a type FromEnum arg :: Nat type EnumFromTo arg arg1 :: [a] type EnumFromThenTo arg arg1 arg2 :: [a] | |
SBounded Bool | |
SEnum Bool | |
Methods sSucc :: Sing t -> Sing (Apply SuccSym0 t) sPred :: Sing t -> Sing (Apply PredSym0 t) sToEnum :: Sing t -> Sing (Apply ToEnumSym0 t) sFromEnum :: Sing t -> Sing (Apply FromEnumSym0 t) sEnumFromTo :: Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) sEnumFromThenTo :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) | |
PEq Bool | |
SEq Bool | |
POrd Bool | |
SOrd Bool | |
Methods sCompare :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) (%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) (%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) (%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) (%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) sMin :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) | |
PShow Bool | |
SShow Bool | |
Methods sShowsPrec :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) sShowList :: Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) | |
ShowSing Bool | |
Methods showsSingPrec :: Int -> Sing a -> ShowS | |
Bundle Bool Source # | |
SingI False | Since: 4.9.0.0 |
SingI True | Since: 4.9.0.0 |
Vector Vector Bool | |
Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Bool -> m (Vector Bool) basicUnsafeThaw :: PrimMonad m => Vector Bool -> m (Mutable Vector (PrimState m) Bool) basicLength :: Vector Bool -> Int basicUnsafeSlice :: Int -> Int -> Vector Bool -> Vector Bool basicUnsafeIndexM :: Monad m => Vector Bool -> Int -> m Bool basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Bool -> Vector Bool -> m () | |
MVector MVector Bool | |
Methods basicLength :: MVector s Bool -> Int basicUnsafeSlice :: Int -> Int -> MVector s Bool -> MVector s Bool basicOverlaps :: MVector s Bool -> MVector s Bool -> Bool basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Bool) basicInitialize :: PrimMonad m => MVector (PrimState m) Bool -> m () basicUnsafeReplicate :: PrimMonad m => Int -> Bool -> m (MVector (PrimState m) Bool) basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Bool -> Int -> m Bool basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Bool -> Int -> Bool -> m () basicClear :: PrimMonad m => MVector (PrimState m) Bool -> m () basicSet :: PrimMonad m => MVector (PrimState m) Bool -> Bool -> m () basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Bool -> MVector (PrimState m) Bool -> m () basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Bool -> MVector (PrimState m) Bool -> m () basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Bool -> Int -> m (MVector (PrimState m) Bool) | |
LockStep Bool c Source # | |
() :=> (Bounded Bool) | |
() :=> (Enum Bool) | |
() :=> (Eq Bool) | |
() :=> (Ord Bool) | |
() :=> (Read Bool) | |
() :=> (Show Bool) | |
() :=> (Bits Bool) | |
SuppressUnusedWarnings ShowParenSym2 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (&&@#@$$) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (||@#@$$) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings Compare_6989586621679551605Sym1 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ShowParenSym1 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ShowsPrec_6989586621679888031Sym2 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ShowsPrec_6989586621679888031Sym1 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings NotSym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (&&@#@$) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (||@#@$) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings Compare_6989586621679551605Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ShowParenSym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings FromEnum_6989586621680021011Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings AndSym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings OrSym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ToEnum_6989586621680021001Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ShowsPrec_6989586621679888031Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (UnionBySym2 :: (TyFun a6989586621679681237 (TyFun a6989586621679681237 Bool -> Type) -> Type) -> [a6989586621679681237] -> TyFun [a6989586621679681237] [a6989586621679681237] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (UnionBySym1 :: (TyFun a6989586621679681237 (TyFun a6989586621679681237 Bool -> Type) -> Type) -> TyFun [a6989586621679681237] (TyFun [a6989586621679681237] [a6989586621679681237] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (TakeWhileSym1 :: (TyFun a6989586621679681264 Bool -> Type) -> TyFun [a6989586621679681264] [a6989586621679681264] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (SpanSym1 :: (TyFun a6989586621679681261 Bool -> Type) -> TyFun [a6989586621679681261] ([a6989586621679681261], [a6989586621679681261]) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (SelectSym2 :: (TyFun a6989586621679681247 Bool -> Type) -> a6989586621679681247 -> TyFun ([a6989586621679681247], [a6989586621679681247]) ([a6989586621679681247], [a6989586621679681247]) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (SelectSym1 :: (TyFun a6989586621679681247 Bool -> Type) -> TyFun a6989586621679681247 (TyFun ([a6989586621679681247], [a6989586621679681247]) ([a6989586621679681247], [a6989586621679681247]) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (PartitionSym1 :: (TyFun a6989586621679681248 Bool -> Type) -> TyFun [a6989586621679681248] ([a6989586621679681248], [a6989586621679681248]) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (NubBySym1 :: (TyFun a6989586621679681239 (TyFun a6989586621679681239 Bool -> Type) -> Type) -> TyFun [a6989586621679681239] [a6989586621679681239] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690979ZsSym2 :: (TyFun k Bool -> Type) -> k -> TyFun [k] [k] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690979ZsSym1 :: (TyFun k Bool -> Type) -> TyFun k (TyFun [k] [k] -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690979YsSym2 :: (TyFun k Bool -> Type) -> k -> TyFun [k] [k] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690979YsSym1 :: (TyFun k Bool -> Type) -> TyFun k (TyFun [k] [k] -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690979X_6989586621679690980Sym2 :: (TyFun k Bool -> Type) -> k -> TyFun [k] ([k], [k]) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690979X_6989586621679690980Sym1 :: (TyFun k Bool -> Type) -> TyFun k (TyFun [k] ([k], [k]) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690886ZsSym2 :: (TyFun k Bool -> Type) -> k -> TyFun [k] [k] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690886ZsSym1 :: (TyFun k Bool -> Type) -> TyFun k (TyFun [k] [k] -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690886YsSym2 :: (TyFun k Bool -> Type) -> k -> TyFun [k] [k] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690886YsSym1 :: (TyFun k Bool -> Type) -> TyFun k (TyFun [k] [k] -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690886X_6989586621679690887Sym2 :: (TyFun k Bool -> Type) -> k -> TyFun [k] ([k], [k]) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690886X_6989586621679690887Sym1 :: (TyFun k Bool -> Type) -> TyFun k (TyFun [k] ([k], [k]) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IntersectBySym2 :: (TyFun a6989586621679681265 (TyFun a6989586621679681265 Bool -> Type) -> Type) -> [a6989586621679681265] -> TyFun [a6989586621679681265] [a6989586621679681265] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IntersectBySym1 :: (TyFun a6989586621679681265 (TyFun a6989586621679681265 Bool -> Type) -> Type) -> TyFun [a6989586621679681265] (TyFun [a6989586621679681265] [a6989586621679681265] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (GroupBySym1 :: (TyFun a6989586621679681251 (TyFun a6989586621679681251 Bool -> Type) -> Type) -> TyFun [a6989586621679681251] [[a6989586621679681251]] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FindSym1 :: (TyFun a6989586621679681271 Bool -> Type) -> TyFun [a6989586621679681271] (Maybe a6989586621679681271) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FindIndicesSym1 :: (TyFun a6989586621679681267 Bool -> Type) -> TyFun [a6989586621679681267] [Nat] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FindIndexSym1 :: (TyFun a6989586621679681268 Bool -> Type) -> TyFun [a6989586621679681268] (Maybe Nat) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FilterSym1 :: (TyFun a6989586621679681272 Bool -> Type) -> TyFun [a6989586621679681272] [a6989586621679681272] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Elem_bySym2 :: (TyFun a6989586621679681238 (TyFun a6989586621679681238 Bool -> Type) -> Type) -> a6989586621679681238 -> TyFun [a6989586621679681238] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Elem_bySym1 :: (TyFun a6989586621679681238 (TyFun a6989586621679681238 Bool -> Type) -> Type) -> TyFun a6989586621679681238 (TyFun [a6989586621679681238] Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (DropWhileSym1 :: (TyFun a6989586621679681263 Bool -> Type) -> TyFun [a6989586621679681263] [a6989586621679681263] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (DropWhileEndSym1 :: (TyFun a6989586621679681262 Bool -> Type) -> TyFun [a6989586621679681262] [a6989586621679681262] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (DeleteFirstsBySym2 :: (TyFun a6989586621679681277 (TyFun a6989586621679681277 Bool -> Type) -> Type) -> [a6989586621679681277] -> TyFun [a6989586621679681277] [a6989586621679681277] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (DeleteFirstsBySym1 :: (TyFun a6989586621679681277 (TyFun a6989586621679681277 Bool -> Type) -> Type) -> TyFun [a6989586621679681277] (TyFun [a6989586621679681277] [a6989586621679681277] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (DeleteBySym2 :: (TyFun a6989586621679681278 (TyFun a6989586621679681278 Bool -> Type) -> Type) -> a6989586621679681278 -> TyFun [a6989586621679681278] [a6989586621679681278] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (DeleteBySym1 :: (TyFun a6989586621679681278 (TyFun a6989586621679681278 Bool -> Type) -> Type) -> TyFun a6989586621679681278 (TyFun [a6989586621679681278] [a6989586621679681278] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (BreakSym1 :: (TyFun a6989586621679681260 Bool -> Type) -> TyFun [a6989586621679681260] ([a6989586621679681260], [a6989586621679681260]) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (AnySym1 :: (TyFun a6989586621679681341 Bool -> Type) -> TyFun [a6989586621679681341] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (AllSym1 :: (TyFun a6989586621679681342 Bool -> Type) -> TyFun [a6989586621679681342] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsSuffixOfSym1 :: [a6989586621679681323] -> TyFun [a6989586621679681323] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsPrefixOfSym1 :: [a6989586621679681324] -> TyFun [a6989586621679681324] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsInfixOfSym1 :: [a6989586621679681322] -> TyFun [a6989586621679681322] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (TFHelper_6989586621679544141Sym1 :: a6989586621679542823 -> TyFun a6989586621679542823 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (TFHelper_6989586621679544108Sym1 :: a6989586621679542823 -> TyFun a6989586621679542823 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (TFHelper_6989586621679544075Sym1 :: a6989586621679542823 -> TyFun a6989586621679542823 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (TFHelper_6989586621679544042Sym1 :: a6989586621679542823 -> TyFun a6989586621679542823 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544194Scrutinee_6989586621679542855Sym1 :: k1 -> TyFun k1 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544161Scrutinee_6989586621679542853Sym1 :: k1 -> TyFun k1 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679543995Scrutinee_6989586621679542843Sym1 :: k1 -> TyFun k1 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679543985Scrutinee_6989586621679542841Sym1 :: k1 -> TyFun k1 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((>@#@$$) :: a6989586621679542823 -> TyFun a6989586621679542823 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((>=@#@$$) :: a6989586621679542823 -> TyFun a6989586621679542823 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((<@#@$$) :: a6989586621679542823 -> TyFun a6989586621679542823 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((<=@#@$$) :: a6989586621679542823 -> TyFun a6989586621679542823 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (NotElemSym1 :: a6989586621679681320 -> TyFun [a6989586621679681320] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ElemSym1 :: a6989586621679681321 -> TyFun [a6989586621679681321] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((==@#@$$) :: a6989586621679532030 -> TyFun a6989586621679532030 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((/=@#@$$) :: a6989586621679532030 -> TyFun a6989586621679532030 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Bool_Sym2 :: a6989586621679529656 -> a6989586621679529656 -> TyFun Bool a6989586621679529656 -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Bool_Sym1 :: a6989586621679529656 -> TyFun a6989586621679529656 (TyFun Bool a6989586621679529656 -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (UnionBySym0 :: TyFun (TyFun a6989586621679681237 (TyFun a6989586621679681237 Bool -> Type) -> Type) (TyFun [a6989586621679681237] (TyFun [a6989586621679681237] [a6989586621679681237] -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (TyFun a6989586621679681264 Bool -> Type) (TyFun [a6989586621679681264] [a6989586621679681264] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (SpanSym0 :: TyFun (TyFun a6989586621679681261 Bool -> Type) (TyFun [a6989586621679681261] ([a6989586621679681261], [a6989586621679681261]) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (SelectSym0 :: TyFun (TyFun a6989586621679681247 Bool -> Type) (TyFun a6989586621679681247 (TyFun ([a6989586621679681247], [a6989586621679681247]) ([a6989586621679681247], [a6989586621679681247]) -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (PartitionSym0 :: TyFun (TyFun a6989586621679681248 Bool -> Type) (TyFun [a6989586621679681248] ([a6989586621679681248], [a6989586621679681248]) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (NubBySym0 :: TyFun (TyFun a6989586621679681239 (TyFun a6989586621679681239 Bool -> Type) -> Type) (TyFun [a6989586621679681239] [a6989586621679681239] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690979ZsSym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690979YsSym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690979X_6989586621679690980Sym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] ([k], [k]) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690886ZsSym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690886YsSym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690886X_6989586621679690887Sym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] ([k], [k]) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (TyFun a6989586621679681265 (TyFun a6989586621679681265 Bool -> Type) -> Type) (TyFun [a6989586621679681265] (TyFun [a6989586621679681265] [a6989586621679681265] -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (GroupBySym0 :: TyFun (TyFun a6989586621679681251 (TyFun a6989586621679681251 Bool -> Type) -> Type) (TyFun [a6989586621679681251] [[a6989586621679681251]] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FindSym0 :: TyFun (TyFun a6989586621679681271 Bool -> Type) (TyFun [a6989586621679681271] (Maybe a6989586621679681271) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (TyFun a6989586621679681267 Bool -> Type) (TyFun [a6989586621679681267] [Nat] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (TyFun a6989586621679681268 Bool -> Type) (TyFun [a6989586621679681268] (Maybe Nat) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FilterSym0 :: TyFun (TyFun a6989586621679681272 Bool -> Type) (TyFun [a6989586621679681272] [a6989586621679681272] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Elem_bySym0 :: TyFun (TyFun a6989586621679681238 (TyFun a6989586621679681238 Bool -> Type) -> Type) (TyFun a6989586621679681238 (TyFun [a6989586621679681238] Bool -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (TyFun a6989586621679681263 Bool -> Type) (TyFun [a6989586621679681263] [a6989586621679681263] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (TyFun a6989586621679681262 Bool -> Type) (TyFun [a6989586621679681262] [a6989586621679681262] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679681277 (TyFun a6989586621679681277 Bool -> Type) -> Type) (TyFun [a6989586621679681277] (TyFun [a6989586621679681277] [a6989586621679681277] -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (DeleteBySym0 :: TyFun (TyFun a6989586621679681278 (TyFun a6989586621679681278 Bool -> Type) -> Type) (TyFun a6989586621679681278 (TyFun [a6989586621679681278] [a6989586621679681278] -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (BreakSym0 :: TyFun (TyFun a6989586621679681260 Bool -> Type) (TyFun [a6989586621679681260] ([a6989586621679681260], [a6989586621679681260]) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (AnySym0 :: TyFun (TyFun a6989586621679681341 Bool -> Type) (TyFun [a6989586621679681341] Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (AllSym0 :: TyFun (TyFun a6989586621679681342 Bool -> Type) (TyFun [a6989586621679681342] Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (NullSym0 :: TyFun [a6989586621679681358] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679681323] (TyFun [a6989586621679681323] Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679681324] (TyFun [a6989586621679681324] Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679681322] (TyFun [a6989586621679681322] Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a6989586621679647548) Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a6989586621679647549) Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (TFHelper_6989586621679544141Sym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (TFHelper_6989586621679544108Sym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (TFHelper_6989586621679544075Sym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (TFHelper_6989586621679544042Sym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544194Scrutinee_6989586621679542855Sym0 :: TyFun k1 (TyFun k1 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544161Scrutinee_6989586621679542853Sym0 :: TyFun k1 (TyFun k1 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679543995Scrutinee_6989586621679542843Sym0 :: TyFun k1 (TyFun k1 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679543985Scrutinee_6989586621679542841Sym0 :: TyFun k1 (TyFun k1 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((>@#@$) :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((>=@#@$) :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((<@#@$) :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((<=@#@$) :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621679681320 (TyFun [a6989586621679681320] Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621679681321 (TyFun [a6989586621679681321] Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((==@#@$) :: TyFun a6989586621679532030 (TyFun a6989586621679532030 Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ((/=@#@$) :: TyFun a6989586621679532030 (TyFun a6989586621679532030 Bool -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Bool_Sym0 :: TyFun a6989586621679529656 (TyFun a6989586621679529656 (TyFun Bool a6989586621679529656 -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690534NubBy'Sym3 :: (TyFun k1 (TyFun k1 Bool -> Type) -> Type) -> k -> [k1] -> TyFun [k1] [k1] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690534NubBy'Sym2 :: (TyFun k1 (TyFun k1 Bool -> Type) -> Type) -> k -> TyFun [k1] ([k1] ~> [k1]) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690534NubBy'Sym1 :: (TyFun k1 (TyFun k1 Bool -> Type) -> Type) -> TyFun k (TyFun [k1] ([k1] ~> [k1]) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690626Scrutinee_6989586621679681939Sym1 :: k1 -> TyFun k Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690534NubBy'Sym0 :: TyFun (TyFun k1 (TyFun k1 Bool -> Type) -> Type) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a6989586621680060960 b6989586621680060961) Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a6989586621680060962 b6989586621680060963) Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690626Scrutinee_6989586621679681939Sym0 :: TyFun k1 (TyFun k Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691043ZsSym0 :: TyFun (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) (TyFun k1 (TyFun [a6989586621679681261] [a6989586621679681261] -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691043YsSym0 :: TyFun (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) (TyFun k1 (TyFun [a6989586621679681261] [a6989586621679681261] -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691043X_6989586621679691044Sym0 :: TyFun (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) (TyFun k1 (TyFun [a6989586621679681261] ([a6989586621679681261], [a6989586621679681261]) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Lambda_6989586621679693422Sym0 :: TyFun (a6989586621679681358 ~> Bool) (TyFun k (TyFun a6989586621679681358 (TyFun [a6989586621679681358] [a6989586621679681358] -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691043ZsSym2 :: (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) -> k1 -> TyFun [a6989586621679681261] [a6989586621679681261] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691043ZsSym1 :: (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) -> TyFun k1 (TyFun [a6989586621679681261] [a6989586621679681261] -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691043YsSym2 :: (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) -> k1 -> TyFun [a6989586621679681261] [a6989586621679681261] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691043YsSym1 :: (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) -> TyFun k1 (TyFun [a6989586621679681261] [a6989586621679681261] -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691043X_6989586621679691044Sym2 :: (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) -> k1 -> TyFun [a6989586621679681261] ([a6989586621679681261], [a6989586621679681261]) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691043X_6989586621679691044Sym1 :: (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) -> TyFun k1 (TyFun [a6989586621679681261] ([a6989586621679681261], [a6989586621679681261]) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Lambda_6989586621679693422Sym3 :: (a6989586621679681358 ~> Bool) -> k -> a6989586621679681358 -> TyFun [a6989586621679681358] [a6989586621679681358] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Lambda_6989586621679693422Sym2 :: (a6989586621679681358 ~> Bool) -> k -> TyFun a6989586621679681358 (TyFun [a6989586621679681358] [a6989586621679681358] -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Lambda_6989586621679693422Sym1 :: (a6989586621679681358 ~> Bool) -> TyFun k (TyFun a6989586621679681358 (TyFun [a6989586621679681358] [a6989586621679681358] -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690558Scrutinee_6989586621679681945Sym4 :: (TyFun k3 (TyFun k3 Bool -> Type) -> Type) -> k1 -> k3 -> k2 -> TyFun [k3] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690558Scrutinee_6989586621679681945Sym3 :: (TyFun k3 (TyFun k3 Bool -> Type) -> Type) -> k1 -> k3 -> TyFun k2 (TyFun [k3] Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690558Scrutinee_6989586621679681945Sym2 :: (TyFun k3 (TyFun k3 Bool -> Type) -> Type) -> k1 -> TyFun k3 (TyFun k2 (TyFun [k3] Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690558Scrutinee_6989586621679681945Sym1 :: (TyFun k3 (TyFun k3 Bool -> Type) -> Type) -> TyFun k1 (TyFun k3 (TyFun k2 (TyFun [k3] Bool -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691889Scrutinee_6989586621679681943Sym3 :: k1 -> k3 -> k2 -> TyFun [k3] Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691889Scrutinee_6989586621679681943Sym2 :: k1 -> k3 -> TyFun k2 (TyFun [k3] Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691889Scrutinee_6989586621679681943Sym1 :: k1 -> TyFun k3 (TyFun k2 (TyFun [k3] Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690818Scrutinee_6989586621679681923Sym2 :: k1 -> k2 -> TyFun k3 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690818Scrutinee_6989586621679681923Sym1 :: k1 -> TyFun k2 (TyFun k3 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690790Scrutinee_6989586621679681925Sym2 :: k1 -> k2 -> TyFun k3 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690790Scrutinee_6989586621679681925Sym1 :: k1 -> TyFun k2 (TyFun k3 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690756Scrutinee_6989586621679681935Sym3 :: k1 -> k1 -> k2 -> TyFun k3 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690756Scrutinee_6989586621679681935Sym2 :: k1 -> k1 -> TyFun k2 (TyFun k3 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690756Scrutinee_6989586621679681935Sym1 :: k1 -> TyFun k1 (TyFun k2 (TyFun k3 Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690599Scrutinee_6989586621679681941Sym2 :: k1 -> k2 -> TyFun k3 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690599Scrutinee_6989586621679681941Sym1 :: k1 -> TyFun k2 (TyFun k3 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690558Scrutinee_6989586621679681945Sym0 :: TyFun (TyFun k3 (TyFun k3 Bool -> Type) -> Type) (TyFun k1 (TyFun k3 (TyFun k2 (TyFun [k3] Bool -> *) -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679691889Scrutinee_6989586621679681943Sym0 :: TyFun k1 (TyFun k3 (TyFun k2 (TyFun [k3] Bool -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690818Scrutinee_6989586621679681923Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690790Scrutinee_6989586621679681925Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690756Scrutinee_6989586621679681935Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679690599Scrutinee_6989586621679681941Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679693426Scrutinee_6989586621679681917Sym0 :: TyFun (k1 ~> Bool) (TyFun k1 (TyFun [a6989586621679681358] (TyFun k Bool -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679693426Scrutinee_6989586621679681917Sym3 :: (k1 ~> Bool) -> k1 -> [a6989586621679681358] -> TyFun k Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679693426Scrutinee_6989586621679681917Sym2 :: (k1 ~> Bool) -> k1 -> TyFun [a6989586621679681358] (TyFun k Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679693426Scrutinee_6989586621679681917Sym1 :: (k1 ~> Bool) -> TyFun k1 (TyFun [a6989586621679681358] (TyFun k Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002365Scrutinee_6989586621680001847Sym4 :: k1 -> k2 -> k2 -> k3 -> TyFun k4 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002365Scrutinee_6989586621680001847Sym3 :: k1 -> k2 -> k2 -> TyFun k3 (TyFun k4 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002365Scrutinee_6989586621680001847Sym2 :: k1 -> k2 -> TyFun k2 (TyFun k3 (TyFun k4 Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002365Scrutinee_6989586621680001847Sym1 :: k1 -> TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002365Scrutinee_6989586621680001847Sym0 :: TyFun k1 (TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> *) -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Lambda_6989586621679692511Sym0 :: TyFun (k3 ~> (TyFun a6989586621679681341 Bool -> Type)) (TyFun k1 (TyFun k2 (TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k3 Bool -> *) -> *) -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Lambda_6989586621679692511Sym5 :: (k3 ~> (TyFun a6989586621679681341 Bool -> Type)) -> k1 -> k2 -> a6989586621679681341 -> [a6989586621679681341] -> TyFun k3 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Lambda_6989586621679692511Sym4 :: (k3 ~> (TyFun a6989586621679681341 Bool -> Type)) -> k1 -> k2 -> a6989586621679681341 -> TyFun [a6989586621679681341] (TyFun k3 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Lambda_6989586621679692511Sym3 :: (k3 ~> (TyFun a6989586621679681341 Bool -> Type)) -> k1 -> k2 -> TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k3 Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Lambda_6989586621679692511Sym2 :: (k3 ~> (TyFun a6989586621679681341 Bool -> Type)) -> k1 -> TyFun k2 (TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k3 Bool -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Lambda_6989586621679692511Sym1 :: (k3 ~> (TyFun a6989586621679681341 Bool -> Type)) -> TyFun k1 (TyFun k2 (TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k3 Bool -> *) -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002138Scrutinee_6989586621680001861Sym5 :: k2 -> k1 -> k2 -> k3 -> k4 -> TyFun k5 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002138Scrutinee_6989586621680001861Sym4 :: k2 -> k1 -> k2 -> k3 -> TyFun k4 (TyFun k5 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002138Scrutinee_6989586621680001861Sym3 :: k2 -> k1 -> k2 -> TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002138Scrutinee_6989586621680001861Sym2 :: k2 -> k1 -> TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002138Scrutinee_6989586621680001861Sym1 :: k2 -> TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680001956Scrutinee_6989586621680001871Sym5 :: k2 -> k1 -> k2 -> k3 -> k4 -> TyFun k5 Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680001956Scrutinee_6989586621680001871Sym4 :: k2 -> k1 -> k2 -> k3 -> TyFun k4 (TyFun k5 Bool -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680001956Scrutinee_6989586621680001871Sym3 :: k2 -> k1 -> k2 -> TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680001956Scrutinee_6989586621680001871Sym2 :: k2 -> k1 -> TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680001956Scrutinee_6989586621680001871Sym1 :: k2 -> TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680002138Scrutinee_6989586621680001861Sym0 :: TyFun k2 (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621680001956Scrutinee_6989586621680001871Sym0 :: TyFun k2 (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
type Rep Bool | |
data Sing (a :: Bool) | |
type DemoteRep Bool | |
data Vector Bool | |
type BitSize Bool Source # | |
data Sing (z :: Bool) | |
type Demote Bool | |
type MaxBound | |
type MaxBound = MaxBound_6989586621679997941Sym0 | |
type MinBound | |
type MinBound = MinBound_6989586621679997939Sym0 | |
data MVector s Bool | |
type FromEnum (a :: Bool) | |
type FromEnum (a :: Bool) = Apply FromEnum_6989586621680021011Sym0 a | |
type ToEnum a | |
type ToEnum a = Apply ToEnum_6989586621680021001Sym0 a | |
type Show_ (arg :: Bool) | |
type Pred (arg :: Bool) | |
type Succ (arg :: Bool) | |
type Unbundled domain Bool Source # | |
type EnumFromTo (arg1 :: Bool) (arg2 :: Bool) | |
type (x :: Bool) /= (y :: Bool) | |
type (a :: Bool) == (b :: Bool) | |
type (arg1 :: Bool) < (arg2 :: Bool) | |
type (arg1 :: Bool) <= (arg2 :: Bool) | |
type (arg1 :: Bool) > (arg2 :: Bool) | |
type (arg1 :: Bool) >= (arg2 :: Bool) | |
type Compare (a1 :: Bool) (a2 :: Bool) | |
type Max (arg1 :: Bool) (arg2 :: Bool) | |
type Min (arg1 :: Bool) (arg2 :: Bool) | |
type ShowList (arg1 :: [Bool]) arg2 | |
type Apply NotSym0 (l :: Bool) | |
type Apply FromEnum_6989586621680021011Sym0 (l :: Bool) | |
type Apply FromEnum_6989586621680021011Sym0 (l :: Bool) = FromEnum_6989586621680021011 l | |
type Apply ToEnum_6989586621680021001Sym0 (l :: Nat) | |
type Apply ToEnum_6989586621680021001Sym0 (l :: Nat) = ToEnum_6989586621680021001 l | |
type EnumFromThenTo (arg1 :: Bool) (arg2 :: Bool) (arg3 :: Bool) | |
type ShowsPrec a1 (a2 :: Bool) a3 | |
type ShowsPrec a1 (a2 :: Bool) a3 = Apply (Apply (Apply ShowsPrec_6989586621679888031Sym0 a1) a2) a3 | |
type Apply ((&&@#@$$) l1 :: TyFun Bool Bool -> *) (l2 :: Bool) | |
type Apply ((||@#@$$) l1 :: TyFun Bool Bool -> *) (l2 :: Bool) | |
type Apply (Compare_6989586621679551605Sym1 l1 :: TyFun Bool Ordering -> *) (l2 :: Bool) | |
type Apply (Let6989586621679543985Scrutinee_6989586621679542841Sym1 l1 :: TyFun k1 Bool -> *) (l2 :: k1) | |
type Apply (TFHelper_6989586621679544141Sym1 l1 :: TyFun a Bool -> *) (l2 :: a) | |
type Apply (TFHelper_6989586621679544108Sym1 l1 :: TyFun a Bool -> *) (l2 :: a) | |
type Apply (TFHelper_6989586621679544075Sym1 l1 :: TyFun a Bool -> *) (l2 :: a) | |
type Apply (TFHelper_6989586621679544042Sym1 l1 :: TyFun a Bool -> *) (l2 :: a) | |
type Apply ((<=@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) | |
type Apply ((>=@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) | |
type Apply ((>@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) | |
type Apply (Let6989586621679544194Scrutinee_6989586621679542855Sym1 l1 :: TyFun k1 Bool -> *) (l2 :: k1) | |
type Apply (Let6989586621679544161Scrutinee_6989586621679542853Sym1 l1 :: TyFun k1 Bool -> *) (l2 :: k1) | |
type Apply (Let6989586621679543995Scrutinee_6989586621679542843Sym1 l1 :: TyFun k1 Bool -> *) (l2 :: k1) | |
type Apply ((<@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) | |
type Apply ((==@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) | |
type Apply ((/=@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) | |
type Apply (Bool_Sym2 l1 l2 :: TyFun Bool a -> *) (l3 :: Bool) | |
type Apply (Let6989586621679690626Scrutinee_6989586621679681939Sym1 l1 :: TyFun k Bool -> *) (l2 :: k) | |
type Apply (Let6989586621679690599Scrutinee_6989586621679681941Sym2 l1 l2 :: TyFun k3 Bool -> *) (l3 :: k3) | |
type Apply (Let6989586621679690790Scrutinee_6989586621679681925Sym2 l1 l2 :: TyFun k3 Bool -> *) (l3 :: k3) | |
type Apply (Let6989586621679690818Scrutinee_6989586621679681923Sym2 l1 l2 :: TyFun k3 Bool -> *) (l3 :: k3) | |
type Apply (Let6989586621679690756Scrutinee_6989586621679681935Sym3 l1 l2 l3 :: TyFun k3 Bool -> *) (l4 :: k3) | |
type Apply (Let6989586621679693426Scrutinee_6989586621679681917Sym3 l1 l2 l3 :: TyFun k Bool -> *) (l4 :: k) | |
type Apply (Let6989586621680002365Scrutinee_6989586621680001847Sym4 l1 l2 l3 l4 :: TyFun k4 Bool -> *) (l5 :: k4) | |
type Apply (Lambda_6989586621679692511Sym5 l1 l2 l3 l4 l5 :: TyFun k1 Bool -> *) (l6 :: k1) | |
type Apply (Let6989586621680001956Scrutinee_6989586621680001871Sym5 l1 l2 l3 l4 l5 :: TyFun k5 Bool -> *) (l6 :: k5) | |
type Apply (Let6989586621680002138Scrutinee_6989586621680001861Sym5 l1 l2 l3 l4 l5 :: TyFun k5 Bool -> *) (l6 :: k5) | |
type Apply (&&@#@$) (l :: Bool) | |
type Apply (&&@#@$) (l :: Bool) = (&&@#@$$) l | |
type Apply (||@#@$) (l :: Bool) | |
type Apply (||@#@$) (l :: Bool) = (||@#@$$) l | |
type Apply Compare_6989586621679551605Sym0 (l :: Bool) | |
type Apply Compare_6989586621679551605Sym0 (l :: Bool) = Compare_6989586621679551605Sym1 l | |
type Apply ShowParenSym0 (l :: Bool) | |
type Apply ShowParenSym0 (l :: Bool) = ShowParenSym1 l | |
type Apply ShowsPrec_6989586621679888031Sym0 (l :: Nat) | |
type Apply ShowsPrec_6989586621679888031Sym0 (l :: Nat) = ShowsPrec_6989586621679888031Sym1 l | |
type Apply (ShowsPrec_6989586621679888031Sym1 l1 :: TyFun Bool (TyFun Symbol Symbol -> Type) -> *) (l2 :: Bool) | |
type Apply (Let6989586621679543985Scrutinee_6989586621679542841Sym0 :: TyFun k1 (TyFun k1 Bool -> *) -> *) (l :: k1) | |
type Apply (TFHelper_6989586621679544141Sym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) (l :: a6989586621679542823) | |
type Apply (TFHelper_6989586621679544108Sym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) (l :: a6989586621679542823) | |
type Apply (TFHelper_6989586621679544075Sym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) (l :: a6989586621679542823) | |
type Apply (TFHelper_6989586621679544042Sym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) (l :: a6989586621679542823) | |
type Apply ((<=@#@$) :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) (l :: a6989586621679542823) | |
type Apply ((>=@#@$) :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) (l :: a6989586621679542823) | |
type Apply ((>@#@$) :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) (l :: a6989586621679542823) | |
type Apply (Let6989586621679544194Scrutinee_6989586621679542855Sym0 :: TyFun k1 (TyFun k1 Bool -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679544161Scrutinee_6989586621679542853Sym0 :: TyFun k1 (TyFun k1 Bool -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679543995Scrutinee_6989586621679542843Sym0 :: TyFun k1 (TyFun k1 Bool -> *) -> *) (l :: k1) | |
type Apply ((<@#@$) :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Bool -> Type) -> *) (l :: a6989586621679542823) | |
type Apply (NotElemSym0 :: TyFun a6989586621679681320 (TyFun [a6989586621679681320] Bool -> Type) -> *) (l :: a6989586621679681320) | |
type Apply (ElemSym0 :: TyFun a6989586621679681321 (TyFun [a6989586621679681321] Bool -> Type) -> *) (l :: a6989586621679681321) | |
type Apply ((==@#@$) :: TyFun a6989586621679532030 (TyFun a6989586621679532030 Bool -> Type) -> *) (l :: a6989586621679532030) | |
type Apply ((/=@#@$) :: TyFun a6989586621679532030 (TyFun a6989586621679532030 Bool -> Type) -> *) (l :: a6989586621679532030) | |
type Apply (Bool_Sym0 :: TyFun a6989586621679529656 (TyFun a6989586621679529656 (TyFun Bool a6989586621679529656 -> Type) -> Type) -> *) (l :: a6989586621679529656) | |
type Apply (Let6989586621679690626Scrutinee_6989586621679681939Sym0 :: TyFun k1 (TyFun k Bool -> *) -> *) (l :: k1) | |
type Apply (Elem_bySym1 l1 :: TyFun a6989586621679681238 (TyFun [a6989586621679681238] Bool -> Type) -> *) (l2 :: a6989586621679681238) | |
type Apply (Bool_Sym1 l1 :: TyFun a6989586621679529656 (TyFun Bool a6989586621679529656 -> Type) -> *) (l2 :: a6989586621679529656) | |
type Apply (Let6989586621679690599Scrutinee_6989586621679681941Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> *) -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679690756Scrutinee_6989586621679681935Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> *) -> *) -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679690790Scrutinee_6989586621679681925Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> *) -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679690818Scrutinee_6989586621679681923Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> *) -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679691889Scrutinee_6989586621679681943Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> *) -> *) -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679690599Scrutinee_6989586621679681941Sym1 l1 :: TyFun k1 (TyFun k3 Bool -> *) -> *) (l2 :: k1) | |
type Apply (Let6989586621679690756Scrutinee_6989586621679681935Sym1 l1 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> *) -> *) -> *) (l2 :: k1) | |
type Apply (Let6989586621679690790Scrutinee_6989586621679681925Sym1 l1 :: TyFun k1 (TyFun k3 Bool -> *) -> *) (l2 :: k1) | |
type Apply (Let6989586621679690818Scrutinee_6989586621679681923Sym1 l1 :: TyFun k1 (TyFun k3 Bool -> *) -> *) (l2 :: k1) | |
type Apply (Let6989586621679690558Scrutinee_6989586621679681945Sym1 l1 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> *) -> *) -> *) -> *) (l2 :: k1) | |
type Apply (Let6989586621679691889Scrutinee_6989586621679681943Sym1 l1 :: TyFun k1 (TyFun k3 (TyFun [k1] Bool -> *) -> *) -> *) (l2 :: k1) | |
type Apply (Let6989586621679693426Scrutinee_6989586621679681917Sym1 l1 :: TyFun k1 (TyFun [a6989586621679681358] (TyFun k Bool -> *) -> *) -> *) (l2 :: k1) | |
type Apply (Let6989586621680002365Scrutinee_6989586621680001847Sym0 :: TyFun k1 (TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> *) -> *) -> *) -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679690756Scrutinee_6989586621679681935Sym2 l1 l2 :: TyFun k2 (TyFun k3 Bool -> *) -> *) (l3 :: k2) | |
type Apply (Let6989586621679690558Scrutinee_6989586621679681945Sym2 l1 l2 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> *) -> *) -> *) (l3 :: k2) | |
type Apply (Let6989586621679691889Scrutinee_6989586621679681943Sym2 l1 l2 :: TyFun k3 (TyFun [k1] Bool -> *) -> *) (l3 :: k3) | |
type Apply (Lambda_6989586621679692511Sym1 l1 :: TyFun k2 (TyFun k3 (TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k1 Bool -> *) -> *) -> *) -> *) -> *) (l2 :: k2) | |
type Apply (Lambda_6989586621679692511Sym1 l1 :: TyFun k2 (TyFun k3 (TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k1 Bool -> *) -> *) -> *) -> *) -> *) (l2 :: k2) = (Lambda_6989586621679692511Sym2 l1 l2 :: TyFun k3 (TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k1 Bool -> *) -> *) -> *) -> *) | |
type Apply (Let6989586621680001956Scrutinee_6989586621680001871Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) -> *) (l :: k1) | |
type Apply (Let6989586621680001956Scrutinee_6989586621680001871Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) -> *) (l :: k1) = (Let6989586621680001956Scrutinee_6989586621680001871Sym1 l :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) | |
type Apply (Let6989586621680002138Scrutinee_6989586621680001861Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) -> *) (l :: k1) | |
type Apply (Let6989586621680002138Scrutinee_6989586621680001861Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) -> *) (l :: k1) = (Let6989586621680002138Scrutinee_6989586621680001861Sym1 l :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) | |
type Apply (Let6989586621680002365Scrutinee_6989586621680001847Sym1 l1 :: TyFun k1 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> *) -> *) -> *) -> *) (l2 :: k1) | |
type Apply (Let6989586621679690558Scrutinee_6989586621679681945Sym3 l1 l2 l3 :: TyFun k3 (TyFun [k2] Bool -> *) -> *) (l4 :: k3) | |
type Apply (Lambda_6989586621679692511Sym2 l1 l2 :: TyFun k3 (TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k1 Bool -> *) -> *) -> *) -> *) (l3 :: k3) | |
type Apply (Let6989586621680001956Scrutinee_6989586621680001871Sym1 l1 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) (l2 :: k1) | |
type Apply (Let6989586621680001956Scrutinee_6989586621680001871Sym1 l1 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) (l2 :: k1) = (Let6989586621680001956Scrutinee_6989586621680001871Sym2 l1 l2 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) | |
type Apply (Let6989586621680002138Scrutinee_6989586621680001861Sym1 l1 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) (l2 :: k1) | |
type Apply (Let6989586621680002138Scrutinee_6989586621680001861Sym1 l1 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) -> *) (l2 :: k1) = (Let6989586621680002138Scrutinee_6989586621680001861Sym2 l1 l2 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) | |
type Apply (Let6989586621680002365Scrutinee_6989586621680001847Sym2 l1 l2 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> *) -> *) -> *) (l3 :: k1) | |
type Apply (Lambda_6989586621679692511Sym3 l1 l2 l3 :: TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k1 Bool -> *) -> *) -> *) (l4 :: a6989586621679681341) | |
type Apply (Let6989586621680001956Scrutinee_6989586621680001871Sym2 l1 l2 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) (l3 :: k2) | |
type Apply (Let6989586621680002138Scrutinee_6989586621680001861Sym2 l1 l2 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) -> *) (l3 :: k2) | |
type Apply (Let6989586621680002365Scrutinee_6989586621680001847Sym3 l1 l2 l3 :: TyFun k3 (TyFun k4 Bool -> *) -> *) (l4 :: k3) | |
type Apply (Let6989586621680001956Scrutinee_6989586621680001871Sym3 l1 l2 l3 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) (l4 :: k3) | |
type Apply (Let6989586621680002138Scrutinee_6989586621680001861Sym3 l1 l2 l3 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> *) -> *) -> *) (l4 :: k3) | |
type Apply (Let6989586621680001956Scrutinee_6989586621680001871Sym4 l1 l2 l3 l4 :: TyFun k4 (TyFun k5 Bool -> *) -> *) (l5 :: k4) | |
type Apply (Let6989586621680002138Scrutinee_6989586621680001861Sym4 l1 l2 l3 l4 :: TyFun k4 (TyFun k5 Bool -> *) -> *) (l5 :: k4) | |
type Apply AndSym0 (l :: [Bool]) | |
type Apply AndSym0 (l :: [Bool]) = And l | |
type Apply OrSym0 (l :: [Bool]) | |
type Apply OrSym0 (l :: [Bool]) = Or l | |
type Apply (NullSym0 :: TyFun [a] Bool -> *) (l :: [a]) | |
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> *) (l :: Maybe a) | |
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> *) (l :: Maybe a) | |
type Apply (NotElemSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) | |
type Apply (ElemSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) | |
type Apply (IsPrefixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) | |
type Apply (AnySym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) | |
type Apply (IsInfixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) | |
type Apply (AllSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) | |
type Apply (IsSuffixOfSym1 l1 :: TyFun [a] Bool -> *) (l2 :: [a]) | |
type Apply (Elem_bySym2 l1 l2 :: TyFun [a] Bool -> *) (l3 :: [a]) | |
type Apply (Let6989586621679691889Scrutinee_6989586621679681943Sym3 l1 l2 l3 :: TyFun [k1] Bool -> *) (l4 :: [k1]) | |
type Apply (Let6989586621679690558Scrutinee_6989586621679681945Sym4 l1 l2 l3 l4 :: TyFun [k2] Bool -> *) (l5 :: [k2]) | |
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679681324] (TyFun [a6989586621679681324] Bool -> Type) -> *) (l :: [a6989586621679681324]) | |
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679681322] (TyFun [a6989586621679681322] Bool -> Type) -> *) (l :: [a6989586621679681322]) | |
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679681323] (TyFun [a6989586621679681323] Bool -> Type) -> *) (l :: [a6989586621679681323]) | |
type Apply (Let6989586621679693426Scrutinee_6989586621679681917Sym2 l1 l2 :: TyFun [a6989586621679681358] (TyFun k Bool -> *) -> *) (l3 :: [a6989586621679681358]) | |
type Apply (Lambda_6989586621679692511Sym4 l1 l2 l3 l4 :: TyFun [a6989586621679681341] (TyFun k1 Bool -> *) -> *) (l5 :: [a6989586621679681341]) | |
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> *) (l :: Either a b) | |
type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> *) (l :: Either a b) | |
type Apply (Elem_bySym0 :: TyFun (TyFun a6989586621679681238 (TyFun a6989586621679681238 Bool -> Type) -> Type) (TyFun a6989586621679681238 (TyFun [a6989586621679681238] Bool -> Type) -> Type) -> *) (l :: TyFun a6989586621679681238 (TyFun a6989586621679681238 Bool -> Type) -> Type) | |
type Apply (NubBySym0 :: TyFun (TyFun a6989586621679681239 (TyFun a6989586621679681239 Bool -> Type) -> Type) (TyFun [a6989586621679681239] [a6989586621679681239] -> Type) -> *) (l :: TyFun a6989586621679681239 (TyFun a6989586621679681239 Bool -> Type) -> Type) | |
type Apply (SelectSym0 :: TyFun (TyFun a6989586621679681247 Bool -> Type) (TyFun a6989586621679681247 (TyFun ([a6989586621679681247], [a6989586621679681247]) ([a6989586621679681247], [a6989586621679681247]) -> Type) -> Type) -> *) (l :: TyFun a6989586621679681247 Bool -> Type) | |
type Apply (PartitionSym0 :: TyFun (TyFun a6989586621679681248 Bool -> Type) (TyFun [a6989586621679681248] ([a6989586621679681248], [a6989586621679681248]) -> Type) -> *) (l :: TyFun a6989586621679681248 Bool -> Type) | |
type Apply (BreakSym0 :: TyFun (TyFun a6989586621679681260 Bool -> Type) (TyFun [a6989586621679681260] ([a6989586621679681260], [a6989586621679681260]) -> Type) -> *) (l :: TyFun a6989586621679681260 Bool -> Type) | |
type Apply (Let6989586621679690886ZsSym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) (l :: TyFun k Bool -> Type) | |
type Apply (Let6989586621679690886YsSym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) (l :: TyFun k Bool -> Type) | |
type Apply (Let6989586621679690886X_6989586621679690887Sym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] ([k], [k]) -> *) -> *) -> *) (l :: TyFun k Bool -> Type) | |
type Apply (SpanSym0 :: TyFun (TyFun a6989586621679681261 Bool -> Type) (TyFun [a6989586621679681261] ([a6989586621679681261], [a6989586621679681261]) -> Type) -> *) (l :: TyFun a6989586621679681261 Bool -> Type) | |
type Apply (Let6989586621679690979ZsSym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) (l :: TyFun k Bool -> Type) | |
type Apply (Let6989586621679690979YsSym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] [k] -> *) -> *) -> *) (l :: TyFun k Bool -> Type) | |
type Apply (Let6989586621679690979X_6989586621679690980Sym0 :: TyFun (TyFun k Bool -> Type) (TyFun k (TyFun [k] ([k], [k]) -> *) -> *) -> *) (l :: TyFun k Bool -> Type) | |
type Apply (GroupBySym0 :: TyFun (TyFun a6989586621679681251 (TyFun a6989586621679681251 Bool -> Type) -> Type) (TyFun [a6989586621679681251] [[a6989586621679681251]] -> Type) -> *) (l :: TyFun a6989586621679681251 (TyFun a6989586621679681251 Bool -> Type) -> Type) | |
type Apply (DropWhileSym0 :: TyFun (TyFun a6989586621679681263 Bool -> Type) (TyFun [a6989586621679681263] [a6989586621679681263] -> Type) -> *) (l :: TyFun a6989586621679681263 Bool -> Type) | |
type Apply (TakeWhileSym0 :: TyFun (TyFun a6989586621679681264 Bool -> Type) (TyFun [a6989586621679681264] [a6989586621679681264] -> Type) -> *) (l :: TyFun a6989586621679681264 Bool -> Type) | |
type Apply (FilterSym0 :: TyFun (TyFun a6989586621679681272 Bool -> Type) (TyFun [a6989586621679681272] [a6989586621679681272] -> Type) -> *) (l :: TyFun a6989586621679681272 Bool -> Type) | |
type Apply (FindSym0 :: TyFun (TyFun a6989586621679681271 Bool -> Type) (TyFun [a6989586621679681271] (Maybe a6989586621679681271) -> Type) -> *) (l :: TyFun a6989586621679681271 Bool -> Type) | |
type Apply (DeleteBySym0 :: TyFun (TyFun a6989586621679681278 (TyFun a6989586621679681278 Bool -> Type) -> Type) (TyFun a6989586621679681278 (TyFun [a6989586621679681278] [a6989586621679681278] -> Type) -> Type) -> *) (l :: TyFun a6989586621679681278 (TyFun a6989586621679681278 Bool -> Type) -> Type) | |
type Apply (DeleteBySym0 :: TyFun (TyFun a6989586621679681278 (TyFun a6989586621679681278 Bool -> Type) -> Type) (TyFun a6989586621679681278 (TyFun [a6989586621679681278] [a6989586621679681278] -> Type) -> Type) -> *) (l :: TyFun a6989586621679681278 (TyFun a6989586621679681278 Bool -> Type) -> Type) = DeleteBySym1 l | |
type Apply (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679681277 (TyFun a6989586621679681277 Bool -> Type) -> Type) (TyFun [a6989586621679681277] (TyFun [a6989586621679681277] [a6989586621679681277] -> Type) -> Type) -> *) (l :: TyFun a6989586621679681277 (TyFun a6989586621679681277 Bool -> Type) -> Type) | |
type Apply (DeleteFirstsBySym0 :: TyFun (TyFun a6989586621679681277 (TyFun a6989586621679681277 Bool -> Type) -> Type) (TyFun [a6989586621679681277] (TyFun [a6989586621679681277] [a6989586621679681277] -> Type) -> Type) -> *) (l :: TyFun a6989586621679681277 (TyFun a6989586621679681277 Bool -> Type) -> Type) = DeleteFirstsBySym1 l | |
type Apply (UnionBySym0 :: TyFun (TyFun a6989586621679681237 (TyFun a6989586621679681237 Bool -> Type) -> Type) (TyFun [a6989586621679681237] (TyFun [a6989586621679681237] [a6989586621679681237] -> Type) -> Type) -> *) (l :: TyFun a6989586621679681237 (TyFun a6989586621679681237 Bool -> Type) -> Type) | |
type Apply (UnionBySym0 :: TyFun (TyFun a6989586621679681237 (TyFun a6989586621679681237 Bool -> Type) -> Type) (TyFun [a6989586621679681237] (TyFun [a6989586621679681237] [a6989586621679681237] -> Type) -> Type) -> *) (l :: TyFun a6989586621679681237 (TyFun a6989586621679681237 Bool -> Type) -> Type) = UnionBySym1 l | |
type Apply (FindIndicesSym0 :: TyFun (TyFun a6989586621679681267 Bool -> Type) (TyFun [a6989586621679681267] [Nat] -> Type) -> *) (l :: TyFun a6989586621679681267 Bool -> Type) | |
type Apply (FindIndexSym0 :: TyFun (TyFun a6989586621679681268 Bool -> Type) (TyFun [a6989586621679681268] (Maybe Nat) -> Type) -> *) (l :: TyFun a6989586621679681268 Bool -> Type) | |
type Apply (AnySym0 :: TyFun (TyFun a6989586621679681341 Bool -> Type) (TyFun [a6989586621679681341] Bool -> Type) -> *) (l :: TyFun a6989586621679681341 Bool -> Type) | |
type Apply (IntersectBySym0 :: TyFun (TyFun a6989586621679681265 (TyFun a6989586621679681265 Bool -> Type) -> Type) (TyFun [a6989586621679681265] (TyFun [a6989586621679681265] [a6989586621679681265] -> Type) -> Type) -> *) (l :: TyFun a6989586621679681265 (TyFun a6989586621679681265 Bool -> Type) -> Type) | |
type Apply (IntersectBySym0 :: TyFun (TyFun a6989586621679681265 (TyFun a6989586621679681265 Bool -> Type) -> Type) (TyFun [a6989586621679681265] (TyFun [a6989586621679681265] [a6989586621679681265] -> Type) -> Type) -> *) (l :: TyFun a6989586621679681265 (TyFun a6989586621679681265 Bool -> Type) -> Type) = IntersectBySym1 l | |
type Apply (AllSym0 :: TyFun (TyFun a6989586621679681342 Bool -> Type) (TyFun [a6989586621679681342] Bool -> Type) -> *) (l :: TyFun a6989586621679681342 Bool -> Type) | |
type Apply (DropWhileEndSym0 :: TyFun (TyFun a6989586621679681262 Bool -> Type) (TyFun [a6989586621679681262] [a6989586621679681262] -> Type) -> *) (l :: TyFun a6989586621679681262 Bool -> Type) | |
type Apply (Let6989586621679690534NubBy'Sym0 :: TyFun (TyFun k1 (TyFun k1 Bool -> Type) -> Type) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> *) -> *) -> *) (l :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) | |
type Apply (Let6989586621679691043ZsSym0 :: TyFun (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) (TyFun k1 (TyFun [a6989586621679681261] [a6989586621679681261] -> *) -> *) -> *) (l :: k1 ~> (TyFun a6989586621679681261 Bool -> Type)) | |
type Apply (Let6989586621679691043YsSym0 :: TyFun (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) (TyFun k1 (TyFun [a6989586621679681261] [a6989586621679681261] -> *) -> *) -> *) (l :: k1 ~> (TyFun a6989586621679681261 Bool -> Type)) | |
type Apply (Let6989586621679691043X_6989586621679691044Sym0 :: TyFun (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) (TyFun k1 (TyFun [a6989586621679681261] ([a6989586621679681261], [a6989586621679681261]) -> *) -> *) -> *) (l :: k1 ~> (TyFun a6989586621679681261 Bool -> Type)) | |
type Apply (Let6989586621679691043X_6989586621679691044Sym0 :: TyFun (k1 ~> (TyFun a6989586621679681261 Bool -> Type)) (TyFun k1 (TyFun [a6989586621679681261] ([a6989586621679681261], [a6989586621679681261]) -> *) -> *) -> *) (l :: k1 ~> (TyFun a6989586621679681261 Bool -> Type)) = Let6989586621679691043X_6989586621679691044Sym1 l | |
type Apply (Lambda_6989586621679693422Sym0 :: TyFun (a6989586621679681358 ~> Bool) (TyFun k (TyFun a6989586621679681358 (TyFun [a6989586621679681358] [a6989586621679681358] -> *) -> *) -> *) -> *) (l :: a6989586621679681358 ~> Bool) | |
type Apply (Lambda_6989586621679693422Sym0 :: TyFun (a6989586621679681358 ~> Bool) (TyFun k (TyFun a6989586621679681358 (TyFun [a6989586621679681358] [a6989586621679681358] -> *) -> *) -> *) -> *) (l :: a6989586621679681358 ~> Bool) = (Lambda_6989586621679693422Sym1 l :: TyFun k (TyFun a6989586621679681358 (TyFun [a6989586621679681358] [a6989586621679681358] -> *) -> *) -> *) | |
type Apply (Let6989586621679690558Scrutinee_6989586621679681945Sym0 :: TyFun (TyFun k1 (TyFun k1 Bool -> Type) -> Type) (TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> *) -> *) -> *) -> *) -> *) (l :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) | |
type Apply (Let6989586621679690558Scrutinee_6989586621679681945Sym0 :: TyFun (TyFun k1 (TyFun k1 Bool -> Type) -> Type) (TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> *) -> *) -> *) -> *) -> *) (l :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) = (Let6989586621679690558Scrutinee_6989586621679681945Sym1 l :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> *) -> *) -> *) -> *) | |
type Apply (Let6989586621679693426Scrutinee_6989586621679681917Sym0 :: TyFun (k1 ~> Bool) (TyFun k1 (TyFun [a6989586621679681358] (TyFun k Bool -> *) -> *) -> *) -> *) (l :: k1 ~> Bool) | |
type Apply (Let6989586621679693426Scrutinee_6989586621679681917Sym0 :: TyFun (k1 ~> Bool) (TyFun k1 (TyFun [a6989586621679681358] (TyFun k Bool -> *) -> *) -> *) -> *) (l :: k1 ~> Bool) = (Let6989586621679693426Scrutinee_6989586621679681917Sym1 l :: TyFun k1 (TyFun [a6989586621679681358] (TyFun k Bool -> *) -> *) -> *) | |
type Apply (Lambda_6989586621679692511Sym0 :: TyFun (k1 ~> (TyFun a6989586621679681341 Bool -> Type)) (TyFun k2 (TyFun k3 (TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k1 Bool -> *) -> *) -> *) -> *) -> *) -> *) (l :: k1 ~> (TyFun a6989586621679681341 Bool -> Type)) | |
type Apply (Lambda_6989586621679692511Sym0 :: TyFun (k1 ~> (TyFun a6989586621679681341 Bool -> Type)) (TyFun k2 (TyFun k3 (TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k1 Bool -> *) -> *) -> *) -> *) -> *) -> *) (l :: k1 ~> (TyFun a6989586621679681341 Bool -> Type)) = (Lambda_6989586621679692511Sym1 l :: TyFun k2 (TyFun k3 (TyFun a6989586621679681341 (TyFun [a6989586621679681341] (TyFun k1 Bool -> *) -> *) -> *) -> *) -> *) |
The character type Char
is an enumeration whose values represent
Unicode (or equivalently ISO/IEC 10646) code points (i.e. characters, see
http://www.unicode.org/ for details). This set extends the ISO 8859-1
(Latin-1) character set (the first 256 characters), which is itself an extension
of the ASCII character set (the first 128 characters). A character literal in
Haskell has type Char
.
To convert a Char
to or from the corresponding Int
value defined
by Unicode, use toEnum
and fromEnum
from the
Enum
class respectively (or equivalently ord
and chr
).
Instances
Bounded Char | Since: 2.1 |
Enum Char | Since: 2.1 |
Eq Char | |
Data Char | Since: 4.0.0.0 |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Char -> c Char # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char # dataTypeOf :: Char -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Char) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) # gmapT :: (forall b. Data b => b -> b) -> Char -> Char # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r # gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char # | |
Ord Char | |
Read Char | Since: 2.1 |
Show Char | Since: 2.1 |
Ix Char | Since: 2.1 |
Lift Char | |
Storable Char | Since: 2.1 |
NFData Char | |
ErrorList Char | |
ShowX Char Source # | |
ShowX String Source # | |
Arbitrary Char | |
CoArbitrary Char | |
Methods coarbitrary :: Char -> Gen b -> Gen b | |
Unbox Char | |
Prim Char | |
Methods alignment# :: Char -> Int# indexByteArray# :: ByteArray# -> Int# -> Char readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Char#) writeByteArray# :: MutableByteArray# s -> Int# -> Char -> State# s -> State# s setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Char -> State# s -> State# s indexOffAddr# :: Addr# -> Int# -> Char readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Char#) writeOffAddr# :: Addr# -> Int# -> Char -> State# s -> State# s setOffAddr# :: Addr# -> Int# -> Int# -> Char -> State# s -> State# s | |
Vector Vector Char | |
Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Char -> m (Vector Char) basicUnsafeThaw :: PrimMonad m => Vector Char -> m (Mutable Vector (PrimState m) Char) basicLength :: Vector Char -> Int basicUnsafeSlice :: Int -> Int -> Vector Char -> Vector Char basicUnsafeIndexM :: Monad m => Vector Char -> Int -> m Char basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Char -> Vector Char -> m () | |
MVector MVector Char | |
Methods basicLength :: MVector s Char -> Int basicUnsafeSlice :: Int -> Int -> MVector s Char -> MVector s Char basicOverlaps :: MVector s Char -> MVector s Char -> Bool basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Char) basicInitialize :: PrimMonad m => MVector (PrimState m) Char -> m () basicUnsafeReplicate :: PrimMonad m => Int -> Char -> m (MVector (PrimState m) Char) basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Char -> Int -> m Char basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Char -> Int -> Char -> m () basicClear :: PrimMonad m => MVector (PrimState m) Char -> m () basicSet :: PrimMonad m => MVector (PrimState m) Char -> Char -> m () basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Char -> MVector (PrimState m) Char -> m () basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Char -> MVector (PrimState m) Char -> m () basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Char -> Int -> m (MVector (PrimState m) Char) | |
KnownSymbol n => Reifies (n :: Symbol) String | |
Cons Text Text Char Char | |
Cons Text Text Char Char | |
Snoc Text Text Char Char | |
Snoc Text Text Char Char | |
() :=> (Bounded Char) | |
() :=> (Enum Char) | |
() :=> (Ord Char) | |
() :=> (Read Char) | |
() :=> (Show Char) | |
Generic1 (URec Char :: k -> *) | |
Functor (URec Char :: * -> *) | |
Foldable (URec Char :: * -> *) | |
Methods fold :: Monoid m => URec Char m -> m # foldMap :: Monoid m => (a -> m) -> URec Char a -> m # foldr :: (a -> b -> b) -> b -> URec Char a -> b # foldr' :: (a -> b -> b) -> b -> URec Char a -> b # foldl :: (b -> a -> b) -> b -> URec Char a -> b # foldl' :: (b -> a -> b) -> b -> URec Char a -> b # foldr1 :: (a -> a -> a) -> URec Char a -> a # foldl1 :: (a -> a -> a) -> URec Char a -> a # toList :: URec Char a -> [a] # length :: URec Char a -> Int # elem :: Eq a => a -> URec Char a -> Bool # maximum :: Ord a => URec Char a -> a # minimum :: Ord a => URec Char a -> a # | |
Traversable (URec Char :: * -> *) | |
Eq (URec Char p) | |
Ord (URec Char p) | |
Show (URec Char p) | |
Generic (URec Char p) | |
data Vector Char | |
data URec Char (p :: k) | Used for marking occurrences of Since: 4.9.0.0 |
data MVector s Char | |
type Rep1 (URec Char :: k -> *) | |
type Rep (URec Char p) | |
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Instances
Eq Double | |
Floating Double | Since: 2.1 |
Data Double | Since: 4.0.0.0 |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double # toConstr :: Double -> Constr # dataTypeOf :: Double -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) # gmapT :: (forall b. Data b => b -> b) -> Double -> Double # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r # gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double # | |
Ord Double | |
Read Double | Since: 2.1 |
RealFloat Double | Since: 2.1 |
Methods floatRadix :: Double -> Integer # floatDigits :: Double -> Int # floatRange :: Double -> (Int, Int) # decodeFloat :: Double -> (Integer, Int) # encodeFloat :: Integer -> Int -> Double # significand :: Double -> Double # scaleFloat :: Int -> Double -> Double # isInfinite :: Double -> Bool # isDenormalized :: Double -> Bool # isNegativeZero :: Double -> Bool # | |
Lift Double | |
Storable Double | Since: 2.1 |
NFData Double | |
ShowX Double Source # | |
Default Double | |
Arbitrary Double | |
CoArbitrary Double | |
Methods coarbitrary :: Double -> Gen b -> Gen b | |
Unbox Double | |
Prim Double | |
Methods alignment# :: Double -> Int# indexByteArray# :: ByteArray# -> Int# -> Double readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Double#) writeByteArray# :: MutableByteArray# s -> Int# -> Double -> State# s -> State# s setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Double -> State# s -> State# s indexOffAddr# :: Addr# -> Int# -> Double readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Double#) writeOffAddr# :: Addr# -> Int# -> Double -> State# s -> State# s setOffAddr# :: Addr# -> Int# -> Int# -> Double -> State# s -> State# s | |
BitPack Double Source # | |
Bundle Double Source # | |
Vector Vector Double | |
Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Double -> m (Vector Double) basicUnsafeThaw :: PrimMonad m => Vector Double -> m (Mutable Vector (PrimState m) Double) basicLength :: Vector Double -> Int basicUnsafeSlice :: Int -> Int -> Vector Double -> Vector Double basicUnsafeIndexM :: Monad m => Vector Double -> Int -> m Double basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Double -> Vector Double -> m () | |
MVector MVector Double | |
Methods basicLength :: MVector s Double -> Int basicUnsafeSlice :: Int -> Int -> MVector s Double -> MVector s Double basicOverlaps :: MVector s Double -> MVector s Double -> Bool basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Double) basicInitialize :: PrimMonad m => MVector (PrimState m) Double -> m () basicUnsafeReplicate :: PrimMonad m => Int -> Double -> m (MVector (PrimState m) Double) basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Double -> Int -> m Double basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Double -> Int -> Double -> m () basicClear :: PrimMonad m => MVector (PrimState m) Double -> m () basicSet :: PrimMonad m => MVector (PrimState m) Double -> Double -> m () basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Double -> MVector (PrimState m) Double -> m () basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Double -> MVector (PrimState m) Double -> m () basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Double -> Int -> m (MVector (PrimState m) Double) | |
() :=> (Enum Double) | |
() :=> (Eq Double) | |
() :=> (Floating Double) | |
() :=> (Fractional Double) | |
Methods ins :: () :- Fractional Double | |
() :=> (Num Double) | |
() :=> (Ord Double) | |
() :=> (Real Double) | |
() :=> (RealFloat Double) | |
() :=> (RealFrac Double) | |
Generic1 (URec Double :: k -> *) | |
Functor (URec Double :: * -> *) | |
Foldable (URec Double :: * -> *) | |
Methods fold :: Monoid m => URec Double m -> m # foldMap :: Monoid m => (a -> m) -> URec Double a -> m # foldr :: (a -> b -> b) -> b -> URec Double a -> b # foldr' :: (a -> b -> b) -> b -> URec Double a -> b # foldl :: (b -> a -> b) -> b -> URec Double a -> b # foldl' :: (b -> a -> b) -> b -> URec Double a -> b # foldr1 :: (a -> a -> a) -> URec Double a -> a # foldl1 :: (a -> a -> a) -> URec Double a -> a # toList :: URec Double a -> [a] # null :: URec Double a -> Bool # length :: URec Double a -> Int # elem :: Eq a => a -> URec Double a -> Bool # maximum :: Ord a => URec Double a -> a # minimum :: Ord a => URec Double a -> a # | |
Traversable (URec Double :: * -> *) | |
Eq (URec Double p) | |
Ord (URec Double p) | |
Methods compare :: URec Double p -> URec Double p -> Ordering # (<) :: URec Double p -> URec Double p -> Bool # (<=) :: URec Double p -> URec Double p -> Bool # (>) :: URec Double p -> URec Double p -> Bool # (>=) :: URec Double p -> URec Double p -> Bool # | |
Show (URec Double p) | |
Generic (URec Double p) | |
data Vector Double | |
type BitSize Double Source # | |
data URec Double (p :: k) | Used for marking occurrences of Since: 4.9.0.0 |
data MVector s Double | |
type Unbundled domain Double Source # | |
type Rep1 (URec Double :: k -> *) | |
type Rep (URec Double p) | |
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Instances
Eq Float | |
Floating Float | Since: 2.1 |
Data Float | Since: 4.0.0.0 |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Float -> c Float # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float # dataTypeOf :: Float -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Float) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) # gmapT :: (forall b. Data b => b -> b) -> Float -> Float # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r # gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float # | |
Ord Float | |
Read Float | Since: 2.1 |
RealFloat Float | Since: 2.1 |
Methods floatRadix :: Float -> Integer # floatDigits :: Float -> Int # floatRange :: Float -> (Int, Int) # decodeFloat :: Float -> (Integer, Int) # encodeFloat :: Integer -> Int -> Float # significand :: Float -> Float # scaleFloat :: Int -> Float -> Float # isInfinite :: Float -> Bool # isDenormalized :: Float -> Bool # isNegativeZero :: Float -> Bool # | |
Lift Float | |
Storable Float | Since: 2.1 |
NFData Float | |
ShowX Float Source # | |
Default Float | |
Arbitrary Float | |
CoArbitrary Float | |
Methods coarbitrary :: Float -> Gen b -> Gen b | |
Unbox Float | |
Prim Float | |
Methods alignment# :: Float -> Int# indexByteArray# :: ByteArray# -> Int# -> Float readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Float#) writeByteArray# :: MutableByteArray# s -> Int# -> Float -> State# s -> State# s setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Float -> State# s -> State# s indexOffAddr# :: Addr# -> Int# -> Float readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Float#) writeOffAddr# :: Addr# -> Int# -> Float -> State# s -> State# s setOffAddr# :: Addr# -> Int# -> Int# -> Float -> State# s -> State# s | |
BitPack Float Source # | |
Bundle Float Source # | |
Vector Vector Float | |
Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Float -> m (Vector Float) basicUnsafeThaw :: PrimMonad m => Vector Float -> m (Mutable Vector (PrimState m) Float) basicLength :: Vector Float -> Int basicUnsafeSlice :: Int -> Int -> Vector Float -> Vector Float basicUnsafeIndexM :: Monad m => Vector Float -> Int -> m Float basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Float -> Vector Float -> m () | |
MVector MVector Float | |
Methods basicLength :: MVector s Float -> Int basicUnsafeSlice :: Int -> Int -> MVector s Float -> MVector s Float basicOverlaps :: MVector s Float -> MVector s Float -> Bool basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Float) basicInitialize :: PrimMonad m => MVector (PrimState m) Float -> m () basicUnsafeReplicate :: PrimMonad m => Int -> Float -> m (MVector (PrimState m) Float) basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Float -> Int -> m Float basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Float -> Int -> Float -> m () basicClear :: PrimMonad m => MVector (PrimState m) Float -> m () basicSet :: PrimMonad m => MVector (PrimState m) Float -> Float -> m () basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Float -> MVector (PrimState m) Float -> m () basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Float -> MVector (PrimState m) Float -> m () basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Float -> Int -> m (MVector (PrimState m) Float) | |
() :=> (Enum Float) | |
() :=> (Eq Float) | |
() :=> (Floating Float) | |
() :=> (Fractional Float) | |
Methods ins :: () :- Fractional Float | |
() :=> (Num Float) | |
() :=> (Ord Float) | |
() :=> (Real Float) | |
() :=> (RealFloat Float) | |
() :=> (RealFrac Float) | |
Generic1 (URec Float :: k -> *) | |
Functor (URec Float :: * -> *) | |
Foldable (URec Float :: * -> *) | |
Methods fold :: Monoid m => URec Float m -> m # foldMap :: Monoid m => (a -> m) -> URec Float a -> m # foldr :: (a -> b -> b) -> b -> URec Float a -> b # foldr' :: (a -> b -> b) -> b -> URec Float a -> b # foldl :: (b -> a -> b) -> b -> URec Float a -> b # foldl' :: (b -> a -> b) -> b -> URec Float a -> b # foldr1 :: (a -> a -> a) -> URec Float a -> a # foldl1 :: (a -> a -> a) -> URec Float a -> a # toList :: URec Float a -> [a] # null :: URec Float a -> Bool # length :: URec Float a -> Int # elem :: Eq a => a -> URec Float a -> Bool # maximum :: Ord a => URec Float a -> a # minimum :: Ord a => URec Float a -> a # | |
Traversable (URec Float :: * -> *) | |
Eq (URec Float p) | |
Ord (URec Float p) | |
Show (URec Float p) | |
Generic (URec Float p) | |
data Vector Float | |
type BitSize Float Source # | |
data URec Float (p :: k) | Used for marking occurrences of Since: 4.9.0.0 |
data MVector s Float | |
type Unbundled domain Float Source # | |
type Rep1 (URec Float :: k -> *) | |
type Rep (URec Float p) | |
A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]
.
The exact range for a given implementation can be determined by using
minBound
and maxBound
from the Bounded
class.
Instances
Bounded Int | Since: 2.1 |
Enum Int | Since: 2.1 |
Eq Int | |
Integral Int | Since: 2.0.1 |
Data Int | Since: 4.0.0.0 |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int -> c Int # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int # dataTypeOf :: Int -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) # gmapT :: (forall b. Data b => b -> b) -> Int -> Int # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r # gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int # | |
Num Int | Since: 2.1 |
Ord Int | |
Read Int | Since: 2.1 |
Real Int | Since: 2.0.1 |
Methods toRational :: Int -> Rational # | |
Show Int | Since: 2.1 |
Ix Int | Since: 2.1 |
Lift Int | |
Storable Int | Since: 2.1 |
Bits Int | Since: 2.1 |
FiniteBits Int | Since: 4.6.0.0 |
Methods finiteBitSize :: Int -> Int # countLeadingZeros :: Int -> Int # countTrailingZeros :: Int -> Int # | |
NFData Int | |
ShowX Int Source # | |
Default Int | |
Arbitrary Int | |
CoArbitrary Int | |
Methods coarbitrary :: Int -> Gen b -> Gen b | |
Unbox Int | |
Prim Int | |
Methods alignment# :: Int -> Int# indexByteArray# :: ByteArray# -> Int# -> Int readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int#) writeByteArray# :: MutableByteArray# s -> Int# -> Int -> State# s -> State# s setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int -> State# s -> State# s indexOffAddr# :: Addr# -> Int# -> Int readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int#) writeOffAddr# :: Addr# -> Int# -> Int -> State# s -> State# s setOffAddr# :: Addr# -> Int# -> Int# -> Int -> State# s -> State# s | |
BitPack Int Source # | |
Bundle Int Source # | |
FoldableWithIndex Int [] | |
FoldableWithIndex Int ZipList | |
Methods ifoldMap :: Monoid m => (Int -> a -> m) -> ZipList a -> m ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> ZipList a -> f (ZipList a) ifoldr :: (Int -> a -> b -> b) -> b -> ZipList a -> b ifoldl :: (Int -> b -> a -> b) -> b -> ZipList a -> b | |
FoldableWithIndex Int NonEmpty | |
Methods ifoldMap :: Monoid m => (Int -> a -> m) -> NonEmpty a -> m ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> NonEmpty a -> f (NonEmpty a) ifoldr :: (Int -> a -> b -> b) -> b -> NonEmpty a -> b ifoldl :: (Int -> b -> a -> b) -> b -> NonEmpty a -> b | |
FoldableWithIndex Int IntMap | |
Methods ifoldMap :: Monoid m => (Int -> a -> m) -> IntMap a -> m ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> IntMap a -> f (IntMap a) ifoldr :: (Int -> a -> b -> b) -> b -> IntMap a -> b ifoldl :: (Int -> b -> a -> b) -> b -> IntMap a -> b | |
FoldableWithIndex Int Seq | |
Methods ifoldMap :: Monoid m => (Int -> a -> m) -> Seq a -> m ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> Seq a -> f (Seq a) ifoldr :: (Int -> a -> b -> b) -> b -> Seq a -> b ifoldl :: (Int -> b -> a -> b) -> b -> Seq a -> b | |
FoldableWithIndex Int Vector | |
Methods ifoldMap :: Monoid m => (Int -> a -> m) -> Vector a -> m ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> Vector a -> f (Vector a) ifoldr :: (Int -> a -> b -> b) -> b -> Vector a -> b ifoldl :: (Int -> b -> a -> b) -> b -> Vector a -> b | |
FunctorWithIndex Int [] | |
FunctorWithIndex Int ZipList | |
FunctorWithIndex Int NonEmpty | |
FunctorWithIndex Int IntMap | |
FunctorWithIndex Int Seq | |
FunctorWithIndex Int Vector | |
TraversableWithIndex Int [] | |
Methods itraverse :: Applicative f => (Int -> a -> f b) -> [a] -> f [b] itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> [a] -> f [b] | |
TraversableWithIndex Int ZipList | |
Methods itraverse :: Applicative f => (Int -> a -> f b) -> ZipList a -> f (ZipList b) itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> ZipList a -> f (ZipList b) | |
TraversableWithIndex Int NonEmpty | |
Methods itraverse :: Applicative f => (Int -> a -> f b) -> NonEmpty a -> f (NonEmpty b) itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> NonEmpty a -> f (NonEmpty b) | |
TraversableWithIndex Int IntMap | |
Methods itraverse :: Applicative f => (Int -> a -> f b) -> IntMap a -> f (IntMap b) itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> IntMap a -> f (IntMap b) | |
TraversableWithIndex Int Seq | |
Methods itraverse :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b) itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> Seq a -> f (Seq b) | |
TraversableWithIndex Int Vector | |
Methods itraverse :: Applicative f => (Int -> a -> f b) -> Vector a -> f (Vector b) itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> Vector a -> f (Vector b) | |
TraverseMax Int IntMap | |
Methods traverseMax :: (Indexable Int p, Applicative f) => p v (f v) -> IntMap v -> f (IntMap v) | |
TraverseMin Int IntMap | |
Methods traverseMin :: (Indexable Int p, Applicative f) => p v (f v) -> IntMap v -> f (IntMap v) | |
Vector Vector Int | |
Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Int -> m (Vector Int) basicUnsafeThaw :: PrimMonad m => Vector Int -> m (Mutable Vector (PrimState m) Int) basicLength :: Vector Int -> Int basicUnsafeSlice :: Int -> Int -> Vector Int -> Vector Int basicUnsafeIndexM :: Monad m => Vector Int -> Int -> m Int basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Int -> Vector Int -> m () | |
MVector MVector Int | |
Methods basicLength :: MVector s Int -> Int basicUnsafeSlice :: Int -> Int -> MVector s Int -> MVector s Int basicOverlaps :: MVector s Int -> MVector s Int -> Bool basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Int) basicInitialize :: PrimMonad m => MVector (PrimState m) Int -> m () basicUnsafeReplicate :: PrimMonad m => Int -> Int -> m (MVector (PrimState m) Int) basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Int -> Int -> m Int basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Int -> Int -> Int -> m () basicClear :: PrimMonad m => MVector (PrimState m) Int -> m () basicSet :: PrimMonad m => MVector (PrimState m) Int -> Int -> m () basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Int -> MVector (PrimState m) Int -> m () basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Int -> MVector (PrimState m) Int -> m () basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Int -> Int -> m (MVector (PrimState m) Int) | |
() :=> (Bounded Int) | |
() :=> (Enum Int) | |
() :=> (Eq Int) | |
() :=> (Integral Int) | |
() :=> (Num Int) | |
() :=> (Ord Int) | |
() :=> (Read Int) | |
() :=> (Real Int) | |
() :=> (Show Int) | |
() :=> (Bits Int) | |
Generic1 (URec Int :: k -> *) | |
FoldableWithIndex [Int] Tree | |
Methods ifoldMap :: Monoid m => ([Int] -> a -> m) -> Tree a -> m ifolded :: (Indexable [Int] p, Contravariant f, Applicative f) => p a (f a) -> Tree a -> f (Tree a) ifoldr :: ([Int] -> a -> b -> b) -> b -> Tree a -> b ifoldl :: ([Int] -> b -> a -> b) -> b -> Tree a -> b | |
FunctorWithIndex [Int] Tree | |
TraversableWithIndex [Int] Tree | |
Methods itraverse :: Applicative f => ([Int] -> a -> f b) -> Tree a -> f (Tree b) itraversed :: (Indexable [Int] p, Applicative f) => p a (f b) -> Tree a -> f (Tree b) | |
Bizarre (Indexed Int) Mafic | |
Methods bazaar :: Applicative f => Indexed Int a (f b) -> Mafic a b t -> f t | |
Reifies Z Int | |
Reifies n Int => Reifies (D n :: *) Int | |
Reifies n Int => Reifies (PD n :: *) Int | |
Reifies n Int => Reifies (SD n :: *) Int | |
Functor (URec Int :: * -> *) | |
Foldable (URec Int :: * -> *) | |
Methods fold :: Monoid m => URec Int m -> m # foldMap :: Monoid m => (a -> m) -> URec Int a -> m # foldr :: (a -> b -> b) -> b -> URec Int a -> b # foldr' :: (a -> b -> b) -> b -> URec Int a -> b # foldl :: (b -> a -> b) -> b -> URec Int a -> b # foldl' :: (b -> a -> b) -> b -> URec Int a -> b # foldr1 :: (a -> a -> a) -> URec Int a -> a # foldl1 :: (a -> a -> a) -> URec Int a -> a # elem :: Eq a => a -> URec Int a -> Bool # maximum :: Ord a => URec Int a -> a # minimum :: Ord a => URec Int a -> a # | |
Traversable (URec Int :: * -> *) | |
Eq (URec Int p) | |
Ord (URec Int p) | |
Show (URec Int p) | |
Generic (URec Int p) | |
data Vector Int | |
type BitSize Int Source # | |
data URec Int (p :: k) | Used for marking occurrences of Since: 4.9.0.0 |
data MVector s Int | |
type Unbundled domain Int Source # | |
type Rep1 (URec Int :: k -> *) | |
type Rep (URec Int p) | |
Invariant: Jn#
and Jp#
are used iff value doesn't fit in S#
Useful properties resulting from the invariants:
Instances
Enum Integer | Since: 2.1 |
Eq Integer | |
Integral Integer | Since: 2.0.1 |
Data Integer | Since: 4.0.0.0 |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Integer -> c Integer # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Integer # toConstr :: Integer -> Constr # dataTypeOf :: Integer -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Integer) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Integer) # gmapT :: (forall b. Data b => b -> b) -> Integer -> Integer # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r # gmapQ :: (forall d. Data d => d -> u) -> Integer -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Integer -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Integer -> m Integer # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer # | |
Num Integer | Since: 2.1 |
Ord Integer | |
Read Integer | Since: 2.1 |
Real Integer | Since: 2.0.1 |
Methods toRational :: Integer -> Rational # | |
Show Integer | Since: 2.1 |
Ix Integer | Since: 2.1 |
Lift Integer | |
Bits Integer | Since: 2.1 |
Methods (.&.) :: Integer -> Integer -> Integer # (.|.) :: Integer -> Integer -> Integer # xor :: Integer -> Integer -> Integer # complement :: Integer -> Integer # shift :: Integer -> Int -> Integer # rotate :: Integer -> Int -> Integer # setBit :: Integer -> Int -> Integer # clearBit :: Integer -> Int -> Integer # complementBit :: Integer -> Int -> Integer # testBit :: Integer -> Int -> Bool # bitSizeMaybe :: Integer -> Maybe Int # shiftL :: Integer -> Int -> Integer # unsafeShiftL :: Integer -> Int -> Integer # shiftR :: Integer -> Int -> Integer # unsafeShiftR :: Integer -> Int -> Integer # rotateL :: Integer -> Int -> Integer # | |
NFData Integer | |
ShowX Integer Source # | |
Default Integer | |
Arbitrary Integer | |
CoArbitrary Integer | |
Methods coarbitrary :: Integer -> Gen b -> Gen b | |
Bundle Integer Source # | |
KnownNat n => Reifies (n :: Nat) Integer | |
() :=> (Enum Integer) | |
() :=> (Eq Integer) | |
() :=> (Integral Integer) | |
() :=> (Num Integer) | |
() :=> (Ord Integer) | |
() :=> (Real Integer) | |
() :=> (Bits Integer) | |
type Unbundled domain Integer Source # | |
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
Monad Maybe | Since: 2.1 |
Functor Maybe | Since: 2.1 |
Applicative Maybe | Since: 2.1 |
Foldable Maybe | Since: 2.1 |
Methods fold :: Monoid m => Maybe m -> m # foldMap :: Monoid m => (a -> m) -> Maybe a -> m # foldr :: (a -> b -> b) -> b -> Maybe a -> b # foldr' :: (a -> b -> b) -> b -> Maybe a -> b # foldl :: (b -> a -> b) -> b -> Maybe a -> b # foldl' :: (b -> a -> b) -> b -> Maybe a -> b # foldr1 :: (a -> a -> a) -> Maybe a -> a # foldl1 :: (a -> a -> a) -> Maybe a -> a # elem :: Eq a => a -> Maybe a -> Bool # maximum :: Ord a => Maybe a -> a # minimum :: Ord a => Maybe a -> a # | |
Traversable Maybe | Since: 2.1 |
Eq1 Maybe | Since: 4.9.0.0 |
Ord1 Maybe | Since: 4.9.0.0 |
Read1 Maybe | Since: 4.9.0.0 |
Show1 Maybe | Since: 4.9.0.0 |
Alternative Maybe | Since: 2.1 |
MonadPlus Maybe | Since: 2.1 |
NFData1 Maybe | Since: 1.4.3.0 |
Arbitrary1 Maybe | |
FoldableWithIndex () Maybe | |
Methods ifoldMap :: Monoid m => (() -> a -> m) -> Maybe a -> m ifolded :: (Indexable () p, Contravariant f, Applicative f) => p a (f a) -> Maybe a -> f (Maybe a) ifoldr :: (() -> a -> b -> b) -> b -> Maybe a -> b ifoldl :: (() -> b -> a -> b) -> b -> Maybe a -> b | |
FunctorWithIndex () Maybe | |
TraversableWithIndex () Maybe | |
Methods itraverse :: Applicative f => (() -> a -> f b) -> Maybe a -> f (Maybe b) itraversed :: (Indexable () p, Applicative f) => p a (f b) -> Maybe a -> f (Maybe b) | |
() :=> (Functor Maybe) | |
() :=> (Applicative Maybe) | |
Methods ins :: () :- Applicative Maybe | |
() :=> (Alternative Maybe) | |
Methods ins :: () :- Alternative Maybe | |
() :=> (MonadPlus Maybe) | |
Eq a => Eq (Maybe a) | |
Data a => Data (Maybe a) | Since: 4.0.0.0 |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Maybe a -> c (Maybe a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) # toConstr :: Maybe a -> Constr # dataTypeOf :: Maybe a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe a)) # gmapT :: (forall b. Data b => b -> b) -> Maybe a -> Maybe a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r # gmapQ :: (forall d. Data d => d -> u) -> Maybe a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # | |
Ord a => Ord (Maybe a) | |
Read a => Read (Maybe a) | Since: 2.1 |
Show a => Show (Maybe a) | |
Generic (Maybe a) | |
Semigroup a => Semigroup (Maybe a) | Since: 4.9.0.0 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: 2.1 |
Lift a => Lift (Maybe a) | |
SingKind a => SingKind (Maybe a) | Since: 4.9.0.0 |
NFData a => NFData (Maybe a) | |
ShowX a => ShowX (Maybe a) Source # | |
At (Maybe a) | |
Ixed (Maybe a) | |
AsEmpty (Maybe a) | |
Default (Maybe a) | |
Arbitrary a => Arbitrary (Maybe a) | |
CoArbitrary a => CoArbitrary (Maybe a) | |
Methods coarbitrary :: Maybe a -> Gen b -> Gen b | |
(BitPack a, KnownNat (BitSize a)) => BitPack (Maybe a) Source # | |
PEq (Maybe a) | |
SEq a => SEq (Maybe a) | |
POrd (Maybe a) | |
SOrd a => SOrd (Maybe a) | |
Methods sCompare :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) (%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) (%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) (%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) (%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) sMin :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) | |
PShow (Maybe a) | |
SShow a => SShow (Maybe a) | |
Methods sShowsPrec :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) sShowList :: Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) | |
ShowSing a => ShowSing (Maybe a) | |
Methods showsSingPrec :: Int -> Sing a0 -> ShowS | |
Bundle (Maybe a) Source # | |
Generic1 Maybe | |
SingI (Nothing :: Maybe a) | Since: 4.9.0.0 |
(Eq a) :=> (Eq (Maybe a)) | |
(Ord a) :=> (Ord (Maybe a)) | |
(Read a) :=> (Read (Maybe a)) | |
(Show a) :=> (Show (Maybe a)) | |
(Semigroup a) :=> (Semigroup (Maybe a)) | |
(Monoid a) :=> (Monoid (Maybe a)) | |
Each (Maybe a) (Maybe b) a b | |
SingI a2 => SingI (Just a2 :: Maybe a1) | Since: 4.9.0.0 |
SuppressUnusedWarnings (FindSym1 :: (TyFun a6989586621679681271 Bool -> Type) -> TyFun [a6989586621679681271] (Maybe a6989586621679681271) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FindIndexSym1 :: (TyFun a6989586621679681268 Bool -> Type) -> TyFun [a6989586621679681268] (Maybe Nat) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551085Sym1 :: Maybe a3530822107858468865 -> TyFun (Maybe a3530822107858468865) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ShowsPrec_6989586621679887881Sym2 :: Nat -> Maybe a3530822107858468865 -> TyFun Symbol Symbol -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ShowsPrec_6989586621679887881Sym1 :: Nat -> TyFun (Maybe a3530822107858468865) (TyFun Symbol Symbol -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FromMaybeSym1 :: a6989586621679647546 -> TyFun (Maybe a6989586621679647546) a6989586621679647546 -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ElemIndexSym1 :: a6989586621679681270 -> TyFun [a6989586621679681270] (Maybe Nat) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FindSym0 :: TyFun (TyFun a6989586621679681271 Bool -> Type) (TyFun [a6989586621679681271] (Maybe a6989586621679681271) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (TyFun a6989586621679681268 Bool -> Type) (TyFun [a6989586621679681268] (Maybe Nat) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (CatMaybesSym0 :: TyFun [Maybe a6989586621679647543] [a6989586621679647543] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ListToMaybeSym0 :: TyFun [a6989586621679647544] (Maybe a6989586621679647544) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551085Sym0 :: TyFun (Maybe a3530822107858468865) (TyFun (Maybe a3530822107858468865) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (MaybeToListSym0 :: TyFun (Maybe a6989586621679647545) [a6989586621679647545] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a6989586621679647548) Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a6989586621679647549) Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FromJustSym0 :: TyFun (Maybe a6989586621679647547) a6989586621679647547 -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ShowsPrec_6989586621679887881Sym0 :: TyFun Nat (TyFun (Maybe a3530822107858468865) (TyFun Symbol Symbol -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (FromMaybeSym0 :: TyFun a6989586621679647546 (TyFun (Maybe a6989586621679647546) a6989586621679647546 -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679681270 (TyFun [a6989586621679681270] (Maybe Nat) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (JustSym0 :: TyFun a3530822107858468865 (Maybe a3530822107858468865) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (MapMaybeSym1 :: (TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) -> TyFun [a6989586621679647541] [b6989586621679647542] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679647720RsSym2 :: (TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) -> a6989586621679647541 -> TyFun [a6989586621679647541] [b6989586621679647542] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679647720RsSym1 :: (TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) -> TyFun a6989586621679647541 (TyFun [a6989586621679647541] [b6989586621679647542] -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (UnfoldrSym1 :: (TyFun b6989586621679681327 (Maybe (a6989586621679681328, b6989586621679681327)) -> Type) -> TyFun b6989586621679681327 [a6989586621679681328] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Maybe_Sym2 :: b6989586621679646418 -> (TyFun a6989586621679646419 b6989586621679646418 -> Type) -> TyFun (Maybe a6989586621679646419) b6989586621679646418 -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Maybe_Sym1 :: b6989586621679646418 -> TyFun (TyFun a6989586621679646419 b6989586621679646418 -> Type) (TyFun (Maybe a6989586621679646419) b6989586621679646418 -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (LookupSym1 :: a6989586621679681249 -> TyFun [(a6989586621679681249, b6989586621679681250)] (Maybe b6989586621679681250) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) (TyFun [a6989586621679647541] [b6989586621679647542] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679647720RsSym0 :: TyFun (TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) (TyFun a6989586621679647541 (TyFun [a6989586621679647541] [b6989586621679647542] -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (TyFun b6989586621679681327 (Maybe (a6989586621679681328, b6989586621679681327)) -> Type) (TyFun b6989586621679681327 [a6989586621679681328] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b6989586621679646418 (TyFun (TyFun a6989586621679646419 b6989586621679646418 -> Type) (TyFun (Maybe a6989586621679646419) b6989586621679646418 -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679681249 (TyFun [(a6989586621679681249, b6989586621679681250)] (Maybe b6989586621679681250) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
type Unbundled domain (Maybe a) Source # | |
type Apply (JustSym0 :: TyFun a (Maybe a) -> *) (l :: a) | |
type Apply (ShowsPrec_6989586621679887881Sym0 :: TyFun Nat (TyFun (Maybe a3530822107858468865) (TyFun Symbol Symbol -> Type) -> Type) -> *) (l :: Nat) | |
type Apply (FromMaybeSym0 :: TyFun a6989586621679647546 (TyFun (Maybe a6989586621679647546) a6989586621679647546 -> Type) -> *) (l :: a6989586621679647546) | |
type Apply (ElemIndexSym0 :: TyFun a6989586621679681270 (TyFun [a6989586621679681270] (Maybe Nat) -> Type) -> *) (l :: a6989586621679681270) | |
type Apply (Maybe_Sym0 :: TyFun b6989586621679646418 (TyFun (TyFun a6989586621679646419 b6989586621679646418 -> Type) (TyFun (Maybe a6989586621679646419) b6989586621679646418 -> Type) -> Type) -> *) (l :: b6989586621679646418) | |
type Apply (Maybe_Sym0 :: TyFun b6989586621679646418 (TyFun (TyFun a6989586621679646419 b6989586621679646418 -> Type) (TyFun (Maybe a6989586621679646419) b6989586621679646418 -> Type) -> Type) -> *) (l :: b6989586621679646418) = (Maybe_Sym1 l :: TyFun (TyFun a6989586621679646419 b6989586621679646418 -> Type) (TyFun (Maybe a6989586621679646419) b6989586621679646418 -> Type) -> *) | |
type Apply (LookupSym0 :: TyFun a6989586621679681249 (TyFun [(a6989586621679681249, b6989586621679681250)] (Maybe b6989586621679681250) -> Type) -> *) (l :: a6989586621679681249) | |
type Rep (Maybe a) | |
data Sing (b :: Maybe a) | |
type DemoteRep (Maybe a) | |
type Index (Maybe a) | |
type Index (Maybe a) = () | |
type IxValue (Maybe a) | |
type IxValue (Maybe a) = a | |
type BitSize (Maybe a) Source # | |
data Sing (z :: Maybe a) | |
type Demote (Maybe a) | |
type Rep1 Maybe | |
type Show_ (arg :: Maybe a) | |
type (x :: Maybe a) /= (y :: Maybe a) | |
type (a2 :: Maybe a1) == (b :: Maybe a1) | |
type (arg1 :: Maybe a) < (arg2 :: Maybe a) | |
type (arg1 :: Maybe a) <= (arg2 :: Maybe a) | |
type (arg1 :: Maybe a) > (arg2 :: Maybe a) | |
type (arg1 :: Maybe a) >= (arg2 :: Maybe a) | |
type Compare (a2 :: Maybe a1) (a3 :: Maybe a1) | |
type Max (arg1 :: Maybe a) (arg2 :: Maybe a) | |
type Min (arg1 :: Maybe a) (arg2 :: Maybe a) | |
type ShowList (arg1 :: [Maybe a]) arg2 | |
type ShowsPrec a2 (a3 :: Maybe a1) a4 | |
type Apply (FromJustSym0 :: TyFun (Maybe a) a -> *) (l :: Maybe a) | |
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> *) (l :: Maybe a) | |
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> *) (l :: Maybe a) | |
type Apply (Compare_6989586621679551085Sym1 l1 :: TyFun (Maybe a) Ordering -> *) (l2 :: Maybe a) | |
type Apply (FromMaybeSym1 l1 :: TyFun (Maybe a) a -> *) (l2 :: Maybe a) | |
type Apply (Maybe_Sym2 l1 l2 :: TyFun (Maybe a) b -> *) (l3 :: Maybe a) | |
type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> *) (l :: [Maybe a]) | |
type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> *) (l :: [a]) | |
type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> *) (l :: Maybe a) | |
type Apply (FindSym1 l1 :: TyFun [a] (Maybe a) -> *) (l2 :: [a]) | |
type Apply (FindIndexSym1 l1 :: TyFun [a] (Maybe Nat) -> *) (l2 :: [a]) | |
type Apply (ElemIndexSym1 l1 :: TyFun [a] (Maybe Nat) -> *) (l2 :: [a]) | |
type Apply (LookupSym1 l1 :: TyFun [(a, b)] (Maybe b) -> *) (l2 :: [(a, b)]) | |
type Apply (Compare_6989586621679551085Sym0 :: TyFun (Maybe a3530822107858468865) (TyFun (Maybe a3530822107858468865) Ordering -> Type) -> *) (l :: Maybe a3530822107858468865) | |
type Apply (ShowsPrec_6989586621679887881Sym1 l1 :: TyFun (Maybe a3530822107858468865) (TyFun Symbol Symbol -> Type) -> *) (l2 :: Maybe a3530822107858468865) | |
type Apply (FindSym0 :: TyFun (TyFun a6989586621679681271 Bool -> Type) (TyFun [a6989586621679681271] (Maybe a6989586621679681271) -> Type) -> *) (l :: TyFun a6989586621679681271 Bool -> Type) | |
type Apply (FindIndexSym0 :: TyFun (TyFun a6989586621679681268 Bool -> Type) (TyFun [a6989586621679681268] (Maybe Nat) -> Type) -> *) (l :: TyFun a6989586621679681268 Bool -> Type) | |
type Apply (MapMaybeSym0 :: TyFun (TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) (TyFun [a6989586621679647541] [b6989586621679647542] -> Type) -> *) (l :: TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) | |
type Apply (Let6989586621679647720RsSym0 :: TyFun (TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) (TyFun a6989586621679647541 (TyFun [a6989586621679647541] [b6989586621679647542] -> *) -> *) -> *) (l :: TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) | |
type Apply (Let6989586621679647720RsSym0 :: TyFun (TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) (TyFun a6989586621679647541 (TyFun [a6989586621679647541] [b6989586621679647542] -> *) -> *) -> *) (l :: TyFun a6989586621679647541 (Maybe b6989586621679647542) -> Type) = Let6989586621679647720RsSym1 l | |
type Apply (UnfoldrSym0 :: TyFun (TyFun b6989586621679681327 (Maybe (a6989586621679681328, b6989586621679681327)) -> Type) (TyFun b6989586621679681327 [a6989586621679681328] -> Type) -> *) (l :: TyFun b6989586621679681327 (Maybe (a6989586621679681328, b6989586621679681327)) -> Type) | |
type Apply (Maybe_Sym1 l1 :: TyFun (TyFun a6989586621679646419 b6989586621679646418 -> Type) (TyFun (Maybe a6989586621679646419) b6989586621679646418 -> Type) -> *) (l2 :: TyFun a6989586621679646419 b6989586621679646418 -> Type) | |
Instances
Bounded Ordering | Since: 2.1 |
Enum Ordering | Since: 2.1 |
Eq Ordering | |
Data Ordering | Since: 4.0.0.0 |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordering -> c Ordering # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering # toConstr :: Ordering -> Constr # dataTypeOf :: Ordering -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) # gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r # gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # | |
Ord Ordering | |
Read Ordering | Since: 2.1 |
Show Ordering | |
Ix Ordering | Since: 2.1 |
Generic Ordering | |
Semigroup Ordering | Since: 4.9.0.0 |
Monoid Ordering | Since: 2.1 |
NFData Ordering | |
AsEmpty Ordering | |
Default Ordering | |
Arbitrary Ordering | |
CoArbitrary Ordering | |
Methods coarbitrary :: Ordering -> Gen b -> Gen b | |
PBounded Ordering | |
Associated Types type MinBound :: a type MaxBound :: a | |
PEnum Ordering | |
Associated Types type Succ arg :: a type Pred arg :: a type ToEnum arg :: a type FromEnum arg :: Nat type EnumFromTo arg arg1 :: [a] type EnumFromThenTo arg arg1 arg2 :: [a] | |
SBounded Ordering | |
SEnum Ordering | |
Methods sSucc :: Sing t -> Sing (Apply SuccSym0 t) sPred :: Sing t -> Sing (Apply PredSym0 t) sToEnum :: Sing t -> Sing (Apply ToEnumSym0 t) sFromEnum :: Sing t -> Sing (Apply FromEnumSym0 t) sEnumFromTo :: Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) sEnumFromThenTo :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) | |
PEq Ordering | |
SEq Ordering | |
POrd Ordering | |
SOrd Ordering | |
Methods sCompare :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) (%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) (%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) (%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) (%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) sMin :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) | |
PShow Ordering | |
SShow Ordering | |
Methods sShowsPrec :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) sShowList :: Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) | |
ShowSing Ordering | |
Methods showsSingPrec :: Int -> Sing a -> ShowS | |
() :=> (Bounded Ordering) | |
() :=> (Enum Ordering) | |
() :=> (Read Ordering) | |
() :=> (Show Ordering) | |
() :=> (Semigroup Ordering) | |
() :=> (Monoid Ordering) | |
SuppressUnusedWarnings Compare_6989586621679551605Sym1 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ThenCmpSym1 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings Compare_6989586621679551625Sym1 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ShowsPrec_6989586621679888076Sym2 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ShowsPrec_6989586621679888076Sym1 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings Compare_6989586621679551645Sym1 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings Compare_6989586621679551222Sym1 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings Compare_6989586621679551605Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ThenCmpSym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings Compare_6989586621679551625Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings FromEnum_6989586621680021043Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ShowsPrec_6989586621679888076Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings ToEnum_6989586621680021033Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings Compare_6989586621679551645Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings Compare_6989586621679551222Sym0 | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (SortBySym1 :: (TyFun a6989586621679681276 (TyFun a6989586621679681276 Ordering -> Type) -> Type) -> TyFun [a6989586621679681276] [a6989586621679681276] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (MinimumBySym1 :: (TyFun a6989586621679681273 (TyFun a6989586621679681273 Ordering -> Type) -> Type) -> TyFun [a6989586621679681273] a6989586621679681273 -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (MaximumBySym1 :: (TyFun a6989586621679681274 (TyFun a6989586621679681274 Ordering -> Type) -> Type) -> TyFun [a6989586621679681274] a6989586621679681274 -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (InsertBySym2 :: (TyFun a6989586621679681275 (TyFun a6989586621679681275 Ordering -> Type) -> Type) -> a6989586621679681275 -> TyFun [a6989586621679681275] [a6989586621679681275] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (InsertBySym1 :: (TyFun a6989586621679681275 (TyFun a6989586621679681275 Ordering -> Type) -> Type) -> TyFun a6989586621679681275 (TyFun [a6989586621679681275] [a6989586621679681275] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551121Sym1 :: [a3530822107858468865] -> TyFun [a3530822107858468865] Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551085Sym1 :: Maybe a3530822107858468865 -> TyFun (Maybe a3530822107858468865) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544128Scrutinee_6989586621679542851Sym1 :: k1 -> TyFun k1 Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544095Scrutinee_6989586621679542849Sym1 :: k1 -> TyFun k1 Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544062Scrutinee_6989586621679542847Sym1 :: k1 -> TyFun k1 Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544029Scrutinee_6989586621679542845Sym1 :: k1 -> TyFun k1 Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679544009Sym1 :: a6989586621679542823 -> TyFun a6989586621679542823 Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (CompareSym1 :: a6989586621679542823 -> TyFun a6989586621679542823 Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551198Sym1 :: NonEmpty a6989586621679060067 -> TyFun (NonEmpty a6989586621679060067) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (SortBySym0 :: TyFun (TyFun a6989586621679681276 (TyFun a6989586621679681276 Ordering -> Type) -> Type) (TyFun [a6989586621679681276] [a6989586621679681276] -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (MinimumBySym0 :: TyFun (TyFun a6989586621679681273 (TyFun a6989586621679681273 Ordering -> Type) -> Type) (TyFun [a6989586621679681273] a6989586621679681273 -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (MaximumBySym0 :: TyFun (TyFun a6989586621679681274 (TyFun a6989586621679681274 Ordering -> Type) -> Type) (TyFun [a6989586621679681274] a6989586621679681274 -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (InsertBySym0 :: TyFun (TyFun a6989586621679681275 (TyFun a6989586621679681275 Ordering -> Type) -> Type) (TyFun a6989586621679681275 (TyFun [a6989586621679681275] [a6989586621679681275] -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551121Sym0 :: TyFun [a3530822107858468865] (TyFun [a3530822107858468865] Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551085Sym0 :: TyFun (Maybe a3530822107858468865) (TyFun (Maybe a3530822107858468865) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544128Scrutinee_6989586621679542851Sym0 :: TyFun k1 (TyFun k1 Ordering -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544095Scrutinee_6989586621679542849Sym0 :: TyFun k1 (TyFun k1 Ordering -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544062Scrutinee_6989586621679542847Sym0 :: TyFun k1 (TyFun k1 Ordering -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679544029Scrutinee_6989586621679542845Sym0 :: TyFun k1 (TyFun k1 Ordering -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679544009Sym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (CompareSym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551198Sym0 :: TyFun (NonEmpty a6989586621679060067) (TyFun (NonEmpty a6989586621679060067) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ComparingSym2 :: (TyFun b6989586621679542813 a6989586621679542812 -> Type) -> b6989586621679542813 -> TyFun b6989586621679542813 Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ComparingSym1 :: (TyFun b6989586621679542813 a6989586621679542812 -> Type) -> TyFun b6989586621679542813 (TyFun b6989586621679542813 Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551161Sym1 :: Either a6989586621679081252 b6989586621679081253 -> TyFun (Either a6989586621679081252 b6989586621679081253) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551256Sym1 :: (a3530822107858468865, b3530822107858468866) -> TyFun (a3530822107858468865, b3530822107858468866) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ComparingSym0 :: TyFun (TyFun b6989586621679542813 a6989586621679542812 -> Type) (TyFun b6989586621679542813 (TyFun b6989586621679542813 Ordering -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551161Sym0 :: TyFun (Either a6989586621679081252 b6989586621679081253) (TyFun (Either a6989586621679081252 b6989586621679081253) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551256Sym0 :: TyFun (a3530822107858468865, b3530822107858468866) (TyFun (a3530822107858468865, b3530822107858468866) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551301Sym1 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867) -> TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551301Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679692761MinBySym0 :: TyFun (k3 ~> (k3 ~> Ordering)) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k3 k3 -> *) -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679692677MaxBySym0 :: TyFun (k3 ~> (k3 ~> Ordering)) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k3 k3 -> *) -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679692761MinBySym4 :: (k3 ~> (k3 ~> Ordering)) -> k1 -> k2 -> k3 -> TyFun k3 k3 -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679692761MinBySym3 :: (k3 ~> (k3 ~> Ordering)) -> k1 -> k2 -> TyFun k3 (TyFun k3 k3 -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679692761MinBySym2 :: (k3 ~> (k3 ~> Ordering)) -> k1 -> TyFun k2 (TyFun k3 (TyFun k3 k3 -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679692761MinBySym1 :: (k3 ~> (k3 ~> Ordering)) -> TyFun k1 (TyFun k2 (TyFun k3 (TyFun k3 k3 -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679692677MaxBySym4 :: (k3 ~> (k3 ~> Ordering)) -> k1 -> k2 -> k3 -> TyFun k3 k3 -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679692677MaxBySym3 :: (k3 ~> (k3 ~> Ordering)) -> k1 -> k2 -> TyFun k3 (TyFun k3 k3 -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679692677MaxBySym2 :: (k3 ~> (k3 ~> Ordering)) -> k1 -> TyFun k2 (TyFun k3 (TyFun k3 k3 -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Let6989586621679692677MaxBySym1 :: (k3 ~> (k3 ~> Ordering)) -> TyFun k1 (TyFun k2 (TyFun k3 (TyFun k3 k3 -> *) -> *) -> *) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551355Sym1 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) -> TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551355Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551418Sym1 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) -> TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551418Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551490Sym1 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) -> TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551490Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551571Sym1 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) -> TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551571Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
type Rep Ordering | |
data Sing (z :: Ordering) | |
type Demote Ordering | |
type MaxBound | |
type MaxBound = MaxBound_6989586621679997945Sym0 | |
type MinBound | |
type MinBound = MinBound_6989586621679997943Sym0 | |
type FromEnum (a :: Ordering) | |
type FromEnum (a :: Ordering) = Apply FromEnum_6989586621680021043Sym0 a | |
type ToEnum a | |
type ToEnum a = Apply ToEnum_6989586621680021033Sym0 a | |
type Show_ (arg :: Ordering) | |
type Pred (arg :: Ordering) | |
type Succ (arg :: Ordering) | |
type EnumFromTo (arg1 :: Ordering) (arg2 :: Ordering) | |
type (x :: Ordering) /= (y :: Ordering) | |
type (a :: Ordering) == (b :: Ordering) | |
type (arg1 :: Ordering) < (arg2 :: Ordering) | |
type (arg1 :: Ordering) <= (arg2 :: Ordering) | |
type (arg1 :: Ordering) > (arg2 :: Ordering) | |
type (arg1 :: Ordering) >= (arg2 :: Ordering) | |
type Compare (a1 :: Ordering) (a2 :: Ordering) | |
type Max (arg1 :: Ordering) (arg2 :: Ordering) | |
type Min (arg1 :: Ordering) (arg2 :: Ordering) | |
type ShowList (arg1 :: [Ordering]) arg2 | |
type Apply FromEnum_6989586621680021043Sym0 (l :: Ordering) | |
type Apply FromEnum_6989586621680021043Sym0 (l :: Ordering) = FromEnum_6989586621680021043 l | |
type Apply ToEnum_6989586621680021033Sym0 (l :: Nat) | |
type Apply ToEnum_6989586621680021033Sym0 (l :: Nat) = ToEnum_6989586621680021033 l | |
type EnumFromThenTo (arg1 :: Ordering) (arg2 :: Ordering) (arg3 :: Ordering) | |
type ShowsPrec a1 (a2 :: Ordering) a3 | |
type ShowsPrec a1 (a2 :: Ordering) a3 = Apply (Apply (Apply ShowsPrec_6989586621679888076Sym0 a1) a2) a3 | |
type Apply (Compare_6989586621679551605Sym1 l1 :: TyFun Bool Ordering -> *) (l2 :: Bool) | |
type Apply (ThenCmpSym1 l1 :: TyFun Ordering Ordering -> *) (l2 :: Ordering) | |
type Apply (Compare_6989586621679551625Sym1 l1 :: TyFun Ordering Ordering -> *) (l2 :: Ordering) | |
type Apply (Compare_6989586621679551645Sym1 l1 :: TyFun () Ordering -> *) (l2 :: ()) | |
type Apply (Compare_6989586621679551222Sym1 l1 :: TyFun Void Ordering -> *) (l2 :: Void) | |
type Apply (Compare_6989586621679544009Sym1 l1 :: TyFun a Ordering -> *) (l2 :: a) | |
type Apply (CompareSym1 l1 :: TyFun a Ordering -> *) (l2 :: a) | |
type Apply (Let6989586621679544128Scrutinee_6989586621679542851Sym1 l1 :: TyFun k1 Ordering -> *) (l2 :: k1) | |
type Apply (Let6989586621679544095Scrutinee_6989586621679542849Sym1 l1 :: TyFun k1 Ordering -> *) (l2 :: k1) | |
type Apply (Let6989586621679544062Scrutinee_6989586621679542847Sym1 l1 :: TyFun k1 Ordering -> *) (l2 :: k1) | |
type Apply (Let6989586621679544029Scrutinee_6989586621679542845Sym1 l1 :: TyFun k1 Ordering -> *) (l2 :: k1) | |
type Apply (ComparingSym2 l1 l2 :: TyFun b Ordering -> *) (l3 :: b) | |
type Apply Compare_6989586621679551605Sym0 (l :: Bool) | |
type Apply Compare_6989586621679551605Sym0 (l :: Bool) = Compare_6989586621679551605Sym1 l | |
type Apply ThenCmpSym0 (l :: Ordering) | |
type Apply ThenCmpSym0 (l :: Ordering) = ThenCmpSym1 l | |
type Apply Compare_6989586621679551625Sym0 (l :: Ordering) | |
type Apply Compare_6989586621679551625Sym0 (l :: Ordering) = Compare_6989586621679551625Sym1 l | |
type Apply ShowsPrec_6989586621679888076Sym0 (l :: Nat) | |
type Apply ShowsPrec_6989586621679888076Sym0 (l :: Nat) = ShowsPrec_6989586621679888076Sym1 l | |
type Apply Compare_6989586621679551645Sym0 (l :: ()) | |
type Apply Compare_6989586621679551645Sym0 (l :: ()) = Compare_6989586621679551645Sym1 l | |
type Apply Compare_6989586621679551222Sym0 (l :: Void) | |
type Apply Compare_6989586621679551222Sym0 (l :: Void) = Compare_6989586621679551222Sym1 l | |
type Apply (ShowsPrec_6989586621679888076Sym1 l1 :: TyFun Ordering (TyFun Symbol Symbol -> Type) -> *) (l2 :: Ordering) | |
type Apply (Compare_6989586621679544009Sym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Ordering -> Type) -> *) (l :: a6989586621679542823) | |
type Apply (CompareSym0 :: TyFun a6989586621679542823 (TyFun a6989586621679542823 Ordering -> Type) -> *) (l :: a6989586621679542823) | |
type Apply (Let6989586621679544128Scrutinee_6989586621679542851Sym0 :: TyFun k1 (TyFun k1 Ordering -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679544095Scrutinee_6989586621679542849Sym0 :: TyFun k1 (TyFun k1 Ordering -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679544062Scrutinee_6989586621679542847Sym0 :: TyFun k1 (TyFun k1 Ordering -> *) -> *) (l :: k1) | |
type Apply (Let6989586621679544029Scrutinee_6989586621679542845Sym0 :: TyFun k1 (TyFun k1 Ordering -> *) -> *) (l :: k1) | |
type Apply (ComparingSym1 l1 :: TyFun b6989586621679542813 (TyFun b6989586621679542813 Ordering -> Type) -> *) (l2 :: b6989586621679542813) | |
type Apply (Compare_6989586621679551121Sym1 l1 :: TyFun [a] Ordering -> *) (l2 :: [a]) | |
type Apply (Compare_6989586621679551085Sym1 l1 :: TyFun (Maybe a) Ordering -> *) (l2 :: Maybe a) | |
type Apply (Compare_6989586621679551198Sym1 l1 :: TyFun (NonEmpty a) Ordering -> *) (l2 :: NonEmpty a) | |
type Apply (Compare_6989586621679551121Sym0 :: TyFun [a3530822107858468865] (TyFun [a3530822107858468865] Ordering -> Type) -> *) (l :: [a3530822107858468865]) | |
type Apply (Compare_6989586621679551085Sym0 :: TyFun (Maybe a3530822107858468865) (TyFun (Maybe a3530822107858468865) Ordering -> Type) -> *) (l :: Maybe a3530822107858468865) | |
type Apply (Compare_6989586621679551198Sym0 :: TyFun (NonEmpty a6989586621679060067) (TyFun (NonEmpty a6989586621679060067) Ordering -> Type) -> *) (l :: NonEmpty a6989586621679060067) | |
type Apply (Compare_6989586621679551161Sym1 l1 :: TyFun (Either a b) Ordering -> *) (l2 :: Either a b) | |
type Apply (Compare_6989586621679551256Sym1 l1 :: TyFun (a, b) Ordering -> *) (l2 :: (a, b)) | |
type Apply (InsertBySym0 :: TyFun (TyFun a6989586621679681275 (TyFun a6989586621679681275 Ordering -> Type) -> Type) (TyFun a6989586621679681275 (TyFun [a6989586621679681275] [a6989586621679681275] -> Type) -> Type) -> *) (l :: TyFun a6989586621679681275 (TyFun a6989586621679681275 Ordering -> Type) -> Type) | |
type Apply (InsertBySym0 :: TyFun (TyFun a6989586621679681275 (TyFun a6989586621679681275 Ordering -> Type) -> Type) (TyFun a6989586621679681275 (TyFun [a6989586621679681275] [a6989586621679681275] -> Type) -> Type) -> *) (l :: TyFun a6989586621679681275 (TyFun a6989586621679681275 Ordering -> Type) -> Type) = InsertBySym1 l | |
type Apply (SortBySym0 :: TyFun (TyFun a6989586621679681276 (TyFun a6989586621679681276 Ordering -> Type) -> Type) (TyFun [a6989586621679681276] [a6989586621679681276] -> Type) -> *) (l :: TyFun a6989586621679681276 (TyFun a6989586621679681276 Ordering -> Type) -> Type) | |
type Apply (MaximumBySym0 :: TyFun (TyFun a6989586621679681274 (TyFun a6989586621679681274 Ordering -> Type) -> Type) (TyFun [a6989586621679681274] a6989586621679681274 -> Type) -> *) (l :: TyFun a6989586621679681274 (TyFun a6989586621679681274 Ordering -> Type) -> Type) | |
type Apply (MinimumBySym0 :: TyFun (TyFun a6989586621679681273 (TyFun a6989586621679681273 Ordering -> Type) -> Type) (TyFun [a6989586621679681273] a6989586621679681273 -> Type) -> *) (l :: TyFun a6989586621679681273 (TyFun a6989586621679681273 Ordering -> Type) -> Type) | |
type Apply (ComparingSym0 :: TyFun (TyFun b6989586621679542813 a6989586621679542812 -> Type) (TyFun b6989586621679542813 (TyFun b6989586621679542813 Ordering -> Type) -> Type) -> *) (l :: TyFun b6989586621679542813 a6989586621679542812 -> Type) | |
type Apply (Compare_6989586621679551161Sym0 :: TyFun (Either a6989586621679081252 b6989586621679081253) (TyFun (Either a6989586621679081252 b6989586621679081253) Ordering -> Type) -> *) (l :: Either a6989586621679081252 b6989586621679081253) | |
type Apply (Compare_6989586621679551256Sym0 :: TyFun (a3530822107858468865, b3530822107858468866) (TyFun (a3530822107858468865, b3530822107858468866) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866)) | |
type Apply (Let6989586621679692677MaxBySym0 :: TyFun (k1 ~> (k1 ~> Ordering)) (TyFun k2 (TyFun k3 (TyFun k1 (TyFun k1 k1 -> *) -> *) -> *) -> *) -> *) (l :: k1 ~> (k1 ~> Ordering)) | |
type Apply (Let6989586621679692761MinBySym0 :: TyFun (k1 ~> (k1 ~> Ordering)) (TyFun k2 (TyFun k3 (TyFun k1 (TyFun k1 k1 -> *) -> *) -> *) -> *) -> *) (l :: k1 ~> (k1 ~> Ordering)) | |
type Apply (Compare_6989586621679551301Sym1 l1 :: TyFun (a, b, c) Ordering -> *) (l2 :: (a, b, c)) | |
type Apply (Compare_6989586621679551301Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866, c3530822107858468867)) | |
type Apply (Compare_6989586621679551301Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866, c3530822107858468867)) = Compare_6989586621679551301Sym1 l | |
type Apply (Compare_6989586621679551355Sym1 l1 :: TyFun (a, b, c, d) Ordering -> *) (l2 :: (a, b, c, d)) | |
type Apply (Compare_6989586621679551355Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868)) | |
type Apply (Compare_6989586621679551355Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868)) = Compare_6989586621679551355Sym1 l | |
type Apply (Compare_6989586621679551418Sym1 l1 :: TyFun (a, b, c, d, e) Ordering -> *) (l2 :: (a, b, c, d, e)) | |
type Apply (Compare_6989586621679551418Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869)) | |
type Apply (Compare_6989586621679551418Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869)) = Compare_6989586621679551418Sym1 l | |
type Apply (Compare_6989586621679551490Sym1 l1 :: TyFun (a, b, c, d, e, f) Ordering -> *) (l2 :: (a, b, c, d, e, f)) | |
type Apply (Compare_6989586621679551490Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870)) | |
type Apply (Compare_6989586621679551490Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870)) = Compare_6989586621679551490Sym1 l | |
type Apply (Compare_6989586621679551571Sym1 l1 :: TyFun (a, b, c, d, e, f, g) Ordering -> *) (l2 :: (a, b, c, d, e, f, g)) | |
type Apply (Compare_6989586621679551571Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871)) | |
type Apply (Compare_6989586621679551571Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) (TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) Ordering -> Type) -> *) (l :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871)) = Compare_6989586621679551571Sym1 l |
A value of type
is a computation which, when performed,
does some I/O before returning a value of type IO
aa
.
There is really only one way to "perform" an I/O action: bind it to
Main.main
in your program. When your program is run, the I/O will
be performed. It isn't possible to perform I/O from an arbitrary
function, unless that function is itself in the IO
monad and called
at some point, directly or indirectly, from Main.main
.
IO
is a monad, so IO
actions can be combined using either the do-notation
or the >>
and >>=
operations from the Monad
class.
Instances
Instances
Bounded Word | Since: 2.1 |
Enum Word | Since: 2.1 |
Eq Word | |
Integral Word | Since: 2.1 |
Data Word | Since: 4.0.0.0 |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word -> c Word # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word # dataTypeOf :: Word -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) # gmapT :: (forall b. Data b => b -> b) -> Word -> Word # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r # gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word # | |
Num Word | Since: 2.1 |
Ord Word | |
Read Word | Since: 4.5.0.0 |
Real Word | Since: 2.1 |
Methods toRational :: Word -> Rational # | |
Show Word | Since: 2.1 |
Ix Word | Since: 4.6.0.0 |
Lift Word | |
Storable Word | Since: 2.1 |
Bits Word | Since: 2.1 |
Methods (.&.) :: Word -> Word -> Word # (.|.) :: Word -> Word -> Word # complement :: Word -> Word # shift :: Word -> Int -> Word # rotate :: Word -> Int -> Word # setBit :: Word -> Int -> Word # clearBit :: Word -> Int -> Word # complementBit :: Word -> Int -> Word # testBit :: Word -> Int -> Bool # bitSizeMaybe :: Word -> Maybe Int # shiftL :: Word -> Int -> Word # unsafeShiftL :: Word -> Int -> Word # shiftR :: Word -> Int -> Word # unsafeShiftR :: Word -> Int -> Word # rotateL :: Word -> Int -> Word # | |
FiniteBits Word | Since: 4.6.0.0 |
Methods finiteBitSize :: Word -> Int # countLeadingZeros :: Word -> Int # countTrailingZeros :: Word -> Int # | |
NFData Word | |
ShowX Word Source # | |
Default Word | |
Arbitrary Word | |
CoArbitrary Word | |
Methods coarbitrary :: Word -> Gen b -> Gen b | |
Unbox Word | |
Prim Word | |
Methods alignment# :: Word -> Int# indexByteArray# :: ByteArray# -> Int# -> Word readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word#) writeByteArray# :: MutableByteArray# s -> Int# -> Word -> State# s -> State# s setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Word -> State# s -> State# s indexOffAddr# :: Addr# -> Int# -> Word readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word#) writeOffAddr# :: Addr# -> Int# -> Word -> State# s -> State# s setOffAddr# :: Addr# -> Int# -> Int# -> Word -> State# s -> State# s | |
BitPack Word Source # | |
Vector Vector Word | |
Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Word -> m (Vector Word) basicUnsafeThaw :: PrimMonad m => Vector Word -> m (Mutable Vector (PrimState m) Word) basicLength :: Vector Word -> Int basicUnsafeSlice :: Int -> Int -> Vector Word -> Vector Word basicUnsafeIndexM :: Monad m => Vector Word -> Int -> m Word basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Word -> Vector Word -> m () | |
MVector MVector Word | |
Methods basicLength :: MVector s Word -> Int basicUnsafeSlice :: Int -> Int -> MVector s Word -> MVector s Word basicOverlaps :: MVector s Word -> MVector s Word -> Bool basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Word) basicInitialize :: PrimMonad m => MVector (PrimState m) Word -> m () basicUnsafeReplicate :: PrimMonad m => Int -> Word -> m (MVector (PrimState m) Word) basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Word -> Int -> m Word basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Word -> Int -> Word -> m () basicClear :: PrimMonad m => MVector (PrimState m) Word -> m () basicSet :: PrimMonad m => MVector (PrimState m) Word -> Word -> m () basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Word -> MVector (PrimState m) Word -> m () basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Word -> MVector (PrimState m) Word -> m () basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Word -> Int -> m (MVector (PrimState m) Word) | |
() :=> (Bounded Word) | |
() :=> (Enum Word) | |
() :=> (Eq Word) | |
() :=> (Integral Word) | |
() :=> (Num Word) | |
() :=> (Ord Word) | |
() :=> (Read Word) | |
() :=> (Real Word) | |
() :=> (Show Word) | |
() :=> (Bits Word) | |
Generic1 (URec Word :: k -> *) | |
Functor (URec Word :: * -> *) | |
Foldable (URec Word :: * -> *) | |
Methods fold :: Monoid m => URec Word m -> m # foldMap :: Monoid m => (a -> m) -> URec Word a -> m # foldr :: (a -> b -> b) -> b -> URec Word a -> b # foldr' :: (a -> b -> b) -> b -> URec Word a -> b # foldl :: (b -> a -> b) -> b -> URec Word a -> b # foldl' :: (b -> a -> b) -> b -> URec Word a -> b # foldr1 :: (a -> a -> a) -> URec Word a -> a # foldl1 :: (a -> a -> a) -> URec Word a -> a # toList :: URec Word a -> [a] # length :: URec Word a -> Int # elem :: Eq a => a -> URec Word a -> Bool # maximum :: Ord a => URec Word a -> a # minimum :: Ord a => URec Word a -> a # | |
Traversable (URec Word :: * -> *) | |
Eq (URec Word p) | |
Ord (URec Word p) | |
Show (URec Word p) | |
Generic (URec Word p) | |
data Vector Word | |
type BitSize Word Source # | |
data URec Word (p :: k) | Used for marking occurrences of Since: 4.9.0.0 |
data MVector s Word | |
type Rep1 (URec Word :: k -> *) | |
type Rep (URec Word p) | |
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
Bifoldable Either | Since: 4.10.0.0 |
Bifunctor Either | Since: 4.8.0.0 |
Eq2 Either | Since: 4.9.0.0 |
Ord2 Either | Since: 4.9.0.0 |
Read2 Either | Since: 4.9.0.0 |
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: 4.9.0.0 |
NFData2 Either | Since: 1.4.3.0 |
Swapped Either | |
Arbitrary2 Either | |
Methods liftArbitrary2 :: Gen a -> Gen b -> Gen (Either a b) liftShrink2 :: (a -> [a]) -> (b -> [b]) -> Either a b -> [Either a b] | |
Bitraversable1 Either | |
Methods bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Either a c -> f (Either b d) bisequence1 :: Apply f => Either (f a) (f b) -> f (Either a b) | |
() :=> (Monad (Either a)) | |
() :=> (Functor (Either a)) | |
() :=> (Applicative (Either a)) | |
Methods ins :: () :- Applicative (Either a) | |
Monad (Either e) | Since: 4.4.0.0 |
Functor (Either a) | Since: 3.0 |
Applicative (Either e) | Since: 3.0 |
Foldable (Either a) | Since: 4.7.0.0 |
Methods fold :: Monoid m => Either a m -> 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 # | |
Traversable (Either a) | Since: 4.7.0.0 |
Eq a => Eq1 (Either a) | Since: 4.9.0.0 |
Ord a => Ord1 (Either a) | Since: 4.9.0.0 |
Read a => Read1 (Either a) | Since: 4.9.0.0 |
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: 4.9.0.0 |
NFData a => NFData1 (Either a) | Since: 1.4.3.0 |
Arbitrary a => Arbitrary1 (Either a) | |
Methods liftArbitrary :: Gen a0 -> Gen (Either a a0) liftShrink :: (a0 -> [a0]) -> Either a a0 -> [Either a a0] | |
Generic1 (Either a :: * -> *) | |
(Eq a, Eq b) => Eq (Either a b) | |
(Data a, Data b) => Data (Either a b) | Since: 4.0.0.0 |
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 :: (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) # | |
(Ord a, Ord b) => Ord (Either a b) | |
(Read a, Read b) => Read (Either a b) | |
(Show a, Show b) => Show (Either a b) | |
Generic (Either a b) | |
Semigroup (Either a b) | Since: 4.9.0.0 |
(Lift a, Lift b) => Lift (Either a b) | |
(NFData a, NFData b) => NFData (Either a b) | |
(ShowX a, ShowX b) => ShowX (Either a b) Source # | |
(Arbitrary a, Arbitrary b) => Arbitrary (Either a b) | |
(CoArbitrary a, CoArbitrary b) => CoArbitrary (Either a b) | |
Methods coarbitrary :: Either a b -> Gen b0 -> Gen b0 | |
PEq (Either a b) | |
(SEq a, SEq b) => SEq (Either a b) | |
POrd (Either a b) | |
(SOrd a, SOrd b) => SOrd (Either a b) | |
Methods sCompare :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) (%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) (%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) (%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) (%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) sMin :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) | |
PShow (Either a b) | |
(SShow a, SShow b) => SShow (Either a b) | |
Methods sShowsPrec :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) sShowList :: Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) | |
(ShowSing a, ShowSing b) => ShowSing (Either a b) | |
Methods showsSingPrec :: Int -> Sing a0 -> ShowS | |
Bundle (Either a b) Source # | |
(Eq a, Eq b) :=> (Eq (Either a b)) | |
(Ord a, Ord b) :=> (Ord (Either a b)) | |
(Read a, Read b) :=> (Read (Either a b)) | |
(Show a, Show b) :=> (Show (Either a b)) | |
SuppressUnusedWarnings (Compare_6989586621679551161Sym1 :: Either a6989586621679081252 b6989586621679081253 -> TyFun (Either a6989586621679081252 b6989586621679081253) Ordering -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ShowsPrec_6989586621679887937Sym2 :: Nat -> Either a6989586621679081252 b6989586621679081253 -> TyFun Symbol Symbol -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ShowsPrec_6989586621679887937Sym1 :: Nat -> TyFun (Either a6989586621679081252 b6989586621679081253) (TyFun Symbol Symbol -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (RightsSym0 :: TyFun [Either a6989586621680060966 b6989586621680060967] [b6989586621680060967] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (PartitionEithersSym0 :: TyFun [Either a6989586621680060964 b6989586621680060965] ([a6989586621680060964], [b6989586621680060965]) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (LeftsSym0 :: TyFun [Either a6989586621680060968 b6989586621680060969] [a6989586621680060968] -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Compare_6989586621679551161Sym0 :: TyFun (Either a6989586621679081252 b6989586621679081253) (TyFun (Either a6989586621679081252 b6989586621679081253) Ordering -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a6989586621680060960 b6989586621680060961) Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a6989586621680060962 b6989586621680060963) Bool -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (ShowsPrec_6989586621679887937Sym0 :: TyFun Nat (TyFun (Either a6989586621679081252 b6989586621679081253) (TyFun Symbol Symbol -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (RightSym0 :: TyFun b6989586621679081253 (Either a6989586621679081252 b6989586621679081253) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (LeftSym0 :: TyFun a6989586621679081252 (Either a6989586621679081252 b6989586621679081253) -> *) | |
Methods suppressUnusedWarnings :: () | |
(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Sum f g) | |
Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> Sum f g a -> m ifolded :: (Indexable (Either i j) p, Contravariant f0, Applicative f0) => p a (f0 a) -> Sum f g a -> f0 (Sum f g a) ifoldr :: (Either i j -> a -> b -> b) -> b -> Sum f g a -> b ifoldl :: (Either i j -> b -> a -> b) -> b -> Sum f g a -> b ifoldr' :: (Either i j -> a -> b -> b) -> b -> Sum f g a -> b ifoldl' :: (Either i j -> b -> a -> b) -> b -> Sum f g a -> b | |
(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Product f g) | |
Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> Product f g a -> m ifolded :: (Indexable (Either i j) p, Contravariant f0, Applicative f0) => p a (f0 a) -> Product f g a -> f0 (Product f g a) ifoldr :: (Either i j -> a -> b -> b) -> b -> Product f g a -> b ifoldl :: (Either i j -> b -> a -> b) -> b -> Product f g a -> b ifoldr' :: (Either i j -> a -> b -> b) -> b -> Product f g a -> b ifoldl' :: (Either i j -> b -> a -> b) -> b -> Product f g a -> b | |
(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :+: g) | |
Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :+: g) a -> m ifolded :: (Indexable (Either i j) p, Contravariant f0, Applicative f0) => p a (f0 a) -> (f :+: g) a -> f0 ((f :+: g) a) ifoldr :: (Either i j -> a -> b -> b) -> b -> (f :+: g) a -> b ifoldl :: (Either i j -> b -> a -> b) -> b -> (f :+: g) a -> b ifoldr' :: (Either i j -> a -> b -> b) -> b -> (f :+: g) a -> b ifoldl' :: (Either i j -> b -> a -> b) -> b -> (f :+: g) a -> b | |
(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :*: g) | |
Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :*: g) a -> m ifolded :: (Indexable (Either i j) p, Contravariant f0, Applicative f0) => p a (f0 a) -> (f :*: g) a -> f0 ((f :*: g) a) ifoldr :: (Either i j -> a -> b -> b) -> b -> (f :*: g) a -> b ifoldl :: (Either i j -> b -> a -> b) -> b -> (f :*: g) a -> b ifoldr' :: (Either i j -> a -> b -> b) -> b -> (f :*: g) a -> b ifoldl' :: (Either i j -> b -> a -> b) -> b -> (f :*: g) a -> b | |
(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Sum f g) | |
(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Product f g) | |
(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (f :+: g) | |
(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (f :*: g) | |
(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (Sum f g) | |
Methods itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> Sum f g a -> f0 (Sum f g b) itraversed :: (Indexable (Either i j) p, Applicative f0) => p a (f0 b) -> Sum f g a -> f0 (Sum f g b) | |
(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (Product f g) | |
Methods itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> Product f g a -> f0 (Product f g b) itraversed :: (Indexable (Either i j) p, Applicative f0) => p a (f0 b) -> Product f g a -> f0 (Product f g b) | |
(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (f :+: g) | |
Methods itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) itraversed :: (Indexable (Either i j) p, Applicative f0) => p a (f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) | |
(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (f :*: g) | |
Methods itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) itraversed :: (Indexable (Either i j) p, Applicative f0) => p a (f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) | |
SuppressUnusedWarnings (Either_Sym2 :: (TyFun a6989586621680059832 c6989586621680059833 -> Type) -> (TyFun b6989586621680059834 c6989586621680059833 -> Type) -> TyFun (Either a6989586621680059832 b6989586621680059834) c6989586621680059833 -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Either_Sym1 :: (TyFun a6989586621680059832 c6989586621680059833 -> Type) -> TyFun (TyFun b6989586621680059834 c6989586621680059833 -> Type) (TyFun (Either a6989586621680059832 b6989586621680059834) c6989586621680059833 -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
SuppressUnusedWarnings (Either_Sym0 :: TyFun (TyFun a6989586621680059832 c6989586621680059833 -> Type) (TyFun (TyFun b6989586621680059834 c6989586621680059833 -> Type) (TyFun (Either a6989586621680059832 b6989586621680059834) c6989586621680059833 -> Type) -> Type) -> *) | |
Methods suppressUnusedWarnings :: () | |
type Unbundled domain (Either a b) Source # | |
type Apply (ShowsPrec_6989586621679887937Sym0 :: TyFun Nat (TyFun (Either a6989586621679081252 b6989586621679081253) (TyFun Symbol Symbol -> Type) -> Type) -> *) (l :: Nat) | |
type Apply (ShowsPrec_6989586621679887937Sym0 :: TyFun Nat (TyFun (Either a6989586621679081252 b6989586621679081253) (TyFun Symbol Symbol -> Type) -> Type) -> *) (l :: Nat) = (ShowsPrec_6989586621679887937Sym1 l :: TyFun (Either a6989586621679081252 b6989586621679081253) (TyFun Symbol Symbol -> Type) -> *) | |
type Apply (LeftSym0 :: TyFun a (Either a b6989586621679081253) -> *) (l :: a) | |
type Apply (RightSym0 :: TyFun b (Either a6989586621679081252 b) -> *) (l :: b) | |
type Rep1 (Either a :: * -> *) | |
type Rep1 (Either a :: * -> *) = 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 Apply (RightsSym0 :: TyFun [Either a b] [b] -> *) (l :: [Either a b]) | |
type Apply (LeftsSym0 :: TyFun [Either a b] [a] -> *) (l :: [Either a b]) | |
type Apply (PartitionEithersSym0 :: TyFun [Either a b] ([a], [b]) -> *) (l :: [Either a b]) | |
type Rep (Either a b) | |
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))) | |
data Sing (z :: Either a b) | |
type Demote (Either a b) | |
type Show_ (arg :: Either a b) | |
type (x :: Either a b) /= (y :: Either a b) | |
type (a2 :: Either a1 b1) == (b2 :: Either a1 b1) | |
type (arg1 :: Either a b) < (arg2 :: Either a b) | |
type (arg1 :: Either a b) <= (arg2 :: Either a b) | |
type (arg1 :: Either a b) > (arg2 :: Either a b) | |
type (arg1 :: Either a b) >= (arg2 :: Either a b) | |
type Compare (a2 :: Either a1 b) (a3 :: Either a1 b) | |
type Max (arg1 :: Either a b) (arg2 :: Either a b) | |
type Min (arg1 :: Either a b) (arg2 :: Either a b) | |
type ShowList (arg1 :: [Either a b]) arg2 | |
type ShowsPrec a2 (a3 :: Either a1 b) a4 | |
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> *) (l :: Either a b) | |
type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> *) (l :: Either a b) | |
type Apply (Compare_6989586621679551161Sym1 l1 :: TyFun (Either a b) Ordering -> *) (l2 :: Either a b) | |
type Apply (Either_Sym2 l1 l2 :: TyFun (Either a b) c -> *) (l3 :: Either a b) | |
type Apply (Compare_6989586621679551161Sym0 :: TyFun (Either a6989586621679081252 b6989586621679081253) (TyFun (Either a6989586621679081252 b6989586621679081253) Ordering -> Type) -> *) (l :: Either a6989586621679081252 b6989586621679081253) | |
type Apply (Either_Sym0 :: TyFun (TyFun a6989586621680059832 c6989586621680059833 -> Type) (TyFun (TyFun b6989586621680059834 c6989586621680059833 -> Type) (TyFun (Either a6989586621680059832 b6989586621680059834) c6989586621680059833 -> Type) -> Type) -> *) (l :: TyFun a6989586621680059832 c6989586621680059833 -> Type) | |
type Apply (Either_Sym0 :: TyFun (TyFun a6989586621680059832 c6989586621680059833 -> Type) (TyFun (TyFun b6989586621680059834 c6989586621680059833 -> Type) (TyFun (Either a6989586621680059832 b6989586621680059834) c6989586621680059833 -> Type) -> Type) -> *) (l :: TyFun a6989586621680059832 c6989586621680059833 -> Type) = (Either_Sym1 l :: TyFun (TyFun b6989586621680059834 c6989586621680059833 -> Type) (TyFun (Either a6989586621680059832 b6989586621680059834) c6989586621680059833 -> Type) -> *) | |
type Apply (ShowsPrec_6989586621679887937Sym1 l1 :: TyFun (Either a6989586621679081252 b6989586621679081253) (TyFun Symbol Symbol -> Type) -> *) (l2 :: Either a6989586621679081252 b6989586621679081253) | |
type Apply (Either_Sym1 l1 :: TyFun (TyFun b6989586621680059834 c6989586621680059833 -> Type) (TyFun (Either a6989586621680059832 b6989586621680059834) c6989586621680059833 -> Type) -> *) (l2 :: TyFun b6989586621680059834 c6989586621680059833 -> Type) | |
appendFile :: FilePath -> String -> IO () #
The computation appendFile
file str
function appends the string str
,
to the file file
.
Note that writeFile
and appendFile
write a literal string
to a file. To write a value of any printable type, as with print
,
use the show
function to convert the value to a string first.
main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]])
writeFile :: FilePath -> String -> IO () #
The computation writeFile
file str
function writes the string str
,
to the file file
.
readFile :: FilePath -> IO String #
The readFile
function reads a file and
returns the contents of the file as a string.
The file is read lazily, on demand, as with getContents
.
interact :: (String -> String) -> IO () #
The interact
function takes a function of type String->String
as its argument. The entire input from the standard input device is
passed to this function as its argument, and the resulting string is
output on the standard output device.
getContents :: IO String #
The getContents
operation returns all user input as a single string,
which is read lazily as it is needed
(same as hGetContents
stdin
).
File and directory names are values of type String
, whose precise
meaning is operating system dependent. Files can be opened, yielding a
handle which can then be used to operate on the contents of that file.
type IOError = IOException #
all :: Foldable t => (a -> Bool) -> t a -> Bool #
Determines whether all elements of the structure satisfy the predicate.
any :: Foldable t => (a -> Bool) -> t a -> Bool #
Determines whether any element of the structure satisfies the predicate.
concatMap :: Foldable t => (a -> [b]) -> t a -> [b] #
Map a function over all the elements of a container and concatenate the resulting lists.
sequence_ :: (Foldable t, Monad m) => t (m a) -> m () #
Evaluate each monadic action in the structure from left to right,
and ignore the results. For a version that doesn't ignore the
results see sequence
.
As of base 4.8.0.0, sequence_
is just sequenceA_
, specialized
to Monad
.
words
breaks a string up into a list of words, which were delimited
by white space.
>>>
words "Lorem ipsum\ndolor"
["Lorem","ipsum","dolor"]
lines
breaks a string up into a list of strings at newline
characters. The resulting strings do not contain newlines.
Note that after splitting the string at newline characters, the last part of the string is considered a line even if it doesn't end with a newline. For example,
>>>
lines ""
[]
>>>
lines "\n"
[""]
>>>
lines "one"
["one"]
>>>
lines "one\n"
["one"]
>>>
lines "one\n\n"
["one",""]
>>>
lines "one\ntwo"
["one","two"]
>>>
lines "one\ntwo\n"
["one","two"]
Thus
contains at least as many elements as newlines in lines
ss
.
read :: Read a => String -> a #
The read
function reads input from a string, which must be
completely consumed by the input process. read
fails with an error
if the
parse is unsuccessful, and it is therefore discouraged from being used in
real applications. Use readMaybe
or readEither
for safe alternatives.
>>>
read "123" :: Int
123
>>>
read "hello" :: Int
*** Exception: Prelude.read: no parse
either :: (a -> c) -> (b -> c) -> Either a b -> c #
Case analysis for the Either
type.
If the value is
, apply the first function to Left
aa
;
if it is
, apply the second function to Right
bb
.
Examples
We create two values of type
, one using the
Either
String
Int
Left
constructor and another using the Right
constructor. Then
we apply "either" the length
function (if we have a String
)
or the "times-two" function (if we have an Int
):
>>>
let s = Left "foo" :: Either String Int
>>>
let n = Right 3 :: Either String Int
>>>
either length (*2) s
3>>>
either length (*2) n
6
The lex
function reads a single lexeme from the input, discarding
initial white space, and returning the characters that constitute the
lexeme. If the input string contains only white space, lex
returns a
single successful `lexeme' consisting of the empty string. (Thus
.) If there is no legal lexeme at the
beginning of the input string, lex
"" = [("","")]lex
fails (i.e. returns []
).
This lexer is not completely faithful to the Haskell lexical syntax in the following respects:
- Qualified names are not handled properly
- Octal and hexadecimal numerics are not recognized as a single token
- Comments are not treated properly
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap
.
The name of this operator is an allusion to $
.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $
is function application, <$>
is function
application lifted over a Functor
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
lcm :: Integral a => a -> a -> a #
is the smallest positive integer that both lcm
x yx
and y
divide.
gcd :: Integral a => a -> a -> a #
is the non-negative factor of both gcd
x yx
and y
of which
every common factor of x
and y
is also a factor; for example
, gcd
4 2 = 2
, gcd
(-4) 6 = 2
= gcd
0 44
.
= gcd
0 00
.
(That is, the common divisor that is "greatest" in the divisibility
preordering.)
Note: Since for signed fixed-width integer types,
,
the result may be negative if one of the arguments is abs
minBound
< 0
(and
necessarily is if the other is minBound
0
or
) for such types.minBound
(^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 #
raise a number to an integral power
showString :: String -> ShowS #
utility function converting a String
to a show function that
simply prepends the string unchanged.
utility function converting a Char
to a show function that
simply prepends the character unchanged.
lookup :: Eq a => a -> [(a, b)] -> Maybe b #
lookup
key assocs
looks up a key in an association list.
break :: (a -> Bool) -> [a] -> ([a], [a]) #
break
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
do not satisfy p
and second element is the remainder of the list:
break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4]) break (< 9) [1,2,3] == ([],[1,2,3]) break (> 9) [1,2,3] == ([1,2,3],[])
span :: (a -> Bool) -> [a] -> ([a], [a]) #
span
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
satisfy p
and second element is the remainder of the list:
span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4]) span (< 9) [1,2,3] == ([1,2,3],[]) span (< 0) [1,2,3] == ([],[1,2,3])
takeWhile :: (a -> Bool) -> [a] -> [a] #
takeWhile
, applied to a predicate p
and a list xs
, returns the
longest prefix (possibly empty) of xs
of elements that satisfy p
:
takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2] takeWhile (< 9) [1,2,3] == [1,2,3] takeWhile (< 0) [1,2,3] == []
cycle
ties a finite list into a circular one, or equivalently,
the infinite repetition of the original list. It is the identity
on infinite lists.
maybe :: b -> (a -> b) -> Maybe a -> b #
The maybe
function takes a default value, a function, and a Maybe
value. If the Maybe
value is Nothing
, the function returns the
default value. Otherwise, it applies the function to the value inside
the Just
and returns the result.
Examples
Basic usage:
>>>
maybe False odd (Just 3)
True
>>>
maybe False odd Nothing
False
Read an integer from a string using readMaybe
. If we succeed,
return twice the integer; that is, apply (*2)
to it. If instead
we fail to parse an integer, return 0
by default:
>>>
import Text.Read ( readMaybe )
>>>
maybe 0 (*2) (readMaybe "5")
10>>>
maybe 0 (*2) (readMaybe "")
0
Apply show
to a Maybe Int
. If we have Just n
, we want to show
the underlying Int
n
. But if we have Nothing
, we return the
empty string instead of (for example) "Nothing":
>>>
maybe "" show (Just 5)
"5">>>
maybe "" show Nothing
""
uncurry :: (a -> b -> c) -> (a, b) -> c #
uncurry
converts a curried function to a function on pairs.
Examples
>>>
uncurry (+) (1,2)
3
>>>
uncurry ($) (show, 1)
"1"
>>>
map (uncurry max) [(1,2), (3,4), (6,8)]
[2,4,8]
until :: (a -> Bool) -> (a -> a) -> a -> a #
yields the result of applying until
p ff
until p
holds.
($!) :: (a -> b) -> a -> b infixr 0 #
Strict (call-by-value) application operator. It takes a function and an argument, evaluates the argument to weak head normal form (WHNF), then calls the function with that value.
flip :: (a -> b -> c) -> b -> a -> c #
takes its (first) two arguments in the reverse order of flip
ff
.
>>>
flip (++) "hello" "world"
"worldhello"
const x
is a unary function which evaluates to x
for all inputs.
>>>
const 42 "hello"
42
>>>
map (const 42) [0..3]
[42,42,42,42]
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 #
Same as >>=
, but with the arguments interchanged.
errorWithoutStackTrace :: [Char] -> a #
A variant of error
that does not produce a stack trace.
Since: 4.9.0.0
error :: HasCallStack => [Char] -> a #
error
stops execution and displays an error message.