Safe Haskell | None |
---|---|
Language | Haskell2010 |
Stack.Prelude
Synopsis
- withSourceFile :: MonadUnliftIO m => FilePath -> (ConduitM i ByteString m () -> m a) -> m a
- withSinkFile :: MonadUnliftIO m => FilePath -> (ConduitM ByteString o m () -> m a) -> m a
- withSinkFileCautious :: MonadUnliftIO m => FilePath -> (ConduitM ByteString o m () -> m a) -> m a
- withSystemTempDir :: MonadUnliftIO m => String -> (Path Abs Dir -> m a) -> m a
- withKeepSystemTempDir :: MonadUnliftIO m => String -> (Path Abs Dir -> m a) -> m a
- sinkProcessStderrStdout :: forall e o env. (HasProcessContext env, HasLogFunc env, HasCallStack) => String -> [String] -> ConduitM ByteString Void (RIO env) e -> ConduitM ByteString Void (RIO env) o -> RIO env (e, o)
- sinkProcessStdout :: (HasProcessContext env, HasLogFunc env, HasCallStack) => String -> [String] -> ConduitM ByteString Void (RIO env) a -> RIO env a
- logProcessStderrStdout :: (HasCallStack, HasProcessContext env, HasLogFunc env) => ProcessConfig stdin stdoutIgnored stderrIgnored -> RIO env ()
- readProcessNull :: (HasProcessContext env, HasLogFunc env, HasCallStack) => String -> [String] -> RIO env ()
- withProcessContext :: HasProcessContext env => ProcessContext -> RIO env a -> RIO env a
- stripCR :: Text -> Text
- hIsTerminalDeviceOrMinTTY :: MonadIO m => Handle -> m Bool
- prompt :: MonadIO m => Text -> m Text
- promptPassword :: MonadIO m => Text -> m Text
- promptBool :: MonadIO m => Text -> m Bool
- (++) :: [a] -> [a] -> [a]
- seq :: a -> b -> b
- filter :: (a -> Bool) -> [a] -> [a]
- zip :: [a] -> [b] -> [(a, b)]
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- otherwise :: Bool
- assert :: Bool -> a -> a
- map :: (a -> b) -> [a] -> [b]
- ($) :: (a -> b) -> a -> b
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- guard :: Alternative f => Bool -> f ()
- join :: Monad m => m (m a) -> m a
- class Bounded a where
- class Enum a where
- class Eq a where
- class Fractional a => Floating a where
- class Num a => Fractional a where
- (/) :: a -> a -> a
- recip :: a -> a
- fromRational :: Rational -> a
- class (Real a, Enum a) => Integral a where
- class Applicative m => Monad (m :: Type -> Type) where
- class Typeable a => Data a where
- gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a
- gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a
- toConstr :: a -> Constr
- dataTypeOf :: a -> DataType
- dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)
- dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)
- gmapT :: (forall b. Data b => b -> b) -> a -> a
- gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r
- gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r
- gmapQ :: (forall d. Data d => d -> u) -> a -> [u]
- gmapQi :: Int -> (forall d. Data d => d -> u) -> a -> u
- gmapM :: Monad m => (forall d. Data d => d -> m d) -> a -> m a
- gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a
- gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a
- class Functor (f :: Type -> Type) where
- class Num a where
- class Eq a => Ord a where
- class Read a
- class (Num a, Ord a) => Real a where
- toRational :: a -> Rational
- class (RealFrac a, Floating a) => RealFloat a where
- floatRadix :: a -> Integer
- floatDigits :: a -> Int
- floatRange :: a -> (Int, Int)
- decodeFloat :: a -> (Integer, Int)
- encodeFloat :: Integer -> Int -> a
- exponent :: a -> Int
- significand :: a -> a
- scaleFloat :: Int -> a -> a
- isNaN :: a -> Bool
- isInfinite :: a -> Bool
- isDenormalized :: a -> Bool
- isNegativeZero :: a -> Bool
- isIEEE :: a -> Bool
- atan2 :: a -> a -> a
- class (Real a, Fractional a) => RealFrac a where
- class Show a where
- class Typeable (a :: k)
- class IsString a where
- fromString :: String -> a
- class Functor f => Applicative (f :: Type -> Type) where
- class Foldable (t :: Type -> Type) where
- class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- sequenceA :: Applicative f => t (f a) -> f (t a)
- mapM :: Monad m => (a -> m b) -> t a -> m (t b)
- sequence :: Monad m => t (m a) -> m (t a)
- class Generic a
- class Semigroup a where
- class Semigroup a => Monoid a where
- data Bool
- data Char
- data Double
- data Float
- data Int
- data Int8
- data Int16
- data Int32
- data Int64
- data Integer
- data Natural
- data Maybe a
- data Ordering
- type Rational = Ratio Integer
- data IO a
- data Word
- data Word8
- data Word16
- data Word32
- data Word64
- data Either a b
- data CallStack
- data ShortByteString
- data ByteString
- byteSwap16 :: Word16 -> Word16
- byteSwap32 :: Word32 -> Word32
- byteSwap64 :: Word64 -> Word64
- class NFData a where
- rnf :: a -> ()
- data Map k a
- not :: Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- (&&) :: Bool -> Bool -> Bool
- error :: HasCallStack => [Char] -> a
- undefined :: HasCallStack => a
- type String = [Char]
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- class Applicative f => Alternative (f :: Type -> Type) where
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- when :: Applicative f => Bool -> f () -> f ()
- liftM :: Monad m => (a1 -> r) -> m a1 -> m r
- liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- id :: a -> a
- const :: a -> b -> a
- (.) :: (b -> c) -> (a -> b) -> a -> c
- flip :: (a -> b -> c) -> b -> a -> c
- ($!) :: (a -> b) -> a -> b
- asTypeOf :: a -> a -> a
- subtract :: Num a => a -> a -> a
- curry :: ((a, b) -> c) -> a -> b -> c
- uncurry :: (a -> b -> c) -> (a, b) -> c
- maybe :: b -> (a -> b) -> Maybe a -> b
- isJust :: Maybe a -> Bool
- isNothing :: Maybe a -> Bool
- fromMaybe :: a -> Maybe a -> a
- maybeToList :: Maybe a -> [a]
- listToMaybe :: [a] -> Maybe a
- catMaybes :: [Maybe a] -> [a]
- mapMaybe :: (a -> Maybe b) -> [a] -> [b]
- replicate :: Int -> a -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- take :: Int -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- reverse :: [a] -> [a]
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- even :: Integral a => a -> Bool
- odd :: Integral a => a -> Bool
- (^) :: (Num a, Integral b) => a -> b -> a
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- gcd :: Integral a => a -> a -> a
- lcm :: Integral a => a -> a -> a
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- void :: Functor f => f a -> f ()
- comparing :: Ord a => (b -> a) -> b -> b -> Ordering
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- lines :: String -> [String]
- unlines :: [String] -> String
- words :: String -> [String]
- unwords :: [String] -> String
- newtype Any = Any {}
- traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
- for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- concat :: Foldable t => t [a] -> [a]
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- and :: Foldable t => t Bool -> Bool
- or :: Foldable t => t Bool -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- type FilePath = String
- optional :: Alternative f => f a -> f (Maybe a)
- for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)
- filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a]
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- unless :: Applicative f => Bool -> f () -> f ()
- data Builder
- class Hashable a
- data Text
- data HashMap k v
- class Monad m => MonadThrow (m :: Type -> Type) where
- data Handle
- data ThreadId
- waitBothSTM :: Async a -> Async b -> STM (a, b)
- waitEitherSTM_ :: Async a -> Async b -> STM ()
- waitEitherSTM :: Async a -> Async b -> STM (Either a b)
- waitEitherCatchSTM :: Async a -> Async b -> STM (Either (Either SomeException a) (Either SomeException b))
- waitAnySTM :: [Async a] -> STM (Async a, a)
- waitAnyCatchSTM :: [Async a] -> STM (Async a, Either SomeException a)
- pollSTM :: Async a -> STM (Maybe (Either SomeException a))
- waitCatchSTM :: Async a -> STM (Either SomeException a)
- waitSTM :: Async a -> STM a
- data Async a
- absurd :: Void -> a
- data Void
- data Chan a
- class Monad m => MonadIO (m :: Type -> Type) where
- (<$!>) :: Monad m => (a -> b) -> m a -> m b
- replicateM_ :: Applicative m => Int -> m a -> m ()
- foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
- zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m ()
- zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c]
- forever :: Applicative f => f a -> f b
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- first :: Arrow a => a b c -> a (b, d) (c, d)
- second :: Arrow a => a b c -> a (d, b) (d, c)
- (***) :: Arrow a => a b c -> a b' c' -> a (b, b') (c, c')
- (&&&) :: Arrow a => a b c -> a b c' -> a b (c, c')
- newtype Identity a = Identity {
- runIdentity :: a
- stderr :: Handle
- stdin :: Handle
- writeTVar :: TVar a -> a -> STM ()
- readTVar :: TVar a -> STM a
- newTVar :: a -> STM (TVar a)
- data STM a
- data TVar a
- data SomeAsyncException where
- SomeAsyncException :: forall e. Exception e => e -> SomeAsyncException
- data ExitCode
- stdout :: Handle
- data BufferMode
- data SeekMode
- data IORef a
- data IOException
- class (Typeable e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
- displayException :: e -> String
- newtype Const a (b :: k) :: forall k. Type -> k -> Type = Const {
- getConst :: a
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
- asum :: (Foldable t, Alternative f) => t (f a) -> f a
- sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f ()
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- newtype First a = First {}
- newtype Endo a = Endo {
- appEndo :: a -> a
- newtype Sum a = Sum {
- getSum :: a
- readMaybe :: Read a => String -> Maybe a
- isRight :: Either a b -> Bool
- isLeft :: Either a b -> Bool
- partitionEithers :: [Either a b] -> ([a], [b])
- rights :: [Either a b] -> [b]
- lefts :: [Either a b] -> [a]
- data Proxy (t :: k) :: forall k. k -> Type = Proxy
- (>>>) :: Category cat => cat a b -> cat b c -> cat a c
- data IOMode
- class Storable a
- bool :: a -> a -> Bool -> a
- (&) :: a -> (a -> b) -> b
- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
- fix :: (a -> a) -> a
- ($>) :: Functor f => f a -> b -> f b
- (<&>) :: Functor f => f a -> (a -> b) -> f b
- data MVar a
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- liftA :: Applicative f => (a -> b) -> f a -> f b
- type HasCallStack = ?callStack :: CallStack
- data SomeException where
- SomeException :: forall e. Exception e => e -> SomeException
- fromShort :: ShortByteString -> ByteString
- toShort :: ByteString -> ShortByteString
- newtype ReaderT r (m :: k -> Type) (a :: k) :: forall k. Type -> (k -> Type) -> k -> Type = ReaderT {
- runReaderT :: r -> m a
- runConduit :: Monad m => ConduitT () Void m r -> m r
- (.|) :: Monad m => ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
- type ConduitM = ConduitT
- class MonadIO m => MonadUnliftIO (m :: Type -> Type) where
- askUnliftIO :: m (UnliftIO m)
- withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b
- class Monad m => PrimMonad (m :: Type -> Type) where
- class MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- data IntMap a
- data IntSet
- data Set a
- force :: NFData a => a -> a
- ($!!) :: NFData a => (a -> b) -> a -> b
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- to :: (s -> a) -> SimpleGetter s a
- (^.) :: s -> Getting a s a -> a
- set :: ASetter s t a b -> b -> s -> t
- over :: ASetter s t a b -> (a -> b) -> s -> t
- sets :: ((a -> b) -> s -> t) -> ASetter s t a b
- type ASetter s t a b = (a -> Identity b) -> s -> Identity t
- type ASetter' s a = ASetter s s a a
- type SimpleGetter s a = forall r. Getting r s a
- type Getting r s a = (a -> Const r a) -> s -> Const r s
- type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Lens s s a a
- asks :: MonadReader r m => (r -> a) -> m a
- class Monad m => MonadReader r (m :: Type -> Type) | m -> r where
- type Reader r = ReaderT r Identity
- runReader :: Reader r a -> r -> a
- data Abs
- data Rel
- data File
- data Dir
- toFilePath :: Path b t -> FilePath
- data Path b t
- newChan :: MonadIO m => m (Chan a)
- writeChan :: MonadIO m => Chan a -> a -> m ()
- readChan :: MonadIO m => Chan a -> m a
- dupChan :: MonadIO m => Chan a -> m (Chan a)
- getChanContents :: MonadIO m => Chan a -> m [a]
- writeList2Chan :: MonadIO m => Chan a -> [a] -> m ()
- data StringException = StringException String CallStack
- data AsyncExceptionWrapper where
- AsyncExceptionWrapper :: forall e. Exception e => e -> AsyncExceptionWrapper
- data SyncExceptionWrapper where
- SyncExceptionWrapper :: forall e. Exception e => e -> SyncExceptionWrapper
- data Handler (m :: Type -> Type) a where
- catch :: (MonadUnliftIO m, Exception e) => m a -> (e -> m a) -> m a
- catchIO :: MonadUnliftIO m => m a -> (IOException -> m a) -> m a
- catchAny :: MonadUnliftIO m => m a -> (SomeException -> m a) -> m a
- catchDeep :: (MonadUnliftIO m, Exception e, NFData a) => m a -> (e -> m a) -> m a
- catchAnyDeep :: (NFData a, MonadUnliftIO m) => m a -> (SomeException -> m a) -> m a
- catchJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a
- handle :: (MonadUnliftIO m, Exception e) => (e -> m a) -> m a -> m a
- handleIO :: MonadUnliftIO m => (IOException -> m a) -> m a -> m a
- handleAny :: MonadUnliftIO m => (SomeException -> m a) -> m a -> m a
- handleDeep :: (MonadUnliftIO m, Exception e, NFData a) => (e -> m a) -> m a -> m a
- handleAnyDeep :: (MonadUnliftIO m, NFData a) => (SomeException -> m a) -> m a -> m a
- handleJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m a
- try :: (MonadUnliftIO m, Exception e) => m a -> m (Either e a)
- tryIO :: MonadUnliftIO m => m a -> m (Either IOException a)
- tryAny :: MonadUnliftIO m => m a -> m (Either SomeException a)
- tryDeep :: (MonadUnliftIO m, Exception e, NFData a) => m a -> m (Either e a)
- tryAnyDeep :: (MonadUnliftIO m, NFData a) => m a -> m (Either SomeException a)
- tryJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> m a -> m (Either b a)
- pureTry :: a -> Either SomeException a
- pureTryDeep :: NFData a => a -> Either SomeException a
- catches :: MonadUnliftIO m => m a -> [Handler m a] -> m a
- catchesDeep :: (MonadUnliftIO m, NFData a) => m a -> [Handler m a] -> m a
- evaluate :: MonadIO m => a -> m a
- evaluateDeep :: (MonadIO m, NFData a) => a -> m a
- bracket :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> m c) -> m c
- bracket_ :: MonadUnliftIO m => m a -> m b -> m c -> m c
- bracketOnError :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> m c) -> m c
- bracketOnError_ :: MonadUnliftIO m => m a -> m b -> m c -> m c
- finally :: MonadUnliftIO m => m a -> m b -> m a
- withException :: (MonadUnliftIO m, Exception e) => m a -> (e -> m b) -> m a
- onException :: MonadUnliftIO m => m a -> m b -> m a
- throwIO :: (MonadIO m, Exception e) => e -> m a
- toSyncException :: Exception e => e -> SomeException
- toAsyncException :: Exception e => e -> SomeException
- isSyncException :: Exception e => e -> Bool
- isAsyncException :: Exception e => e -> Bool
- mask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b
- uninterruptibleMask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b
- mask_ :: MonadUnliftIO m => m a -> m a
- uninterruptibleMask_ :: MonadUnliftIO m => m a -> m a
- throwString :: (MonadIO m, HasCallStack) => String -> m a
- stringException :: HasCallStack -> String -> StringException
- throwTo :: (Exception e, MonadIO m) => ThreadId -> e -> m ()
- impureThrow :: Exception e => e -> a
- fromEither :: (Exception e, MonadIO m) => Either e a -> m a
- fromEitherIO :: (Exception e, MonadIO m) => IO (Either e a) -> m a
- fromEitherM :: (Exception e, MonadIO m) => m (Either e a) -> m a
- newtype Concurrently (m :: Type -> Type) a = Concurrently {
- runConcurrently :: m a
- async :: MonadUnliftIO m => m a -> m (Async a)
- asyncBound :: MonadUnliftIO m => m a -> m (Async a)
- asyncOn :: MonadUnliftIO m => Int -> m a -> m (Async a)
- asyncWithUnmask :: MonadUnliftIO m => ((forall b. m b -> m b) -> m a) -> m (Async a)
- asyncOnWithUnmask :: MonadUnliftIO m => Int -> ((forall b. m b -> m b) -> m a) -> m (Async a)
- withAsync :: MonadUnliftIO m => m a -> (Async a -> m b) -> m b
- withAsyncBound :: MonadUnliftIO m => m a -> (Async a -> m b) -> m b
- withAsyncOn :: MonadUnliftIO m => Int -> m a -> (Async a -> m b) -> m b
- withAsyncWithUnmask :: MonadUnliftIO m => ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
- withAsyncOnWithUnmask :: MonadUnliftIO m => Int -> ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
- wait :: MonadIO m => Async a -> m a
- poll :: MonadIO m => Async a -> m (Maybe (Either SomeException a))
- waitCatch :: MonadIO m => Async a -> m (Either SomeException a)
- cancel :: MonadIO m => Async a -> m ()
- uninterruptibleCancel :: MonadIO m => Async a -> m ()
- cancelWith :: (Exception e, MonadIO m) => Async a -> e -> m ()
- waitAny :: MonadIO m => [Async a] -> m (Async a, a)
- waitAnyCatch :: MonadIO m => [Async a] -> m (Async a, Either SomeException a)
- waitAnyCancel :: MonadIO m => [Async a] -> m (Async a, a)
- waitAnyCatchCancel :: MonadIO m => [Async a] -> m (Async a, Either SomeException a)
- waitEither :: MonadIO m => Async a -> Async b -> m (Either a b)
- waitEitherCatch :: MonadIO m => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b))
- waitEitherCancel :: MonadIO m => Async a -> Async b -> m (Either a b)
- waitEitherCatchCancel :: MonadIO m => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b))
- waitEither_ :: MonadIO m => Async a -> Async b -> m ()
- waitBoth :: MonadIO m => Async a -> Async b -> m (a, b)
- link :: MonadIO m => Async a -> m ()
- link2 :: MonadIO m => Async a -> Async b -> m ()
- race :: MonadUnliftIO m => m a -> m b -> m (Either a b)
- race_ :: MonadUnliftIO m => m a -> m b -> m ()
- concurrently :: MonadUnliftIO m => m a -> m b -> m (a, b)
- concurrently_ :: MonadUnliftIO m => m a -> m b -> m ()
- mapConcurrently :: (MonadUnliftIO m, Traversable t) => (a -> m b) -> t a -> m (t b)
- forConcurrently :: (MonadUnliftIO m, Traversable t) => t a -> (a -> m b) -> m (t b)
- mapConcurrently_ :: (MonadUnliftIO m, Foldable f) => (a -> m b) -> f a -> m ()
- forConcurrently_ :: (MonadUnliftIO m, Foldable f) => f a -> (a -> m b) -> m ()
- replicateConcurrently :: MonadUnliftIO m => Int -> m a -> m [a]
- replicateConcurrently_ :: MonadUnliftIO m => Int -> m a -> m ()
- withFile :: MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m a) -> m a
- withBinaryFile :: MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m a) -> m a
- hClose :: MonadIO m => Handle -> m ()
- hFlush :: MonadIO m => Handle -> m ()
- hFileSize :: MonadIO m => Handle -> m Integer
- hSetFileSize :: MonadIO m => Handle -> Integer -> m ()
- hIsEOF :: MonadIO m => Handle -> m Bool
- hSetBuffering :: MonadIO m => Handle -> BufferMode -> m ()
- hGetBuffering :: MonadIO m => Handle -> m BufferMode
- hSeek :: MonadIO m => Handle -> SeekMode -> Integer -> m ()
- hTell :: MonadIO m => Handle -> m Integer
- hIsOpen :: MonadIO m => Handle -> m Bool
- hIsClosed :: MonadIO m => Handle -> m Bool
- hIsReadable :: MonadIO m => Handle -> m Bool
- hIsWritable :: MonadIO m => Handle -> m Bool
- hIsSeekable :: MonadIO m => Handle -> m Bool
- hIsTerminalDevice :: MonadIO m => Handle -> m Bool
- hSetEcho :: MonadIO m => Handle -> Bool -> m ()
- hGetEcho :: MonadIO m => Handle -> m Bool
- hWaitForInput :: MonadIO m => Handle -> Int -> m Bool
- hReady :: MonadIO m => Handle -> m Bool
- getMonotonicTime :: MonadIO m => m Double
- newIORef :: MonadIO m => a -> m (IORef a)
- readIORef :: MonadIO m => IORef a -> m a
- writeIORef :: MonadIO m => IORef a -> a -> m ()
- modifyIORef :: MonadIO m => IORef a -> (a -> a) -> m ()
- modifyIORef' :: MonadIO m => IORef a -> (a -> a) -> m ()
- atomicModifyIORef :: MonadIO m => IORef a -> (a -> (a, b)) -> m b
- atomicModifyIORef' :: MonadIO m => IORef a -> (a -> (a, b)) -> m b
- atomicWriteIORef :: MonadIO m => IORef a -> a -> m ()
- mkWeakIORef :: MonadUnliftIO m => IORef a -> m () -> m (Weak (IORef a))
- newEmptyMVar :: MonadIO m => m (MVar a)
- newMVar :: MonadIO m => a -> m (MVar a)
- takeMVar :: MonadIO m => MVar a -> m a
- putMVar :: MonadIO m => MVar a -> a -> m ()
- readMVar :: MonadIO m => MVar a -> m a
- swapMVar :: MonadIO m => MVar a -> a -> m a
- tryTakeMVar :: MonadIO m => MVar a -> m (Maybe a)
- tryPutMVar :: MonadIO m => MVar a -> a -> m Bool
- isEmptyMVar :: MonadIO m => MVar a -> m Bool
- tryReadMVar :: MonadIO m => MVar a -> m (Maybe a)
- withMVar :: MonadUnliftIO m => MVar a -> (a -> m b) -> m b
- withMVarMasked :: MonadUnliftIO m => MVar a -> (a -> m b) -> m b
- modifyMVar_ :: MonadUnliftIO m => MVar a -> (a -> m a) -> m ()
- modifyMVar :: MonadUnliftIO m => MVar a -> (a -> m (a, b)) -> m b
- modifyMVarMasked_ :: MonadUnliftIO m => MVar a -> (a -> m a) -> m ()
- modifyMVarMasked :: MonadUnliftIO m => MVar a -> (a -> m (a, b)) -> m b
- mkWeakMVar :: MonadUnliftIO m => MVar a -> m () -> m (Weak (MVar a))
- data Memoized a
- runMemoized :: MonadIO m => Memoized a -> m a
- memoizeRef :: MonadUnliftIO m => m a -> m (Memoized a)
- memoizeMVar :: MonadUnliftIO m => m a -> m (Memoized a)
- atomically :: MonadIO m => STM a -> m a
- retrySTM :: STM a
- checkSTM :: Bool -> STM ()
- newTVarIO :: MonadIO m => a -> m (TVar a)
- readTVarIO :: MonadIO m => TVar a -> m a
- registerDelay :: MonadIO m => Int -> m (TVar Bool)
- mkWeakTVar :: MonadUnliftIO m => TVar a -> m () -> m (Weak (TVar a))
- newTMVarIO :: MonadIO m => a -> m (TMVar a)
- newEmptyTMVarIO :: MonadIO m => m (TMVar a)
- mkWeakTMVar :: MonadUnliftIO m => TMVar a -> m () -> m (Weak (TMVar a))
- newTChanIO :: MonadIO m => m (TChan a)
- newBroadcastTChanIO :: MonadIO m => m (TChan a)
- newTQueueIO :: MonadIO m => m (TQueue a)
- newTBQueueIO :: MonadIO m => Natural -> m (TBQueue a)
- withSystemTempFile :: MonadUnliftIO m => String -> (FilePath -> Handle -> m a) -> m a
- withSystemTempDirectory :: MonadUnliftIO m => String -> (FilePath -> m a) -> m a
- withTempFile :: MonadUnliftIO m => FilePath -> String -> (FilePath -> Handle -> m a) -> m a
- withTempDirectory :: MonadUnliftIO m => FilePath -> String -> (FilePath -> m a) -> m a
- timeout :: MonadUnliftIO m => Int -> m a -> m (Maybe a)
- wrappedWithRunInIO :: MonadUnliftIO n => (n b -> m b) -> (forall a. m a -> n a) -> ((forall a. m a -> IO a) -> IO b) -> m b
- toIO :: MonadUnliftIO m => m a -> m (IO a)
- withUnliftIO :: MonadUnliftIO m => (UnliftIO m -> IO a) -> m a
- askRunInIO :: MonadUnliftIO m => m (m a -> IO a)
- newtype UnliftIO (m :: Type -> Type) = UnliftIO {}
- data TBQueue a
- newTBQueue :: Natural -> STM (TBQueue a)
- writeTBQueue :: TBQueue a -> a -> STM ()
- readTBQueue :: TBQueue a -> STM a
- tryReadTBQueue :: TBQueue a -> STM (Maybe a)
- peekTBQueue :: TBQueue a -> STM a
- tryPeekTBQueue :: TBQueue a -> STM (Maybe a)
- unGetTBQueue :: TBQueue a -> a -> STM ()
- isEmptyTBQueue :: TBQueue a -> STM Bool
- isFullTBQueue :: TBQueue a -> STM Bool
- data TChan a
- newTChan :: STM (TChan a)
- newBroadcastTChan :: STM (TChan a)
- writeTChan :: TChan a -> a -> STM ()
- readTChan :: TChan a -> STM a
- tryReadTChan :: TChan a -> STM (Maybe a)
- peekTChan :: TChan a -> STM a
- tryPeekTChan :: TChan a -> STM (Maybe a)
- dupTChan :: TChan a -> STM (TChan a)
- unGetTChan :: TChan a -> a -> STM ()
- isEmptyTChan :: TChan a -> STM Bool
- cloneTChan :: TChan a -> STM (TChan a)
- data TMVar a
- newTMVar :: a -> STM (TMVar a)
- newEmptyTMVar :: STM (TMVar a)
- takeTMVar :: TMVar a -> STM a
- tryTakeTMVar :: TMVar a -> STM (Maybe a)
- putTMVar :: TMVar a -> a -> STM ()
- tryPutTMVar :: TMVar a -> a -> STM Bool
- readTMVar :: TMVar a -> STM a
- tryReadTMVar :: TMVar a -> STM (Maybe a)
- swapTMVar :: TMVar a -> a -> STM a
- isEmptyTMVar :: TMVar a -> STM Bool
- data TQueue a
- newTQueue :: STM (TQueue a)
- writeTQueue :: TQueue a -> a -> STM ()
- readTQueue :: TQueue a -> STM a
- tryReadTQueue :: TQueue a -> STM (Maybe a)
- peekTQueue :: TQueue a -> STM a
- tryPeekTQueue :: TQueue a -> STM (Maybe a)
- unGetTQueue :: TQueue a -> a -> STM ()
- isEmptyTQueue :: TQueue a -> STM Bool
- modifyTVar :: TVar a -> (a -> a) -> STM ()
- modifyTVar' :: TVar a -> (a -> a) -> STM ()
- swapTVar :: TVar a -> a -> STM a
- traceDisplayStack :: Display a => a -> b -> b
- traceDisplayMarkerIO :: (Display a, MonadIO m) => a -> m ()
- traceDisplayMarker :: Display a => a -> b -> b
- traceDisplayEventIO :: (Display a, MonadIO m) => a -> m ()
- traceDisplayEvent :: Display a => a -> b -> b
- traceDisplayM :: (Display a, Applicative f) => a -> f ()
- traceDisplayIO :: (Display a, MonadIO m) => a -> m ()
- traceDisplayId :: Display a => a -> a
- traceDisplay :: Display a => a -> b -> b
- traceShowStack :: Show a => a -> b -> b
- traceShowMarkerIO :: (Show a, MonadIO m) => a -> m ()
- traceShowMarker :: Show a => a -> b -> b
- traceShowEventIO :: (Show a, MonadIO m) => a -> m ()
- traceShowEvent :: Show a => a -> b -> b
- traceShowM :: (Show a, Applicative f) => a -> f ()
- traceShowIO :: (Show a, MonadIO m) => a -> m ()
- traceShowId :: Show a => a -> a
- traceShow :: Show a => a -> b -> b
- traceStack :: Text -> a -> a
- traceMarkerIO :: MonadIO m => Text -> m ()
- traceMarker :: Text -> a -> a
- traceEventIO :: MonadIO m => Text -> m ()
- traceEvent :: Text -> a -> a
- traceM :: Applicative f => Text -> f ()
- traceIO :: MonadIO m => Text -> m ()
- traceId :: Text -> Text
- trace :: Text -> a -> a
- runSimpleApp :: MonadIO m => RIO SimpleApp a -> m a
- data SimpleApp
- newUnboxedSomeRef :: (MonadIO m, Unbox a) => a -> m (SomeRef a)
- newSomeRef :: MonadIO m => a -> m (SomeRef a)
- modifySomeRef :: MonadIO m => SomeRef a -> (a -> a) -> m ()
- writeSomeRef :: MonadIO m => SomeRef a -> a -> m ()
- readSomeRef :: MonadIO m => SomeRef a -> m a
- liftRIO :: (MonadIO m, MonadReader env m) => RIO env a -> m a
- runRIO :: MonadIO m => env -> RIO env a -> m a
- newtype RIO env a = RIO {}
- data SomeRef a
- class HasStateRef s env | env -> s where
- class HasWriteRef w env | env -> w where
- modifyURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> (a -> a) -> m ()
- writeURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> a -> m ()
- readURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> m a
- newURef :: (PrimMonad m, Unbox a) => a -> m (URef (PrimState m) a)
- data URef s a
- type IOURef = URef (PrimState IO)
- decodeUtf8Lenient :: ByteString -> Text
- tshow :: Show a => a -> Text
- noLogging :: (HasLogFunc env, MonadReader env m) => m a -> m a
- logFuncUseColorL :: HasLogFunc env => SimpleGetter env Bool
- displayCallStack :: CallStack -> Utf8Builder
- setLogUseLoc :: Bool -> LogOptions -> LogOptions
- setLogUseColor :: Bool -> LogOptions -> LogOptions
- setLogUseTime :: Bool -> LogOptions -> LogOptions
- setLogTerminal :: Bool -> LogOptions -> LogOptions
- setLogVerboseFormatIO :: IO Bool -> LogOptions -> LogOptions
- setLogVerboseFormat :: Bool -> LogOptions -> LogOptions
- setLogMinLevelIO :: IO LogLevel -> LogOptions -> LogOptions
- setLogMinLevel :: LogLevel -> LogOptions -> LogOptions
- withLogFunc :: MonadUnliftIO m => LogOptions -> (LogFunc -> m a) -> m a
- newLogFunc :: (MonadIO n, MonadIO m) => LogOptions -> n (LogFunc, m ())
- logOptionsHandle :: MonadIO m => Handle -> Bool -> m LogOptions
- logOptionsMemory :: MonadIO m => m (IORef Builder, LogOptions)
- logStickyDone :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => Utf8Builder -> m ()
- logSticky :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => Utf8Builder -> m ()
- logOtherS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Text -> LogSource -> Utf8Builder -> m ()
- logErrorS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m ()
- logWarnS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m ()
- logInfoS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m ()
- logDebugS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m ()
- logOther :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Text -> Utf8Builder -> m ()
- logError :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m ()
- logWarn :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m ()
- logInfo :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m ()
- logDebug :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m ()
- logGeneric :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogLevel -> Utf8Builder -> m ()
- mkLogFunc :: (CallStack -> LogSource -> LogLevel -> Utf8Builder -> IO ()) -> LogFunc
- data LogLevel
- type LogSource = Text
- class HasLogFunc env where
- data LogFunc
- data LogOptions
- fromStrictBytes :: ByteString -> LByteString
- toStrictBytes :: LByteString -> ByteString
- sappend :: Semigroup s => s -> s -> s
- type UVector = Vector
- type SVector = Vector
- type GVector = Vector
- type LByteString = ByteString
- type LText = Text
- asIO :: IO a -> IO a
- unlessM :: Monad m => m Bool -> m () -> m ()
- whenM :: Monad m => m Bool -> m () -> m ()
- nubOrd :: Ord a => [a] -> [a]
- foldMapM :: (Monad m, Monoid w, Foldable t) => (a -> m w) -> t a -> m w
- forMaybeM :: Monad m => [a] -> (a -> m (Maybe b)) -> m [b]
- mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b]
- forMaybeA :: Applicative f => [a] -> (a -> f (Maybe b)) -> f [b]
- mapMaybeA :: Applicative f => (a -> f (Maybe b)) -> [a] -> f [b]
- fromFirst :: a -> First a -> a
- mapLeft :: (a1 -> a2) -> Either a1 b -> Either a2 b
- readFileUtf8 :: MonadIO m => FilePath -> m Text
- writeFileBinary :: MonadIO m => FilePath -> ByteString -> m ()
- readFileBinary :: MonadIO m => FilePath -> m ByteString
- hPutBuilder :: MonadIO m => Handle -> Builder -> m ()
- writeFileUtf8 :: MonadIO m => FilePath -> Text -> m ()
- withLazyFile :: MonadUnliftIO m => FilePath -> (ByteString -> m a) -> m a
- yieldThread :: MonadIO m => m ()
- view :: MonadReader s m => Getting a s a -> m a
- writeFileUtf8Builder :: MonadIO m => FilePath -> Utf8Builder -> m ()
- utf8BuilderToLazyText :: Utf8Builder -> Text
- utf8BuilderToText :: Utf8Builder -> Text
- displayBytesUtf8 :: ByteString -> Utf8Builder
- displayShow :: Show a => a -> Utf8Builder
- newtype Utf8Builder = Utf8Builder {}
- class Display a where
- display :: a -> Utf8Builder
- data Vector a
- class (Vector Vector a, MVector MVector a) => Unbox a
- data HashSet a
- myThreadId :: MonadIO m => m ThreadId
- threadDelay :: MonadIO m => Int -> m ()
- threadWaitRead :: MonadIO m => Fd -> m ()
- threadWaitWrite :: MonadIO m => Fd -> m ()
- isCurrentThreadBound :: MonadIO m => m Bool
- data UnicodeException
- = DecodeError String (Maybe Word8)
- | EncodeError String (Maybe Char)
- lenientDecode :: OnDecodeError
- decodeUtf8With :: OnDecodeError -> ByteString -> Text
- decodeUtf8' :: ByteString -> Either UnicodeException Text
- encodeUtf8Builder :: Text -> Builder
- encodeUtf8 :: Text -> ByteString
- class Store a
Documentation
withSourceFile :: MonadUnliftIO m => FilePath -> (ConduitM i ByteString m () -> m a) -> m a Source #
Get a source for a file. Unlike sourceFile
, doesn't require
ResourceT
. Unlike explicit withBinaryFile
and sourceHandle
usage, you can't accidentally use WriteMode
instead of
ReadMode
.
withSinkFile :: MonadUnliftIO m => FilePath -> (ConduitM ByteString o m () -> m a) -> m a Source #
Same idea as withSourceFile
, see comments there.
withSinkFileCautious :: MonadUnliftIO m => FilePath -> (ConduitM ByteString o m () -> m a) -> m a Source #
Like withSinkFile
, but ensures that the file is atomically
moved after all contents are written.
withSystemTempDir :: MonadUnliftIO m => String -> (Path Abs Dir -> m a) -> m a Source #
Path version
withKeepSystemTempDir :: MonadUnliftIO m => String -> (Path Abs Dir -> m a) -> m a Source #
Like withSystemTempDir
, but the temporary directory is not deleted.
sinkProcessStderrStdout Source #
Arguments
:: (HasProcessContext env, HasLogFunc env, HasCallStack) | |
=> String | Command |
-> [String] | Command line arguments |
-> ConduitM ByteString Void (RIO env) e | Sink for stderr |
-> ConduitM ByteString Void (RIO env) o | Sink for stdout |
-> RIO env (e, o) |
Consume the stdout and stderr of a process feeding strict ByteString
s to the consumers.
Throws a ReadProcessException
if unsuccessful in launching, or ProcessExitedUnsuccessfully
if the process itself fails.
Arguments
:: (HasProcessContext env, HasLogFunc env, HasCallStack) | |
=> String | Command |
-> [String] | Command line arguments |
-> ConduitM ByteString Void (RIO env) a | Sink for stdout |
-> RIO env a |
Consume the stdout of a process feeding strict ByteString
s to a consumer.
If the process fails, spits out stdout and stderr as error log
level. Should not be used for long-running processes or ones with
lots of output; for that use sinkProcessStderrStdout
.
Throws a ReadProcessException
if unsuccessful.
logProcessStderrStdout :: (HasCallStack, HasProcessContext env, HasLogFunc env) => ProcessConfig stdin stdoutIgnored stderrIgnored -> RIO env () Source #
Arguments
:: (HasProcessContext env, HasLogFunc env, HasCallStack) | |
=> String | Command |
-> [String] | Command line arguments |
-> RIO env () |
Read from the process, ignoring any output.
Throws a ReadProcessException
exception if the process fails.
withProcessContext :: HasProcessContext env => ProcessContext -> RIO env a -> RIO env a Source #
Use the new ProcessContext
, but retain the working directory
from the parent environment.
hIsTerminalDeviceOrMinTTY :: MonadIO m => Handle -> m Bool Source #
hIsTerminaDevice does not recognise handles to mintty terminals as terminal devices, but isMinTTYHandle does.
prompt :: MonadIO m => Text -> m Text Source #
Prompt the user by sending text to stdout, and taking a line of input from stdin.
promptPassword :: MonadIO m => Text -> m Text Source #
Prompt the user by sending text to stdout, and collecting a line of input from stdin. While taking input from stdin, input echoing is disabled, to hide passwords.
Based on code from cabal-install, Distribution.Client.Upload
promptBool :: MonadIO m => Text -> m Bool Source #
Prompt the user by sending text to stdout, and collecting a line of input from stdin. If something other than "y" or "n" is entered, then print a message indicating that "y" or "n" is expected, and ask again.
(++) :: [a] -> [a] -> [a] infixr 5 #
Append two lists, i.e.,
[x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
If the first list is not finite, the result is the first list.
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]
If the first argument evaluates to True
, then the result is the
second argument. Otherwise an AssertionFailed
exception is raised,
containing a String
with the source file and line number of the
call to assert
.
Assertions can normally be turned on or off with a compiler flag
(for GHC, assertions are normally on unless optimisation is turned on
with -O
or the -fignore-asserts
option is given). When assertions are turned off, the first
argument to assert
is ignored, and the second argument is
returned as the result.
map :: (a -> b) -> [a] -> [b] #
map
f xs
is the list obtained by applying f
to each element
of xs
, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
($) :: (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
Note that ($)
is levity-polymorphic in its result type, so that
foo $ True where foo :: Bool -> Int#
is well-typed
fromIntegral :: (Integral a, Num b) => a -> b #
general coercion from integral types
realToFrac :: (Real a, Fractional b) => a -> b #
general coercion to fractional types
guard :: Alternative f => Bool -> f () #
Conditional failure of Alternative
computations. Defined by
guard True =pure
() guard False =empty
Examples
Common uses of guard
include conditionally signaling an error in
an error monad and conditionally rejecting the current choice in an
Alternative
-based parser.
As an example of signaling an error in the error monad Maybe
,
consider a safe division function safeDiv x y
that returns
Nothing
when the denominator y
is zero and
otherwise. For example:Just
(x `div`
y)
>>> safeDiv 4 0 Nothing >>> safeDiv 4 2 Just 2
A definition of safeDiv
using guards, but not guard
:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y | y /= 0 = Just (x `div` y) | otherwise = Nothing
A definition of safeDiv
using guard
and Monad
do
-notation:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y = do guard (y /= 0) return (x `div` y)
join :: Monad m => m (m a) -> m a #
The join
function is the conventional monad join operator. It
is used to remove one level of monadic structure, projecting its
bound argument into the outer level.
Examples
A common use of join
is to run an IO
computation returned from
an STM
transaction, since STM
transactions
can't perform IO
directly. Recall that
atomically
:: STM a -> IO a
is used to run STM
transactions atomically. So, by
specializing the types of atomically
and join
to
atomically
:: STM (IO b) -> IO (IO b)join
:: IO (IO b) -> IO b
we can compose them as
join
.atomically
:: STM (IO b) -> IO b
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
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
.
The Haskell Report defines no laws for Eq
. However, ==
is customarily
expected to implement an equivalence relationship where two values comparing
equal are indistinguishable by "public" functions, with a "public" function
being one not allowing to see implementation details. For example, for a
type representing non-normalised natural numbers modulo 100, a "public"
function doesn't make the difference between 1 and 201. It is expected to
have the following properties:
Instances
class Fractional a => Floating a where #
Trigonometric and hyperbolic functions and related functions.
The Haskell Report defines no laws for Floating
. However, '(+)', '(*)'
and exp
are customarily expected to define an exponential field and have
the following properties:
exp (a + b)
= @exp a * exp bexp (fromInteger 0)
=fromInteger 1
Minimal complete definition
pi, exp, log, sin, cos, asin, acos, atan, sinh, cosh, asinh, acosh, atanh
Instances
class Num a => Fractional a where #
Fractional numbers, supporting real division.
The Haskell Report defines no laws for Fractional
. However, '(+)' and
'(*)' are customarily expected to define a division ring and have the
following properties:
recip
gives the multiplicative inversex * recip x
=recip x * x
=fromInteger 1
Note that it isn't customarily expected that a type instance of
Fractional
implement a field. However, all instances in base
do.
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
class (Real a, Enum a) => Integral a where #
Integral numbers, supporting integer division.
The Haskell Report defines no laws for Integral
. However, Integral
instances are customarily expected to define a Euclidean domain and have the
following properties for the 'div'/'mod' and 'quot'/'rem' pairs, given
suitable Euclidean functions f
and g
:
x
=y * quot x y + rem x y
withrem x y
=fromInteger 0
org (rem x y)
<g y
x
=y * div x y + mod x y
withmod x y
=fromInteger 0
orf (mod x y)
<f y
An example of a suitable Euclidean function, for Integer
's instance, is
abs
.
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 :: Type -> Type) 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: base-2.1 |
Monad Maybe | Since: base-2.1 |
Monad IO | Since: base-2.1 |
Monad Par1 | Since: base-4.9.0.0 |
Monad Q | |
Monad Last | Since: base-4.9.0.0 |
Monad ParseResult | |
Defined in Distribution.Parsec.ParseResult Methods (>>=) :: ParseResult a -> (a -> ParseResult b) -> ParseResult b # (>>) :: ParseResult a -> ParseResult b -> ParseResult b # return :: a -> ParseResult a # fail :: String -> ParseResult a # | |
Monad ParseResult | |
Defined in Distribution.ParseUtils Methods (>>=) :: ParseResult a -> (a -> ParseResult b) -> ParseResult b # (>>) :: ParseResult a -> ParseResult b -> ParseResult b # return :: a -> ParseResult a # fail :: String -> ParseResult a # | |
Monad Condition | |
Monad IResult | |
Monad Result | |
Monad Parser | |
Monad Complex | Since: base-4.9.0.0 |
Monad Min | Since: base-4.9.0.0 |
Monad Max | Since: base-4.9.0.0 |
Monad First | Since: base-4.9.0.0 |
Monad Option | Since: base-4.9.0.0 |
Monad Identity | Since: base-4.8.0.0 |
Monad STM | Since: base-4.3.0.0 |
Monad First | Since: base-4.8.0.0 |
Monad Last | Since: base-4.8.0.0 |
Monad Dual | Since: base-4.8.0.0 |
Monad Sum | Since: base-4.8.0.0 |
Monad Product | Since: base-4.8.0.0 |
Monad Down | Since: base-4.11.0.0 |
Monad ReadPrec | Since: base-2.1 |
Monad ReadP | Since: base-2.1 |
Monad NonEmpty | Since: base-4.9.0.0 |
Monad Put | |
Monad Tree | |
Monad Seq | |
Monad CryptoFailable | |
Defined in Crypto.Error.Types Methods (>>=) :: CryptoFailable a -> (a -> CryptoFailable b) -> CryptoFailable b # (>>) :: CryptoFailable a -> CryptoFailable b -> CryptoFailable b # return :: a -> CryptoFailable a # fail :: String -> CryptoFailable a # | |
Monad DList | |
Monad SubM | |
Monad ReadM | |
Monad ParserM | |
Monad ParserResult | |
Defined in Options.Applicative.Types Methods (>>=) :: ParserResult a -> (a -> ParserResult b) -> ParserResult b # (>>) :: ParserResult a -> ParserResult b -> ParserResult b # return :: a -> ParserResult a # fail :: String -> ParserResult a # | |
Monad Chunk | |
Monad SmallArray | |
Defined in Data.Primitive.SmallArray Methods (>>=) :: SmallArray a -> (a -> SmallArray b) -> SmallArray b # (>>) :: SmallArray a -> SmallArray b -> SmallArray b # return :: a -> SmallArray a # fail :: String -> SmallArray a # | |
Monad Array | |
Monad Memoized | |
Monad Vector | |
Monad Sh | |
Monad Peek | |
Monad Poke | |
Monad Id | |
Monad Box | |
Monad Stream | |
Monad P | Since: base-2.1 |
Monad (Either e) | Since: base-4.4.0.0 |
Monad (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Monoid a => Monad ((,) a) | Since: base-4.9.0.0 |
Monad (ST s) | Since: base-2.1 |
Monad (Parser i) | |
Monad m => Monad (WrappedMonad m) | Since: base-4.7.0.0 |
Defined in Control.Applicative 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: base-2.1 |
Defined in Control.Arrow 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 :: Type -> Type) | Since: base-4.7.0.0 |
Monad m => Monad (MaybeT m) | |
Monad m => Monad (ResourceT m) | |
Monad m => Monad (ListT m) | |
Monad m => Monad (NoLoggingT m) | |
Defined in Control.Monad.Logger Methods (>>=) :: NoLoggingT m a -> (a -> NoLoggingT m b) -> NoLoggingT m b # (>>) :: NoLoggingT m a -> NoLoggingT m b -> NoLoggingT m b # return :: a -> NoLoggingT m a # fail :: String -> NoLoggingT m a # | |
Monad m => Monad (WriterLoggingT m) | |
Defined in Control.Monad.Logger Methods (>>=) :: WriterLoggingT m a -> (a -> WriterLoggingT m b) -> WriterLoggingT m b # (>>) :: WriterLoggingT m a -> WriterLoggingT m b -> WriterLoggingT m b # return :: a -> WriterLoggingT m a # fail :: String -> WriterLoggingT m a # | |
Monad m => Monad (LoggingT m) | |
Monad (RIO env) | |
Monad (IParser t) | |
Monad (Partial e) | |
Monad (SetM s) | |
Monad f => Monad (Rec1 f) | Since: base-4.9.0.0 |
Monad f => Monad (Ap f) | Since: base-4.12.0.0 |
Monad f => Monad (Alt f) | Since: base-4.8.0.0 |
Monad m => Monad (IdentityT m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
Monad m => Monad (StateT s m) | |
Monad m => Monad (StateT s m) | |
Monad m => Monad (ExceptT e m) | |
(Applicative f, Monad f) => Monad (WhenMissing f x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal 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 (Tagged s) | |
(Monoid w, Functor m, Monad m) => Monad (AccumT w m) | |
Monad m => Monad (SelectT r m) | |
Monad m => Monad (StateT s m) | |
Monad ((->) r :: Type -> Type) | Since: base-2.1 |
(Monad f, Monad g) => Monad (f :*: g) | Since: base-4.9.0.0 |
(Monad f, Monad g) => Monad (Product f g) | Since: base-4.9.0.0 |
Monad m => Monad (ReaderT r m) | |
Monad (ConduitT i o m) | |
(Monad f, Applicative f) => Monad (WhenMatched f x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal 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: containers-0.5.9 |
Defined in Data.Map.Internal 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 (ContT r m) | |
Monad f => Monad (M1 i c f) | Since: base-4.9.0.0 |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
(Monad f, Applicative f) => Monad (WhenMatched f k x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal 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 # | |
Monad state => Monad (Builder collection mutCollection step state err) | |
Defined in Basement.MutableBuilder Methods (>>=) :: Builder collection mutCollection step state err a -> (a -> Builder collection mutCollection step state err b) -> Builder collection mutCollection step state err b # (>>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b # return :: a -> Builder collection mutCollection step state err a # fail :: String -> Builder collection mutCollection step state err a # | |
Monad m => Monad (Pipe l i o u m) | |
class Typeable a => Data a where #
The Data
class comprehends a fundamental primitive gfoldl
for
folding over constructor applications, say terms. This primitive can
be instantiated in several ways to map over the immediate subterms
of a term; see the gmap
combinators later in this class. Indeed, a
generic programmer does not necessarily need to use the ingenious gfoldl
primitive but rather the intuitive gmap
combinators. The gfoldl
primitive is completed by means to query top-level constructors, to
turn constructor representations into proper terms, and to list all
possible datatype constructors. This completion allows us to serve
generic programming scenarios like read, show, equality, term generation.
The combinators gmapT
, gmapQ
, gmapM
, etc are all provided with
default definitions in terms of gfoldl
, leaving open the opportunity
to provide datatype-specific definitions.
(The inclusion of the gmap
combinators as members of class Data
allows the programmer or the compiler to derive specialised, and maybe
more efficient code per datatype. Note: gfoldl
is more higher-order
than the gmap
combinators. This is subject to ongoing benchmarking
experiments. It might turn out that the gmap
combinators will be
moved out of the class Data
.)
Conceptually, the definition of the gmap
combinators in terms of the
primitive gfoldl
requires the identification of the gfoldl
function
arguments. Technically, we also need to identify the type constructor
c
for the construction of the result type from the folded term type.
In the definition of gmapQ
x combinators, we use phantom type
constructors for the c
in the type of gfoldl
because the result type
of a query does not involve the (polymorphic) type of the term argument.
In the definition of gmapQl
we simply use the plain constant type
constructor because gfoldl
is left-associative anyway and so it is
readily suited to fold a left-associative binary operation over the
immediate subterms. In the definition of gmapQr, extra effort is
needed. We use a higher-order accumulation trick to mediate between
left-associative constructor application vs. right-associative binary
operation (e.g., (:)
). When the query is meant to compute a value
of type r
, then the result type withing generic folding is r -> r
.
So the result of folding is a function to which we finally pass the
right unit.
With the -XDeriveDataTypeable
option, GHC can generate instances of the
Data
class automatically. For example, given the declaration
data T a b = C1 a b | C2 deriving (Typeable, Data)
GHC will generate an instance that is equivalent to
instance (Data a, Data b) => Data (T a b) where gfoldl k z (C1 a b) = z C1 `k` a `k` b gfoldl k z C2 = z C2 gunfold k z c = case constrIndex c of 1 -> k (k (z C1)) 2 -> z C2 toConstr (C1 _ _) = con_C1 toConstr C2 = con_C2 dataTypeOf _ = ty_T con_C1 = mkConstr ty_T "C1" [] Prefix con_C2 = mkConstr ty_T "C2" [] Prefix ty_T = mkDataType "Module.T" [con_C1, con_C2]
This is suitable for datatypes that are exported transparently.
Minimal complete definition
Methods
Arguments
:: (forall d b. Data d => c (d -> b) -> d -> c b) | defines how nonempty constructor applications are folded. It takes the folded tail of the constructor application and its head, i.e., an immediate subterm, and combines them in some way. |
-> (forall g. g -> c g) | defines how the empty constructor application is folded, like the neutral / start element for list folding. |
-> a | structure to be folded. |
-> c a | result, with a type defined in terms of |
Left-associative fold operation for constructor applications.
The type of gfoldl
is a headache, but operationally it is a simple
generalisation of a list fold.
The default definition for gfoldl
is
, which is
suitable for abstract datatypes with no substructures.const
id
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a #
Unfolding constructor applications
Obtaining the constructor from a given datum. For proper terms, this is meant to be the top-level constructor. Primitive datatypes are here viewed as potentially infinite sets of values (i.e., constructors).
dataTypeOf :: a -> DataType #
The outer type constructor of the type
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a) #
Mediate types and unary type constructors.
In Data
instances of the form
instance (Data a, ...) => Data (T a)
dataCast1
should be defined as gcast1
.
The default definition is
, which is appropriate
for instances of other forms.const
Nothing
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a) #
Mediate types and binary type constructors.
In Data
instances of the form
instance (Data a, Data b, ...) => Data (T a b)
dataCast2
should be defined as gcast2
.
The default definition is
, which is appropriate
for instances of other forms.const
Nothing
gmapT :: (forall b. Data b => b -> b) -> a -> a #
A generic transformation that maps over the immediate subterms
The default definition instantiates the type constructor c
in the
type of gfoldl
to an identity datatype constructor, using the
isomorphism pair as injection and projection.
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r #
A generic query with a left-associative binary operator
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r #
A generic query with a right-associative binary operator
gmapQ :: (forall d. Data d => d -> u) -> a -> [u] #
A generic query that processes the immediate subterms and returns a list of results. The list is given in the same order as originally specified in the declaration of the data constructors.
gmapQi :: Int -> (forall d. Data d => d -> u) -> a -> u #
A generic query that processes one child by index (zero-based)
gmapM :: Monad m => (forall d. Data d => d -> m d) -> a -> m a #
A generic monadic transformation that maps over the immediate subterms
The default definition instantiates the type constructor c
in
the type of gfoldl
to the monad datatype constructor, defining
injection and projection using return
and >>=
.
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a #
Transformation of at least one immediate subterm does not fail
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a #
Transformation of one immediate subterm with success
Instances
Data Bool | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Data Char | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Data Double | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Data Float | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Data Int | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Data Int8 | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int8 -> c Int8 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int8 # dataTypeOf :: Int8 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int8) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int8) # gmapT :: (forall b. Data b => b -> b) -> Int8 -> Int8 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int8 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int8 -> r # gmapQ :: (forall d. Data d => d -> u) -> Int8 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int8 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 # | |
Data Int16 | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int16 -> c Int16 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int16 # dataTypeOf :: Int16 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int16) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int16) # gmapT :: (forall b. Data b => b -> b) -> Int16 -> Int16 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int16 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int16 -> r # gmapQ :: (forall d. Data d => d -> u) -> Int16 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int16 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 # | |
Data Int32 | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int32 -> c Int32 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int32 # dataTypeOf :: Int32 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int32) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int32) # gmapT :: (forall b. Data b => b -> b) -> Int32 -> Int32 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r # gmapQ :: (forall d. Data d => d -> u) -> Int32 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int32 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 # | |
Data Int64 | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int64 -> c Int64 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int64 # dataTypeOf :: Int64 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int64) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int64) # gmapT :: (forall b. Data b => b -> b) -> Int64 -> Int64 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r # gmapQ :: (forall d. Data d => d -> u) -> Int64 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int64 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 # | |
Data Integer | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Data Natural | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Natural -> c Natural # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Natural # toConstr :: Natural -> Constr # dataTypeOf :: Natural -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Natural) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Natural) # gmapT :: (forall b. Data b => b -> b) -> Natural -> Natural # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r # gmapQ :: (forall d. Data d => d -> u) -> Natural -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Natural -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Natural -> m Natural # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural # | |
Data Ordering | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Data Word | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Data Word8 | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word8 -> c Word8 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word8 # dataTypeOf :: Word8 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word8) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word8) # gmapT :: (forall b. Data b => b -> b) -> Word8 -> Word8 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r # gmapQ :: (forall d. Data d => d -> u) -> Word8 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word8 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 # | |
Data Word16 | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word16 -> c Word16 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word16 # toConstr :: Word16 -> Constr # dataTypeOf :: Word16 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word16) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word16) # gmapT :: (forall b. Data b => b -> b) -> Word16 -> Word16 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word16 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word16 -> r # gmapQ :: (forall d. Data d => d -> u) -> Word16 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word16 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 # | |
Data Word32 | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word32 -> c Word32 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word32 # toConstr :: Word32 -> Constr # dataTypeOf :: Word32 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word32) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word32) # gmapT :: (forall b. Data b => b -> b) -> Word32 -> Word32 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r # gmapQ :: (forall d. Data d => d -> u) -> Word32 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word32 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 # | |
Data Word64 | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word64 -> c Word64 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word64 # toConstr :: Word64 -> Constr # dataTypeOf :: Word64 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word64) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word64) # gmapT :: (forall b. Data b => b -> b) -> Word64 -> Word64 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r # gmapQ :: (forall d. Data d => d -> u) -> Word64 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word64 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 # | |
Data Exp | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exp -> c Exp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exp # dataTypeOf :: Exp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Exp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp) # gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r # gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exp -> m Exp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp # | |
Data Match | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match -> c Match # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Match # dataTypeOf :: Match -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Match) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Match) # gmapT :: (forall b. Data b => b -> b) -> Match -> Match # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match -> r # gmapQ :: (forall d. Data d => d -> u) -> Match -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match -> m Match # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match -> m Match # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match -> m Match # | |
Data Clause | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Clause -> c Clause # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Clause # toConstr :: Clause -> Constr # dataTypeOf :: Clause -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Clause) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Clause) # gmapT :: (forall b. Data b => b -> b) -> Clause -> Clause # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Clause -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Clause -> r # gmapQ :: (forall d. Data d => d -> u) -> Clause -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Clause -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Clause -> m Clause # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Clause -> m Clause # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Clause -> m Clause # | |
Data Pat | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat -> c Pat # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pat # dataTypeOf :: Pat -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pat) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pat) # gmapT :: (forall b. Data b => b -> b) -> Pat -> Pat # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat -> r # gmapQ :: (forall d. Data d => d -> u) -> Pat -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat -> m Pat # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat -> m Pat # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat -> m Pat # | |
Data Type | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type # dataTypeOf :: Type -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Type) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) # gmapT :: (forall b. Data b => b -> b) -> Type -> Type # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # | |
Data Dec | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dec -> c Dec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dec # dataTypeOf :: Dec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dec) # gmapT :: (forall b. Data b => b -> b) -> Dec -> Dec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dec -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dec -> r # gmapQ :: (forall d. Data d => d -> u) -> Dec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dec -> m Dec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dec -> m Dec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dec -> m Dec # | |
Data Name | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # dataTypeOf :: Name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) # gmapT :: (forall b. Data b => b -> b) -> Name -> Name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
Data FunDep | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunDep -> c FunDep # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunDep # toConstr :: FunDep -> Constr # dataTypeOf :: FunDep -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunDep) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunDep) # gmapT :: (forall b. Data b => b -> b) -> FunDep -> FunDep # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunDep -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunDep -> r # gmapQ :: (forall d. Data d => d -> u) -> FunDep -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunDep -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep # | |
Data InjectivityAnn | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn -> c InjectivityAnn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InjectivityAnn # toConstr :: InjectivityAnn -> Constr # dataTypeOf :: InjectivityAnn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InjectivityAnn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InjectivityAnn) # gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn -> InjectivityAnn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn -> r # gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn -> m InjectivityAnn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn -> m InjectivityAnn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn -> m InjectivityAnn # | |
Data Overlap | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Overlap -> c Overlap # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Overlap # toConstr :: Overlap -> Constr # dataTypeOf :: Overlap -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Overlap) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Overlap) # gmapT :: (forall b. Data b => b -> b) -> Overlap -> Overlap # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Overlap -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Overlap -> r # gmapQ :: (forall d. Data d => d -> u) -> Overlap -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Overlap -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Overlap -> m Overlap # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Overlap -> m Overlap # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Overlap -> m Overlap # | |
Data () | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> () -> c () # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c () # dataTypeOf :: () -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ()) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ()) # gmapT :: (forall b. Data b => b -> b) -> () -> () # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> () -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> () -> r # gmapQ :: (forall d. Data d => d -> u) -> () -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> () -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> () -> m () # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> () -> m () # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> () -> m () # | |
Data ShortTextLst | |
Defined in Distribution.ModuleName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShortTextLst -> c ShortTextLst # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShortTextLst # toConstr :: ShortTextLst -> Constr # dataTypeOf :: ShortTextLst -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ShortTextLst) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShortTextLst) # gmapT :: (forall b. Data b => b -> b) -> ShortTextLst -> ShortTextLst # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShortTextLst -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShortTextLst -> r # gmapQ :: (forall d. Data d => d -> u) -> ShortTextLst -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ShortTextLst -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShortTextLst -> m ShortTextLst # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortTextLst -> m ShortTextLst # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortTextLst -> m ShortTextLst # | |
Data Version | Since: base-4.7.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version # toConstr :: Version -> Constr # dataTypeOf :: Version -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) # gmapT :: (forall b. Data b => b -> b) -> Version -> Version # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # | |
Data ByteString | |
Defined in Data.ByteString.Lazy.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString # toConstr :: ByteString -> Constr # dataTypeOf :: ByteString -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) # gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r # gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # | |
Data ShortByteString | |
Defined in Data.ByteString.Short.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShortByteString -> c ShortByteString # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShortByteString # toConstr :: ShortByteString -> Constr # dataTypeOf :: ShortByteString -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ShortByteString) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShortByteString) # gmapT :: (forall b. Data b => b -> b) -> ShortByteString -> ShortByteString # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShortByteString -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShortByteString -> r # gmapQ :: (forall d. Data d => d -> u) -> ShortByteString -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ShortByteString -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShortByteString -> m ShortByteString # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortByteString -> m ShortByteString # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortByteString -> m ShortByteString # | |
Data ByteString | |
Defined in Data.ByteString.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString # toConstr :: ByteString -> Constr # dataTypeOf :: ByteString -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) # gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r # gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # | |
Data GenericPackageDescription | |
Defined in Distribution.Types.GenericPackageDescription Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenericPackageDescription -> c GenericPackageDescription # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GenericPackageDescription # toConstr :: GenericPackageDescription -> Constr # dataTypeOf :: GenericPackageDescription -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GenericPackageDescription) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GenericPackageDescription) # gmapT :: (forall b. Data b => b -> b) -> GenericPackageDescription -> GenericPackageDescription # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenericPackageDescription -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenericPackageDescription -> r # gmapQ :: (forall d. Data d => d -> u) -> GenericPackageDescription -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenericPackageDescription -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenericPackageDescription -> m GenericPackageDescription # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenericPackageDescription -> m GenericPackageDescription # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenericPackageDescription -> m GenericPackageDescription # | |
Data Flag | |
Defined in Distribution.Types.GenericPackageDescription Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Flag -> c Flag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Flag # dataTypeOf :: Flag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Flag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Flag) # gmapT :: (forall b. Data b => b -> b) -> Flag -> Flag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Flag -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Flag -> r # gmapQ :: (forall d. Data d => d -> u) -> Flag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Flag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Flag -> m Flag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Flag -> m Flag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Flag -> m Flag # | |
Data FlagName | |
Defined in Distribution.Types.GenericPackageDescription Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FlagName -> c FlagName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FlagName # toConstr :: FlagName -> Constr # dataTypeOf :: FlagName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FlagName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FlagName) # gmapT :: (forall b. Data b => b -> b) -> FlagName -> FlagName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r # gmapQ :: (forall d. Data d => d -> u) -> FlagName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FlagName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # | |
Data ConfVar | |
Defined in Distribution.Types.GenericPackageDescription Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConfVar -> c ConfVar # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConfVar # toConstr :: ConfVar -> Constr # dataTypeOf :: ConfVar -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConfVar) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConfVar) # gmapT :: (forall b. Data b => b -> b) -> ConfVar -> ConfVar # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConfVar -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConfVar -> r # gmapQ :: (forall d. Data d => d -> u) -> ConfVar -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConfVar -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConfVar -> m ConfVar # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfVar -> m ConfVar # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfVar -> m ConfVar # | |
Data PackageDescription | |
Defined in Distribution.Types.PackageDescription Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageDescription -> c PackageDescription # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageDescription # toConstr :: PackageDescription -> Constr # dataTypeOf :: PackageDescription -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageDescription) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageDescription) # gmapT :: (forall b. Data b => b -> b) -> PackageDescription -> PackageDescription # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageDescription -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageDescription -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageDescription -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageDescription -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription # | |
Data Benchmark | |
Defined in Distribution.Types.Benchmark Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Benchmark -> c Benchmark # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Benchmark # toConstr :: Benchmark -> Constr # dataTypeOf :: Benchmark -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Benchmark) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Benchmark) # gmapT :: (forall b. Data b => b -> b) -> Benchmark -> Benchmark # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Benchmark -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Benchmark -> r # gmapQ :: (forall d. Data d => d -> u) -> Benchmark -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Benchmark -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Benchmark -> m Benchmark # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Benchmark -> m Benchmark # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Benchmark -> m Benchmark # | |
Data Executable | |
Defined in Distribution.Types.Executable Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Executable -> c Executable # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Executable # toConstr :: Executable -> Constr # dataTypeOf :: Executable -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Executable) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Executable) # gmapT :: (forall b. Data b => b -> b) -> Executable -> Executable # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Executable -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Executable -> r # gmapQ :: (forall d. Data d => d -> u) -> Executable -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Executable -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Executable -> m Executable # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Executable -> m Executable # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Executable -> m Executable # | |
Data ForeignLib | |
Defined in Distribution.Types.ForeignLib Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignLib -> c ForeignLib # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForeignLib # toConstr :: ForeignLib -> Constr # dataTypeOf :: ForeignLib -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForeignLib) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignLib) # gmapT :: (forall b. Data b => b -> b) -> ForeignLib -> ForeignLib # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignLib -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignLib -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignLib -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignLib -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib # | |
Data LibVersionInfo | |
Defined in Distribution.Types.ForeignLib Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LibVersionInfo -> c LibVersionInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LibVersionInfo # toConstr :: LibVersionInfo -> Constr # dataTypeOf :: LibVersionInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LibVersionInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LibVersionInfo) # gmapT :: (forall b. Data b => b -> b) -> LibVersionInfo -> LibVersionInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> LibVersionInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LibVersionInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LibVersionInfo -> m LibVersionInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LibVersionInfo -> m LibVersionInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LibVersionInfo -> m LibVersionInfo # | |
Data Library | |
Defined in Distribution.Types.Library Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Library -> c Library # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Library # toConstr :: Library -> Constr # dataTypeOf :: Library -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Library) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Library) # gmapT :: (forall b. Data b => b -> b) -> Library -> Library # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Library -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Library -> r # gmapQ :: (forall d. Data d => d -> u) -> Library -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Library -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Library -> m Library # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Library -> m Library # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Library -> m Library # | |
Data TestSuite | |
Defined in Distribution.Types.TestSuite Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TestSuite -> c TestSuite # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TestSuite # toConstr :: TestSuite -> Constr # dataTypeOf :: TestSuite -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TestSuite) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestSuite) # gmapT :: (forall b. Data b => b -> b) -> TestSuite -> TestSuite # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TestSuite -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TestSuite -> r # gmapQ :: (forall d. Data d => d -> u) -> TestSuite -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TestSuite -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TestSuite -> m TestSuite # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TestSuite -> m TestSuite # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TestSuite -> m TestSuite # | |
Data BuildInfo | |
Defined in Distribution.Types.BuildInfo Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuildInfo -> c BuildInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuildInfo # toConstr :: BuildInfo -> Constr # dataTypeOf :: BuildInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BuildInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildInfo) # gmapT :: (forall b. Data b => b -> b) -> BuildInfo -> BuildInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuildInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuildInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> BuildInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BuildInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo # | |
Data LegacyExeDependency | |
Defined in Distribution.Types.LegacyExeDependency Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LegacyExeDependency -> c LegacyExeDependency # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LegacyExeDependency # toConstr :: LegacyExeDependency -> Constr # dataTypeOf :: LegacyExeDependency -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LegacyExeDependency) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LegacyExeDependency) # gmapT :: (forall b. Data b => b -> b) -> LegacyExeDependency -> LegacyExeDependency # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LegacyExeDependency -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LegacyExeDependency -> r # gmapQ :: (forall d. Data d => d -> u) -> LegacyExeDependency -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LegacyExeDependency -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LegacyExeDependency -> m LegacyExeDependency # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LegacyExeDependency -> m LegacyExeDependency # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LegacyExeDependency -> m LegacyExeDependency # | |
Data MungedPackageId | |
Defined in Distribution.Types.MungedPackageId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MungedPackageId -> c MungedPackageId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MungedPackageId # toConstr :: MungedPackageId -> Constr # dataTypeOf :: MungedPackageId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MungedPackageId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MungedPackageId) # gmapT :: (forall b. Data b => b -> b) -> MungedPackageId -> MungedPackageId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MungedPackageId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MungedPackageId -> r # gmapQ :: (forall d. Data d => d -> u) -> MungedPackageId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MungedPackageId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MungedPackageId -> m MungedPackageId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MungedPackageId -> m MungedPackageId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MungedPackageId -> m MungedPackageId # | |
Data MungedPackageName | |
Defined in Distribution.Types.MungedPackageName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MungedPackageName -> c MungedPackageName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MungedPackageName # toConstr :: MungedPackageName -> Constr # dataTypeOf :: MungedPackageName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MungedPackageName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MungedPackageName) # gmapT :: (forall b. Data b => b -> b) -> MungedPackageName -> MungedPackageName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MungedPackageName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MungedPackageName -> r # gmapQ :: (forall d. Data d => d -> u) -> MungedPackageName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MungedPackageName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MungedPackageName -> m MungedPackageName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MungedPackageName -> m MungedPackageName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MungedPackageName -> m MungedPackageName # | |
Data SetupBuildInfo | |
Defined in Distribution.Types.SetupBuildInfo Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetupBuildInfo -> c SetupBuildInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SetupBuildInfo # toConstr :: SetupBuildInfo -> Constr # dataTypeOf :: SetupBuildInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SetupBuildInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetupBuildInfo) # gmapT :: (forall b. Data b => b -> b) -> SetupBuildInfo -> SetupBuildInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetupBuildInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetupBuildInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> SetupBuildInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SetupBuildInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetupBuildInfo -> m SetupBuildInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetupBuildInfo -> m SetupBuildInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetupBuildInfo -> m SetupBuildInfo # | |
Data Dependency | |
Defined in Distribution.Types.Dependency Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dependency -> c Dependency # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dependency # toConstr :: Dependency -> Constr # dataTypeOf :: Dependency -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dependency) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dependency) # gmapT :: (forall b. Data b => b -> b) -> Dependency -> Dependency # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dependency -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dependency -> r # gmapQ :: (forall d. Data d => d -> u) -> Dependency -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dependency -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency # | |
Data ExeDependency | |
Defined in Distribution.Types.ExeDependency Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExeDependency -> c ExeDependency # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExeDependency # toConstr :: ExeDependency -> Constr # dataTypeOf :: ExeDependency -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExeDependency) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExeDependency) # gmapT :: (forall b. Data b => b -> b) -> ExeDependency -> ExeDependency # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExeDependency -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExeDependency -> r # gmapQ :: (forall d. Data d => d -> u) -> ExeDependency -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExeDependency -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency # | |
Data Mixin | |
Defined in Distribution.Types.Mixin Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Mixin -> c Mixin # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Mixin # dataTypeOf :: Mixin -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Mixin) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mixin) # gmapT :: (forall b. Data b => b -> b) -> Mixin -> Mixin # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mixin -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mixin -> r # gmapQ :: (forall d. Data d => d -> u) -> Mixin -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Mixin -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Mixin -> m Mixin # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Mixin -> m Mixin # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Mixin -> m Mixin # | |
Data ModuleReexport | |
Defined in Distribution.Types.ModuleReexport Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleReexport -> c ModuleReexport # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleReexport # toConstr :: ModuleReexport -> Constr # dataTypeOf :: ModuleReexport -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleReexport) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleReexport) # gmapT :: (forall b. Data b => b -> b) -> ModuleReexport -> ModuleReexport # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleReexport -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleReexport -> r # gmapQ :: (forall d. Data d => d -> u) -> ModuleReexport -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleReexport -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleReexport -> m ModuleReexport # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleReexport -> m ModuleReexport # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleReexport -> m ModuleReexport # | |
Data OpenUnitId | |
Defined in Distribution.Backpack Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OpenUnitId -> c OpenUnitId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OpenUnitId # toConstr :: OpenUnitId -> Constr # dataTypeOf :: OpenUnitId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OpenUnitId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OpenUnitId) # gmapT :: (forall b. Data b => b -> b) -> OpenUnitId -> OpenUnitId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OpenUnitId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OpenUnitId -> r # gmapQ :: (forall d. Data d => d -> u) -> OpenUnitId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OpenUnitId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OpenUnitId -> m OpenUnitId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenUnitId -> m OpenUnitId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenUnitId -> m OpenUnitId # | |
Data OpenModule | |
Defined in Distribution.Backpack Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OpenModule -> c OpenModule # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OpenModule # toConstr :: OpenModule -> Constr # dataTypeOf :: OpenModule -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OpenModule) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OpenModule) # gmapT :: (forall b. Data b => b -> b) -> OpenModule -> OpenModule # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OpenModule -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OpenModule -> r # gmapQ :: (forall d. Data d => d -> u) -> OpenModule -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OpenModule -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OpenModule -> m OpenModule # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenModule -> m OpenModule # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenModule -> m OpenModule # | |
Data Module | |
Defined in Distribution.Types.Module Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module # toConstr :: Module -> Constr # dataTypeOf :: Module -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Module) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) # gmapT :: (forall b. Data b => b -> b) -> Module -> Module # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r # gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module # | |
Data UnitId | |
Defined in Distribution.Types.UnitId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnitId -> c UnitId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnitId # toConstr :: UnitId -> Constr # dataTypeOf :: UnitId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnitId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnitId) # gmapT :: (forall b. Data b => b -> b) -> UnitId -> UnitId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r # gmapQ :: (forall d. Data d => d -> u) -> UnitId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnitId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId # | |
Data DefUnitId | |
Defined in Distribution.Types.UnitId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefUnitId -> c DefUnitId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DefUnitId # toConstr :: DefUnitId -> Constr # dataTypeOf :: DefUnitId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DefUnitId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DefUnitId) # gmapT :: (forall b. Data b => b -> b) -> DefUnitId -> DefUnitId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefUnitId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefUnitId -> r # gmapQ :: (forall d. Data d => d -> u) -> DefUnitId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DefUnitId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefUnitId -> m DefUnitId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefUnitId -> m DefUnitId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefUnitId -> m DefUnitId # | |
Data PackageIdentifier | |
Defined in Distribution.Types.PackageId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageIdentifier -> c PackageIdentifier # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageIdentifier # toConstr :: PackageIdentifier -> Constr # dataTypeOf :: PackageIdentifier -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageIdentifier) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageIdentifier) # gmapT :: (forall b. Data b => b -> b) -> PackageIdentifier -> PackageIdentifier # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageIdentifier -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageIdentifier -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier # | |
Data UnqualComponentName | |
Defined in Distribution.Types.UnqualComponentName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnqualComponentName -> c UnqualComponentName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnqualComponentName # toConstr :: UnqualComponentName -> Constr # dataTypeOf :: UnqualComponentName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnqualComponentName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnqualComponentName) # gmapT :: (forall b. Data b => b -> b) -> UnqualComponentName -> UnqualComponentName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnqualComponentName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnqualComponentName -> r # gmapQ :: (forall d. Data d => d -> u) -> UnqualComponentName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnqualComponentName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnqualComponentName -> m UnqualComponentName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnqualComponentName -> m UnqualComponentName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnqualComponentName -> m UnqualComponentName # | |
Data PackageName | |
Defined in Distribution.Types.PackageName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageName -> c PackageName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageName # toConstr :: PackageName -> Constr # dataTypeOf :: PackageName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageName) # gmapT :: (forall b. Data b => b -> b) -> PackageName -> PackageName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageName -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName # | |
Data CompilerFlavor | |
Defined in Distribution.Compiler Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompilerFlavor -> c CompilerFlavor # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompilerFlavor # toConstr :: CompilerFlavor -> Constr # dataTypeOf :: CompilerFlavor -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CompilerFlavor) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompilerFlavor) # gmapT :: (forall b. Data b => b -> b) -> CompilerFlavor -> CompilerFlavor # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompilerFlavor -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompilerFlavor -> r # gmapQ :: (forall d. Data d => d -> u) -> CompilerFlavor -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CompilerFlavor -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompilerFlavor -> m CompilerFlavor # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompilerFlavor -> m CompilerFlavor # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompilerFlavor -> m CompilerFlavor # | |
Data Language | |
Defined in Language.Haskell.Extension Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Language -> c Language # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Language # toConstr :: Language -> Constr # dataTypeOf :: Language -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Language) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Language) # gmapT :: (forall b. Data b => b -> b) -> Language -> Language # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Language -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Language -> r # gmapQ :: (forall d. Data d => d -> u) -> Language -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Language -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Language -> m Language # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Language -> m Language # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Language -> m Language # | |
Data Extension | |
Defined in Language.Haskell.Extension Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Extension -> c Extension # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Extension # toConstr :: Extension -> Constr # dataTypeOf :: Extension -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Extension) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extension) # gmapT :: (forall b. Data b => b -> b) -> Extension -> Extension # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Extension -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Extension -> r # gmapQ :: (forall d. Data d => d -> u) -> Extension -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Extension -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Extension -> m Extension # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Extension -> m Extension # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Extension -> m Extension # | |
Data KnownExtension | |
Defined in Language.Haskell.Extension Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KnownExtension -> c KnownExtension # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KnownExtension # toConstr :: KnownExtension -> Constr # dataTypeOf :: KnownExtension -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KnownExtension) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KnownExtension) # gmapT :: (forall b. Data b => b -> b) -> KnownExtension -> KnownExtension # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KnownExtension -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KnownExtension -> r # gmapQ :: (forall d. Data d => d -> u) -> KnownExtension -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> KnownExtension -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> KnownExtension -> m KnownExtension # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KnownExtension -> m KnownExtension # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KnownExtension -> m KnownExtension # | |
Data License | |
Defined in Distribution.License Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> License -> c License # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c License # toConstr :: License -> Constr # dataTypeOf :: License -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c License) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License) # gmapT :: (forall b. Data b => b -> b) -> License -> License # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> License -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> License -> r # gmapQ :: (forall d. Data d => d -> u) -> License -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> License -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> License -> m License # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> License -> m License # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> License -> m License # | |
Data BenchmarkInterface | |
Defined in Distribution.Types.BenchmarkInterface Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BenchmarkInterface -> c BenchmarkInterface # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BenchmarkInterface # toConstr :: BenchmarkInterface -> Constr # dataTypeOf :: BenchmarkInterface -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BenchmarkInterface) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BenchmarkInterface) # gmapT :: (forall b. Data b => b -> b) -> BenchmarkInterface -> BenchmarkInterface # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BenchmarkInterface -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BenchmarkInterface -> r # gmapQ :: (forall d. Data d => d -> u) -> BenchmarkInterface -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BenchmarkInterface -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BenchmarkInterface -> m BenchmarkInterface # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BenchmarkInterface -> m BenchmarkInterface # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BenchmarkInterface -> m BenchmarkInterface # | |
Data BenchmarkType | |
Defined in Distribution.Types.BenchmarkType Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BenchmarkType -> c BenchmarkType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BenchmarkType # toConstr :: BenchmarkType -> Constr # dataTypeOf :: BenchmarkType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BenchmarkType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BenchmarkType) # gmapT :: (forall b. Data b => b -> b) -> BenchmarkType -> BenchmarkType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BenchmarkType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BenchmarkType -> r # gmapQ :: (forall d. Data d => d -> u) -> BenchmarkType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BenchmarkType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BenchmarkType -> m BenchmarkType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BenchmarkType -> m BenchmarkType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BenchmarkType -> m BenchmarkType # | |
Data PkgconfigDependency | |
Defined in Distribution.Types.PkgconfigDependency Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PkgconfigDependency -> c PkgconfigDependency # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PkgconfigDependency # toConstr :: PkgconfigDependency -> Constr # dataTypeOf :: PkgconfigDependency -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PkgconfigDependency) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PkgconfigDependency) # gmapT :: (forall b. Data b => b -> b) -> PkgconfigDependency -> PkgconfigDependency # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PkgconfigDependency -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PkgconfigDependency -> r # gmapQ :: (forall d. Data d => d -> u) -> PkgconfigDependency -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PkgconfigDependency -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PkgconfigDependency -> m PkgconfigDependency # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgconfigDependency -> m PkgconfigDependency # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgconfigDependency -> m PkgconfigDependency # | |
Data TestSuiteInterface | |
Defined in Distribution.Types.TestSuiteInterface Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TestSuiteInterface -> c TestSuiteInterface # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TestSuiteInterface # toConstr :: TestSuiteInterface -> Constr # dataTypeOf :: TestSuiteInterface -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TestSuiteInterface) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestSuiteInterface) # gmapT :: (forall b. Data b => b -> b) -> TestSuiteInterface -> TestSuiteInterface # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r # gmapQ :: (forall d. Data d => d -> u) -> TestSuiteInterface -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TestSuiteInterface -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TestSuiteInterface -> m TestSuiteInterface # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TestSuiteInterface -> m TestSuiteInterface # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TestSuiteInterface -> m TestSuiteInterface # | |
Data TestType | |
Defined in Distribution.Types.TestType Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TestType -> c TestType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TestType # toConstr :: TestType -> Constr # dataTypeOf :: TestType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TestType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestType) # gmapT :: (forall b. Data b => b -> b) -> TestType -> TestType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TestType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TestType -> r # gmapQ :: (forall d. Data d => d -> u) -> TestType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TestType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TestType -> m TestType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TestType -> m TestType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TestType -> m TestType # | |
Data IncludeRenaming | |
Defined in Distribution.Types.IncludeRenaming Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IncludeRenaming -> c IncludeRenaming # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IncludeRenaming # toConstr :: IncludeRenaming -> Constr # dataTypeOf :: IncludeRenaming -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IncludeRenaming) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IncludeRenaming) # gmapT :: (forall b. Data b => b -> b) -> IncludeRenaming -> IncludeRenaming # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IncludeRenaming -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IncludeRenaming -> r # gmapQ :: (forall d. Data d => d -> u) -> IncludeRenaming -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IncludeRenaming -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IncludeRenaming -> m IncludeRenaming # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IncludeRenaming -> m IncludeRenaming # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IncludeRenaming -> m IncludeRenaming # | |
Data ModuleRenaming | |
Defined in Distribution.Types.ModuleRenaming Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleRenaming -> c ModuleRenaming # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleRenaming # toConstr :: ModuleRenaming -> Constr # dataTypeOf :: ModuleRenaming -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleRenaming) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleRenaming) # gmapT :: (forall b. Data b => b -> b) -> ModuleRenaming -> ModuleRenaming # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r # gmapQ :: (forall d. Data d => d -> u) -> ModuleRenaming -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleRenaming -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleRenaming -> m ModuleRenaming # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleRenaming -> m ModuleRenaming # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleRenaming -> m ModuleRenaming # | |
Data ModuleName | |
Defined in Distribution.ModuleName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleName -> c ModuleName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleName # toConstr :: ModuleName -> Constr # dataTypeOf :: ModuleName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleName) # gmapT :: (forall b. Data b => b -> b) -> ModuleName -> ModuleName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r # gmapQ :: (forall d. Data d => d -> u) -> ModuleName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName # | |
Data License | |
Defined in Distribution.SPDX.License Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> License -> c License # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c License # toConstr :: License -> Constr # dataTypeOf :: License -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c License) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License) # gmapT :: (forall b. Data b => b -> b) -> License -> License # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> License -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> License -> r # gmapQ :: (forall d. Data d => d -> u) -> License -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> License -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> License -> m License # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> License -> m License # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> License -> m License # | |
Data LicenseExpression | |
Defined in Distribution.SPDX.LicenseExpression Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LicenseExpression -> c LicenseExpression # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LicenseExpression # toConstr :: LicenseExpression -> Constr # dataTypeOf :: LicenseExpression -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LicenseExpression) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseExpression) # gmapT :: (forall b. Data b => b -> b) -> LicenseExpression -> LicenseExpression # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r # gmapQ :: (forall d. Data d => d -> u) -> LicenseExpression -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LicenseExpression -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LicenseExpression -> m LicenseExpression # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseExpression -> m LicenseExpression # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseExpression -> m LicenseExpression # | |
Data SimpleLicenseExpression | |
Defined in Distribution.SPDX.LicenseExpression Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SimpleLicenseExpression -> c SimpleLicenseExpression # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SimpleLicenseExpression # toConstr :: SimpleLicenseExpression -> Constr # dataTypeOf :: SimpleLicenseExpression -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SimpleLicenseExpression) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SimpleLicenseExpression) # gmapT :: (forall b. Data b => b -> b) -> SimpleLicenseExpression -> SimpleLicenseExpression # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SimpleLicenseExpression -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SimpleLicenseExpression -> r # gmapQ :: (forall d. Data d => d -> u) -> SimpleLicenseExpression -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SimpleLicenseExpression -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SimpleLicenseExpression -> m SimpleLicenseExpression # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleLicenseExpression -> m SimpleLicenseExpression # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleLicenseExpression -> m SimpleLicenseExpression # | |
Data LicenseExceptionId | |
Defined in Distribution.SPDX.LicenseExceptionId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LicenseExceptionId -> c LicenseExceptionId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LicenseExceptionId # toConstr :: LicenseExceptionId -> Constr # dataTypeOf :: LicenseExceptionId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LicenseExceptionId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseExceptionId) # gmapT :: (forall b. Data b => b -> b) -> LicenseExceptionId -> LicenseExceptionId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LicenseExceptionId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LicenseExceptionId -> r # gmapQ :: (forall d. Data d => d -> u) -> LicenseExceptionId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LicenseExceptionId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LicenseExceptionId -> m LicenseExceptionId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseExceptionId -> m LicenseExceptionId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseExceptionId -> m LicenseExceptionId # | |
Data LicenseId | |
Defined in Distribution.SPDX.LicenseId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LicenseId -> c LicenseId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LicenseId # toConstr :: LicenseId -> Constr # dataTypeOf :: LicenseId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LicenseId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseId) # gmapT :: (forall b. Data b => b -> b) -> LicenseId -> LicenseId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LicenseId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LicenseId -> r # gmapQ :: (forall d. Data d => d -> u) -> LicenseId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LicenseId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LicenseId -> m LicenseId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseId -> m LicenseId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseId -> m LicenseId # | |
Data LicenseRef | |
Defined in Distribution.SPDX.LicenseReference Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LicenseRef -> c LicenseRef # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LicenseRef # toConstr :: LicenseRef -> Constr # dataTypeOf :: LicenseRef -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LicenseRef) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseRef) # gmapT :: (forall b. Data b => b -> b) -> LicenseRef -> LicenseRef # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LicenseRef -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LicenseRef -> r # gmapQ :: (forall d. Data d => d -> u) -> LicenseRef -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LicenseRef -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef # | |
Data OS | |
Defined in Distribution.System Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OS -> c OS # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OS # dataTypeOf :: OS -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OS) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OS) # gmapT :: (forall b. Data b => b -> b) -> OS -> OS # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r # gmapQ :: (forall d. Data d => d -> u) -> OS -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OS -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OS -> m OS # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OS -> m OS # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OS -> m OS # | |
Data Arch | |
Defined in Distribution.System Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Arch -> c Arch # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Arch # dataTypeOf :: Arch -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Arch) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Arch) # gmapT :: (forall b. Data b => b -> b) -> Arch -> Arch # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r # gmapQ :: (forall d. Data d => d -> u) -> Arch -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Arch -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Arch -> m Arch # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Arch -> m Arch # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Arch -> m Arch # | |
Data Platform | |
Defined in Distribution.System Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Platform -> c Platform # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Platform # toConstr :: Platform -> Constr # dataTypeOf :: Platform -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Platform) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Platform) # gmapT :: (forall b. Data b => b -> b) -> Platform -> Platform # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Platform -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Platform -> r # gmapQ :: (forall d. Data d => d -> u) -> Platform -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Platform -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Platform -> m Platform # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Platform -> m Platform # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Platform -> m Platform # | |
Data BuildType | |
Defined in Distribution.Types.BuildType Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuildType -> c BuildType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuildType # toConstr :: BuildType -> Constr # dataTypeOf :: BuildType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BuildType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildType) # gmapT :: (forall b. Data b => b -> b) -> BuildType -> BuildType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuildType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuildType -> r # gmapQ :: (forall d. Data d => d -> u) -> BuildType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BuildType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuildType -> m BuildType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildType -> m BuildType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildType -> m BuildType # | |
Data ComponentId | |
Defined in Distribution.Types.ComponentId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ComponentId -> c ComponentId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ComponentId # toConstr :: ComponentId -> Constr # dataTypeOf :: ComponentId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ComponentId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ComponentId) # gmapT :: (forall b. Data b => b -> b) -> ComponentId -> ComponentId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ComponentId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ComponentId -> r # gmapQ :: (forall d. Data d => d -> u) -> ComponentId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ComponentId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ComponentId -> m ComponentId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ComponentId -> m ComponentId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ComponentId -> m ComponentId # | |
Data ExecutableScope | |
Defined in Distribution.Types.ExecutableScope Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExecutableScope -> c ExecutableScope # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExecutableScope # toConstr :: ExecutableScope -> Constr # dataTypeOf :: ExecutableScope -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExecutableScope) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExecutableScope) # gmapT :: (forall b. Data b => b -> b) -> ExecutableScope -> ExecutableScope # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExecutableScope -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExecutableScope -> r # gmapQ :: (forall d. Data d => d -> u) -> ExecutableScope -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExecutableScope -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExecutableScope -> m ExecutableScope # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExecutableScope -> m ExecutableScope # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExecutableScope -> m ExecutableScope # | |
Data ForeignLibOption | |
Defined in Distribution.Types.ForeignLibOption Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignLibOption -> c ForeignLibOption # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForeignLibOption # toConstr :: ForeignLibOption -> Constr # dataTypeOf :: ForeignLibOption -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForeignLibOption) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignLibOption) # gmapT :: (forall b. Data b => b -> b) -> ForeignLibOption -> ForeignLibOption # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignLibOption -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignLibOption -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignLibOption -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignLibOption -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignLibOption -> m ForeignLibOption # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignLibOption -> m ForeignLibOption # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignLibOption -> m ForeignLibOption # | |
Data ForeignLibType | |
Defined in Distribution.Types.ForeignLibType Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignLibType -> c ForeignLibType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForeignLibType # toConstr :: ForeignLibType -> Constr # dataTypeOf :: ForeignLibType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForeignLibType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignLibType) # gmapT :: (forall b. Data b => b -> b) -> ForeignLibType -> ForeignLibType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignLibType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignLibType -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignLibType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignLibType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignLibType -> m ForeignLibType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignLibType -> m ForeignLibType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignLibType -> m ForeignLibType # | |
Data PkgconfigName | |
Defined in Distribution.Types.PkgconfigName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PkgconfigName -> c PkgconfigName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PkgconfigName # toConstr :: PkgconfigName -> Constr # dataTypeOf :: PkgconfigName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PkgconfigName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PkgconfigName) # gmapT :: (forall b. Data b => b -> b) -> PkgconfigName -> PkgconfigName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r # gmapQ :: (forall d. Data d => d -> u) -> PkgconfigName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PkgconfigName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName # | |
Data SourceRepo | |
Defined in Distribution.Types.SourceRepo Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceRepo -> c SourceRepo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceRepo # toConstr :: SourceRepo -> Constr # dataTypeOf :: SourceRepo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceRepo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceRepo) # gmapT :: (forall b. Data b => b -> b) -> SourceRepo -> SourceRepo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceRepo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceRepo -> r # gmapQ :: (forall d. Data d => d -> u) -> SourceRepo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceRepo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo # | |
Data RepoKind | |
Defined in Distribution.Types.SourceRepo Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoKind -> c RepoKind # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoKind # toConstr :: RepoKind -> Constr # dataTypeOf :: RepoKind -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RepoKind) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoKind) # gmapT :: (forall b. Data b => b -> b) -> RepoKind -> RepoKind # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoKind -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoKind -> r # gmapQ :: (forall d. Data d => d -> u) -> RepoKind -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoKind -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoKind -> m RepoKind # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoKind -> m RepoKind # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoKind -> m RepoKind # | |
Data RepoType | |
Defined in Distribution.Types.SourceRepo Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoType -> c RepoType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoType # toConstr :: RepoType -> Constr # dataTypeOf :: RepoType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RepoType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoType) # gmapT :: (forall b. Data b => b -> b) -> RepoType -> RepoType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoType -> r # gmapQ :: (forall d. Data d => d -> u) -> RepoType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType # | |
Data VersionRange | |
Defined in Distribution.Types.VersionRange Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VersionRange -> c VersionRange # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VersionRange # toConstr :: VersionRange -> Constr # dataTypeOf :: VersionRange -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VersionRange) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VersionRange) # gmapT :: (forall b. Data b => b -> b) -> VersionRange -> VersionRange # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VersionRange -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VersionRange -> r # gmapQ :: (forall d. Data d => d -> u) -> VersionRange -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionRange -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange # | |
Data Version | |
Defined in Distribution.Types.Version Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version # toConstr :: Version -> Constr # dataTypeOf :: Version -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) # gmapT :: (forall b. Data b => b -> b) -> Version -> Version # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # | |
Data ShortText | |
Defined in Distribution.Utils.ShortText Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShortText -> c ShortText # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShortText # toConstr :: ShortText -> Constr # dataTypeOf :: ShortText -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ShortText) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShortText) # gmapT :: (forall b. Data b => b -> b) -> ShortText -> ShortText # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShortText -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShortText -> r # gmapQ :: (forall d. Data d => d -> u) -> ShortText -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ShortText -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShortText -> m ShortText # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortText -> m ShortText # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortText -> m ShortText # | |
Data CabalSpecVersion | |
Defined in Distribution.CabalSpecVersion Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CabalSpecVersion -> c CabalSpecVersion # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CabalSpecVersion # toConstr :: CabalSpecVersion -> Constr # dataTypeOf :: CabalSpecVersion -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CabalSpecVersion) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CabalSpecVersion) # gmapT :: (forall b. Data b => b -> b) -> CabalSpecVersion -> CabalSpecVersion # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CabalSpecVersion -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CabalSpecVersion -> r # gmapQ :: (forall d. Data d => d -> u) -> CabalSpecVersion -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CabalSpecVersion -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CabalSpecVersion -> m CabalSpecVersion # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CabalSpecVersion -> m CabalSpecVersion # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CabalSpecVersion -> m CabalSpecVersion # | |
Data CabalFeature | |
Defined in Distribution.CabalSpecVersion Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CabalFeature -> c CabalFeature # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CabalFeature # toConstr :: CabalFeature -> Constr # dataTypeOf :: CabalFeature -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CabalFeature) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CabalFeature) # gmapT :: (forall b. Data b => b -> b) -> CabalFeature -> CabalFeature # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CabalFeature -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CabalFeature -> r # gmapQ :: (forall d. Data d => d -> u) -> CabalFeature -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CabalFeature -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CabalFeature -> m CabalFeature # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CabalFeature -> m CabalFeature # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CabalFeature -> m CabalFeature # | |
Data Any | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Any -> c Any # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Any # dataTypeOf :: Any -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Any) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Any) # gmapT :: (forall b. Data b => b -> b) -> Any -> Any # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r # gmapQ :: (forall d. Data d => d -> u) -> Any -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Any -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Any -> m Any # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any # | |
Data All | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> All -> c All # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c All # dataTypeOf :: All -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c All) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c All) # gmapT :: (forall b. Data b => b -> b) -> All -> All # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> All -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> All -> r # gmapQ :: (forall d. Data d => d -> u) -> All -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> All -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> All -> m All # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m All # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m All # | |
Data Con | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Con -> c Con # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Con # dataTypeOf :: Con -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Con) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Con) # gmapT :: (forall b. Data b => b -> b) -> Con -> Con # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Con -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Con -> r # gmapQ :: (forall d. Data d => d -> u) -> Con -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Con -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Con -> m Con # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Con -> m Con # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Con -> m Con # | |
Data Scientific | |
Defined in Data.Scientific Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scientific -> c Scientific # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scientific # toConstr :: Scientific -> Constr # dataTypeOf :: Scientific -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scientific) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scientific) # gmapT :: (forall b. Data b => b -> b) -> Scientific -> Scientific # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scientific -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scientific -> r # gmapQ :: (forall d. Data d => d -> u) -> Scientific -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Scientific -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scientific -> m Scientific # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scientific -> m Scientific # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scientific -> m Scientific # | |
Data UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime # toConstr :: UTCTime -> Constr # dataTypeOf :: UTCTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) # gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # | |
Data Value | |
Defined in Data.Aeson.Types.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value # dataTypeOf :: Value -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) # gmapT :: (forall b. Data b => b -> b) -> Value -> Value # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r # gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value # | |
Data Number | |
Defined in Data.Attoparsec.Number Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Number -> c Number # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Number # toConstr :: Number -> Constr # dataTypeOf :: Number -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Number) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Number) # gmapT :: (forall b. Data b => b -> b) -> Number -> Number # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Number -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Number -> r # gmapQ :: (forall d. Data d => d -> u) -> Number -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Number -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Number -> m Number # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Number -> m Number # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Number -> m Number # | |
Data Void | Since: base-4.8.0.0 |
Defined in Data.Void Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Void -> c Void # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Void # dataTypeOf :: Void -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Void) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Void) # gmapT :: (forall b. Data b => b -> b) -> Void -> Void # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r # gmapQ :: (forall d. Data d => d -> u) -> Void -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Void -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Void -> m Void # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void # | |
Data SpecConstrAnnotation | Since: base-4.3.0.0 |
Defined in GHC.Exts Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpecConstrAnnotation -> c SpecConstrAnnotation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpecConstrAnnotation # toConstr :: SpecConstrAnnotation -> Constr # dataTypeOf :: SpecConstrAnnotation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SpecConstrAnnotation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpecConstrAnnotation) # gmapT :: (forall b. Data b => b -> b) -> SpecConstrAnnotation -> SpecConstrAnnotation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpecConstrAnnotation -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpecConstrAnnotation -> r # gmapQ :: (forall d. Data d => d -> u) -> SpecConstrAnnotation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpecConstrAnnotation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpecConstrAnnotation -> m SpecConstrAnnotation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpecConstrAnnotation -> m SpecConstrAnnotation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpecConstrAnnotation -> m SpecConstrAnnotation # | |
Data Fixity | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixity -> c Fixity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixity # toConstr :: Fixity -> Constr # dataTypeOf :: Fixity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Fixity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity) # gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r # gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # | |
Data Associativity | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Associativity -> c Associativity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Associativity # toConstr :: Associativity -> Constr # dataTypeOf :: Associativity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Associativity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Associativity) # gmapT :: (forall b. Data b => b -> b) -> Associativity -> Associativity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Associativity -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Associativity -> r # gmapQ :: (forall d. Data d => d -> u) -> Associativity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Associativity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Associativity -> m Associativity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Associativity -> m Associativity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Associativity -> m Associativity # | |
Data SourceUnpackedness | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceUnpackedness -> c SourceUnpackedness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceUnpackedness # toConstr :: SourceUnpackedness -> Constr # dataTypeOf :: SourceUnpackedness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceUnpackedness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceUnpackedness) # gmapT :: (forall b. Data b => b -> b) -> SourceUnpackedness -> SourceUnpackedness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceUnpackedness -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceUnpackedness -> r # gmapQ :: (forall d. Data d => d -> u) -> SourceUnpackedness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceUnpackedness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness # | |
Data SourceStrictness | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceStrictness -> c SourceStrictness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceStrictness # toConstr :: SourceStrictness -> Constr # dataTypeOf :: SourceStrictness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceStrictness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceStrictness) # gmapT :: (forall b. Data b => b -> b) -> SourceStrictness -> SourceStrictness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceStrictness -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceStrictness -> r # gmapQ :: (forall d. Data d => d -> u) -> SourceStrictness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceStrictness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness # | |
Data DecidedStrictness | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DecidedStrictness -> c DecidedStrictness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DecidedStrictness # toConstr :: DecidedStrictness -> Constr # dataTypeOf :: DecidedStrictness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DecidedStrictness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DecidedStrictness) # gmapT :: (forall b. Data b => b -> b) -> DecidedStrictness -> DecidedStrictness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DecidedStrictness -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DecidedStrictness -> r # gmapQ :: (forall d. Data d => d -> u) -> DecidedStrictness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DecidedStrictness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness # | |
Data WordPtr | Since: base-4.11.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WordPtr -> c WordPtr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WordPtr # toConstr :: WordPtr -> Constr # dataTypeOf :: WordPtr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WordPtr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WordPtr) # gmapT :: (forall b. Data b => b -> b) -> WordPtr -> WordPtr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WordPtr -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WordPtr -> r # gmapQ :: (forall d. Data d => d -> u) -> WordPtr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WordPtr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WordPtr -> m WordPtr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WordPtr -> m WordPtr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WordPtr -> m WordPtr # | |
Data IntPtr | Since: base-4.11.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntPtr -> c IntPtr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntPtr # toConstr :: IntPtr -> Constr # dataTypeOf :: IntPtr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IntPtr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntPtr) # gmapT :: (forall b. Data b => b -> b) -> IntPtr -> IntPtr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntPtr -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntPtr -> r # gmapQ :: (forall d. Data d => d -> u) -> IntPtr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IntPtr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntPtr -> m IntPtr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntPtr -> m IntPtr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntPtr -> m IntPtr # | |
Data Encoding | |
Defined in Basement.String Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Encoding -> c Encoding # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Encoding # toConstr :: Encoding -> Constr # dataTypeOf :: Encoding -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Encoding) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encoding) # gmapT :: (forall b. Data b => b -> b) -> Encoding -> Encoding # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Encoding -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Encoding -> r # gmapQ :: (forall d. Data d => d -> u) -> Encoding -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Encoding -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Encoding -> m Encoding # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Encoding -> m Encoding # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Encoding -> m Encoding # | |
Data String | |
Defined in Basement.UTF8.Base Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> String -> c String # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c String # toConstr :: String -> Constr # dataTypeOf :: String -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c String) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c String) # gmapT :: (forall b. Data b => b -> b) -> String -> String # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> String -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> String -> r # gmapQ :: (forall d. Data d => d -> u) -> String -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> String -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> String -> m String # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> String -> m String # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> String -> m String # | |
Data IntSet | |
Defined in Data.IntSet.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntSet -> c IntSet # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntSet # toConstr :: IntSet -> Constr # dataTypeOf :: IntSet -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IntSet) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntSet) # gmapT :: (forall b. Data b => b -> b) -> IntSet -> IntSet # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntSet -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntSet -> r # gmapQ :: (forall d. Data d => d -> u) -> IntSet -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IntSet -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet # | |
Data DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DiffTime -> c DiffTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DiffTime # toConstr :: DiffTime -> Constr # dataTypeOf :: DiffTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DiffTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DiffTime) # gmapT :: (forall b. Data b => b -> b) -> DiffTime -> DiffTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DiffTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DiffTime -> r # gmapQ :: (forall d. Data d => d -> u) -> DiffTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DiffTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # | |
Data Whirlpool | |
Defined in Crypto.Hash.Whirlpool Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Whirlpool -> c Whirlpool # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Whirlpool # toConstr :: Whirlpool -> Constr # dataTypeOf :: Whirlpool -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Whirlpool) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Whirlpool) # gmapT :: (forall b. Data b => b -> b) -> Whirlpool -> Whirlpool # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Whirlpool -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Whirlpool -> r # gmapQ :: (forall d. Data d => d -> u) -> Whirlpool -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Whirlpool -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Whirlpool -> m Whirlpool # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Whirlpool -> m Whirlpool # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Whirlpool -> m Whirlpool # | |
Data Tiger | |
Defined in Crypto.Hash.Tiger Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tiger -> c Tiger # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tiger # dataTypeOf :: Tiger -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Tiger) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tiger) # gmapT :: (forall b. Data b => b -> b) -> Tiger -> Tiger # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tiger -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tiger -> r # gmapQ :: (forall d. Data d => d -> u) -> Tiger -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tiger -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tiger -> m Tiger # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tiger -> m Tiger # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tiger -> m Tiger # | |
Data Skein512_512 | |
Defined in Crypto.Hash.Skein512 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Skein512_512 -> c Skein512_512 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Skein512_512 # toConstr :: Skein512_512 -> Constr # dataTypeOf :: Skein512_512 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Skein512_512) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Skein512_512) # gmapT :: (forall b. Data b => b -> b) -> Skein512_512 -> Skein512_512 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Skein512_512 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Skein512_512 -> r # gmapQ :: (forall d. Data d => d -> u) -> Skein512_512 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Skein512_512 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Skein512_512 -> m Skein512_512 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein512_512 -> m Skein512_512 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein512_512 -> m Skein512_512 # | |
Data Skein512_384 | |
Defined in Crypto.Hash.Skein512 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Skein512_384 -> c Skein512_384 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Skein512_384 # toConstr :: Skein512_384 -> Constr # dataTypeOf :: Skein512_384 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Skein512_384) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Skein512_384) # gmapT :: (forall b. Data b => b -> b) -> Skein512_384 -> Skein512_384 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Skein512_384 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Skein512_384 -> r # gmapQ :: (forall d. Data d => d -> u) -> Skein512_384 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Skein512_384 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Skein512_384 -> m Skein512_384 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein512_384 -> m Skein512_384 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein512_384 -> m Skein512_384 # | |
Data Skein512_256 | |
Defined in Crypto.Hash.Skein512 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Skein512_256 -> c Skein512_256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Skein512_256 # toConstr :: Skein512_256 -> Constr # dataTypeOf :: Skein512_256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Skein512_256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Skein512_256) # gmapT :: (forall b. Data b => b -> b) -> Skein512_256 -> Skein512_256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Skein512_256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Skein512_256 -> r # gmapQ :: (forall d. Data d => d -> u) -> Skein512_256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Skein512_256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Skein512_256 -> m Skein512_256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein512_256 -> m Skein512_256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein512_256 -> m Skein512_256 # | |
Data Skein512_224 | |
Defined in Crypto.Hash.Skein512 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Skein512_224 -> c Skein512_224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Skein512_224 # toConstr :: Skein512_224 -> Constr # dataTypeOf :: Skein512_224 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Skein512_224) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Skein512_224) # gmapT :: (forall b. Data b => b -> b) -> Skein512_224 -> Skein512_224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Skein512_224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Skein512_224 -> r # gmapQ :: (forall d. Data d => d -> u) -> Skein512_224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Skein512_224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Skein512_224 -> m Skein512_224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein512_224 -> m Skein512_224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein512_224 -> m Skein512_224 # | |
Data Skein256_256 | |
Defined in Crypto.Hash.Skein256 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Skein256_256 -> c Skein256_256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Skein256_256 # toConstr :: Skein256_256 -> Constr # dataTypeOf :: Skein256_256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Skein256_256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Skein256_256) # gmapT :: (forall b. Data b => b -> b) -> Skein256_256 -> Skein256_256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Skein256_256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Skein256_256 -> r # gmapQ :: (forall d. Data d => d -> u) -> Skein256_256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Skein256_256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Skein256_256 -> m Skein256_256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein256_256 -> m Skein256_256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein256_256 -> m Skein256_256 # | |
Data Skein256_224 | |
Defined in Crypto.Hash.Skein256 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Skein256_224 -> c Skein256_224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Skein256_224 # toConstr :: Skein256_224 -> Constr # dataTypeOf :: Skein256_224 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Skein256_224) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Skein256_224) # gmapT :: (forall b. Data b => b -> b) -> Skein256_224 -> Skein256_224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Skein256_224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Skein256_224 -> r # gmapQ :: (forall d. Data d => d -> u) -> Skein256_224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Skein256_224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Skein256_224 -> m Skein256_224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein256_224 -> m Skein256_224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Skein256_224 -> m Skein256_224 # | |
Data SHA512 | |
Defined in Crypto.Hash.SHA512 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA512 -> c SHA512 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA512 # toConstr :: SHA512 -> Constr # dataTypeOf :: SHA512 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA512) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA512) # gmapT :: (forall b. Data b => b -> b) -> SHA512 -> SHA512 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA512 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA512 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA512 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA512 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA512 -> m SHA512 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA512 -> m SHA512 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA512 -> m SHA512 # | |
Data SHA384 | |
Defined in Crypto.Hash.SHA384 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA384 -> c SHA384 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA384 # toConstr :: SHA384 -> Constr # dataTypeOf :: SHA384 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA384) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA384) # gmapT :: (forall b. Data b => b -> b) -> SHA384 -> SHA384 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA384 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA384 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA384 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA384 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA384 -> m SHA384 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA384 -> m SHA384 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA384 -> m SHA384 # | |
Data SHA3_512 | |
Defined in Crypto.Hash.SHA3 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA3_512 -> c SHA3_512 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA3_512 # toConstr :: SHA3_512 -> Constr # dataTypeOf :: SHA3_512 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA3_512) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA3_512) # gmapT :: (forall b. Data b => b -> b) -> SHA3_512 -> SHA3_512 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_512 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_512 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA3_512 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA3_512 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA3_512 -> m SHA3_512 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_512 -> m SHA3_512 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_512 -> m SHA3_512 # | |
Data SHA3_384 | |
Defined in Crypto.Hash.SHA3 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA3_384 -> c SHA3_384 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA3_384 # toConstr :: SHA3_384 -> Constr # dataTypeOf :: SHA3_384 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA3_384) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA3_384) # gmapT :: (forall b. Data b => b -> b) -> SHA3_384 -> SHA3_384 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_384 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_384 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA3_384 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA3_384 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA3_384 -> m SHA3_384 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_384 -> m SHA3_384 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_384 -> m SHA3_384 # | |
Data SHA3_256 | |
Defined in Crypto.Hash.SHA3 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA3_256 -> c SHA3_256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA3_256 # toConstr :: SHA3_256 -> Constr # dataTypeOf :: SHA3_256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA3_256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA3_256) # gmapT :: (forall b. Data b => b -> b) -> SHA3_256 -> SHA3_256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_256 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA3_256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA3_256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA3_256 -> m SHA3_256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_256 -> m SHA3_256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_256 -> m SHA3_256 # | |
Data SHA3_224 | |
Defined in Crypto.Hash.SHA3 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA3_224 -> c SHA3_224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA3_224 # toConstr :: SHA3_224 -> Constr # dataTypeOf :: SHA3_224 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA3_224) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA3_224) # gmapT :: (forall b. Data b => b -> b) -> SHA3_224 -> SHA3_224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_224 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA3_224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA3_224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA3_224 -> m SHA3_224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_224 -> m SHA3_224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_224 -> m SHA3_224 # | |
Data SHA256 | |
Defined in Crypto.Hash.SHA256 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA256 -> c SHA256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA256 # toConstr :: SHA256 -> Constr # dataTypeOf :: SHA256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA256) # gmapT :: (forall b. Data b => b -> b) -> SHA256 -> SHA256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # | |
Data SHA224 | |
Defined in Crypto.Hash.SHA224 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA224 -> c SHA224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA224 # toConstr :: SHA224 -> Constr # dataTypeOf :: SHA224 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA224) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA224) # gmapT :: (forall b. Data b => b -> b) -> SHA224 -> SHA224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA224 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA224 -> m SHA224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA224 -> m SHA224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA224 -> m SHA224 # | |
Data SHA1 | |
Defined in Crypto.Hash.SHA1 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA1 -> c SHA1 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA1 # dataTypeOf :: SHA1 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA1) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA1) # gmapT :: (forall b. Data b => b -> b) -> SHA1 -> SHA1 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA1 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA1 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA1 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA1 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA1 -> m SHA1 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA1 -> m SHA1 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA1 -> m SHA1 # | |
Data RIPEMD160 | |
Defined in Crypto.Hash.RIPEMD160 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RIPEMD160 -> c RIPEMD160 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RIPEMD160 # toConstr :: RIPEMD160 -> Constr # dataTypeOf :: RIPEMD160 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RIPEMD160) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RIPEMD160) # gmapT :: (forall b. Data b => b -> b) -> RIPEMD160 -> RIPEMD160 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RIPEMD160 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RIPEMD160 -> r # gmapQ :: (forall d. Data d => d -> u) -> RIPEMD160 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RIPEMD160 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RIPEMD160 -> m RIPEMD160 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RIPEMD160 -> m RIPEMD160 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RIPEMD160 -> m RIPEMD160 # | |
Data MD5 | |
Defined in Crypto.Hash.MD5 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MD5 -> c MD5 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MD5 # dataTypeOf :: MD5 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MD5) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MD5) # gmapT :: (forall b. Data b => b -> b) -> MD5 -> MD5 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MD5 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MD5 -> r # gmapQ :: (forall d. Data d => d -> u) -> MD5 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MD5 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MD5 -> m MD5 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MD5 -> m MD5 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MD5 -> m MD5 # | |
Data MD4 | |
Defined in Crypto.Hash.MD4 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MD4 -> c MD4 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MD4 # dataTypeOf :: MD4 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MD4) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MD4) # gmapT :: (forall b. Data b => b -> b) -> MD4 -> MD4 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MD4 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MD4 -> r # gmapQ :: (forall d. Data d => d -> u) -> MD4 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MD4 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MD4 -> m MD4 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MD4 -> m MD4 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MD4 -> m MD4 # | |
Data MD2 | |
Defined in Crypto.Hash.MD2 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MD2 -> c MD2 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MD2 # dataTypeOf :: MD2 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MD2) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MD2) # gmapT :: (forall b. Data b => b -> b) -> MD2 -> MD2 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MD2 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MD2 -> r # gmapQ :: (forall d. Data d => d -> u) -> MD2 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MD2 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MD2 -> m MD2 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MD2 -> m MD2 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MD2 -> m MD2 # | |
Data Curve_P256R1 | |
Defined in Crypto.ECC Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_P256R1 -> c Curve_P256R1 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_P256R1 # toConstr :: Curve_P256R1 -> Constr # dataTypeOf :: Curve_P256R1 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Curve_P256R1) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_P256R1) # gmapT :: (forall b. Data b => b -> b) -> Curve_P256R1 -> Curve_P256R1 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P256R1 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P256R1 -> r # gmapQ :: (forall d. Data d => d -> u) -> Curve_P256R1 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_P256R1 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_P256R1 -> m Curve_P256R1 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P256R1 -> m Curve_P256R1 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P256R1 -> m Curve_P256R1 # | |
Data Curve_P384R1 | |
Defined in Crypto.ECC Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_P384R1 -> c Curve_P384R1 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_P384R1 # toConstr :: Curve_P384R1 -> Constr # dataTypeOf :: Curve_P384R1 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Curve_P384R1) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_P384R1) # gmapT :: (forall b. Data b => b -> b) -> Curve_P384R1 -> Curve_P384R1 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P384R1 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P384R1 -> r # gmapQ :: (forall d. Data d => d -> u) -> Curve_P384R1 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_P384R1 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_P384R1 -> m Curve_P384R1 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P384R1 -> m Curve_P384R1 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P384R1 -> m Curve_P384R1 # | |
Data Curve_P521R1 | |
Defined in Crypto.ECC Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_P521R1 -> c Curve_P521R1 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_P521R1 # toConstr :: Curve_P521R1 -> Constr # dataTypeOf :: Curve_P521R1 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Curve_P521R1) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_P521R1) # gmapT :: (forall b. Data b => b -> b) -> Curve_P521R1 -> Curve_P521R1 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P521R1 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_P521R1 -> r # gmapQ :: (forall d. Data d => d -> u) -> Curve_P521R1 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_P521R1 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_P521R1 -> m Curve_P521R1 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P521R1 -> m Curve_P521R1 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_P521R1 -> m Curve_P521R1 # | |
Data Curve_X25519 | |
Defined in Crypto.ECC Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_X25519 -> c Curve_X25519 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_X25519 # toConstr :: Curve_X25519 -> Constr # dataTypeOf :: Curve_X25519 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Curve_X25519) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_X25519) # gmapT :: (forall b. Data b => b -> b) -> Curve_X25519 -> Curve_X25519 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_X25519 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_X25519 -> r # gmapQ :: (forall d. Data d => d -> u) -> Curve_X25519 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_X25519 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_X25519 -> m Curve_X25519 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_X25519 -> m Curve_X25519 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_X25519 -> m Curve_X25519 # | |
Data Curve_X448 | |
Defined in Crypto.ECC Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_X448 -> c Curve_X448 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_X448 # toConstr :: Curve_X448 -> Constr # dataTypeOf :: Curve_X448 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Curve_X448) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_X448) # gmapT :: (forall b. Data b => b -> b) -> Curve_X448 -> Curve_X448 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_X448 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_X448 -> r # gmapQ :: (forall d. Data d => d -> u) -> Curve_X448 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_X448 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_X448 -> m Curve_X448 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_X448 -> m Curve_X448 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_X448 -> m Curve_X448 # | |
Data Curve_Edwards25519 | |
Defined in Crypto.ECC Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Curve_Edwards25519 -> c Curve_Edwards25519 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Curve_Edwards25519 # toConstr :: Curve_Edwards25519 -> Constr # dataTypeOf :: Curve_Edwards25519 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Curve_Edwards25519) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Curve_Edwards25519) # gmapT :: (forall b. Data b => b -> b) -> Curve_Edwards25519 -> Curve_Edwards25519 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Curve_Edwards25519 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Curve_Edwards25519 -> r # gmapQ :: (forall d. Data d => d -> u) -> Curve_Edwards25519 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Curve_Edwards25519 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Curve_Edwards25519 -> m Curve_Edwards25519 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_Edwards25519 -> m Curve_Edwards25519 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Curve_Edwards25519 -> m Curve_Edwards25519 # | |
Data CryptoError | |
Defined in Crypto.Error.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CryptoError -> c CryptoError # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CryptoError # toConstr :: CryptoError -> Constr # dataTypeOf :: CryptoError -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CryptoError) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CryptoError) # gmapT :: (forall b. Data b => b -> b) -> CryptoError -> CryptoError # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CryptoError -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CryptoError -> r # gmapQ :: (forall d. Data d => d -> u) -> CryptoError -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CryptoError -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CryptoError -> m CryptoError # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CryptoError -> m CryptoError # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CryptoError -> m CryptoError # | |
Data Blake2b_160 | |
Defined in Crypto.Hash.Blake2b Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2b_160 -> c Blake2b_160 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2b_160 # toConstr :: Blake2b_160 -> Constr # dataTypeOf :: Blake2b_160 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2b_160) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2b_160) # gmapT :: (forall b. Data b => b -> b) -> Blake2b_160 -> Blake2b_160 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b_160 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b_160 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2b_160 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2b_160 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2b_160 -> m Blake2b_160 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b_160 -> m Blake2b_160 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b_160 -> m Blake2b_160 # | |
Data Blake2b_224 | |
Defined in Crypto.Hash.Blake2b Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2b_224 -> c Blake2b_224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2b_224 # toConstr :: Blake2b_224 -> Constr # dataTypeOf :: Blake2b_224 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2b_224) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2b_224) # gmapT :: (forall b. Data b => b -> b) -> Blake2b_224 -> Blake2b_224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b_224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b_224 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2b_224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2b_224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2b_224 -> m Blake2b_224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b_224 -> m Blake2b_224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b_224 -> m Blake2b_224 # | |
Data Blake2b_256 | |
Defined in Crypto.Hash.Blake2b Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2b_256 -> c Blake2b_256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2b_256 # toConstr :: Blake2b_256 -> Constr # dataTypeOf :: Blake2b_256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2b_256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2b_256) # gmapT :: (forall b. Data b => b -> b) -> Blake2b_256 -> Blake2b_256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b_256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b_256 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2b_256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2b_256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2b_256 -> m Blake2b_256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b_256 -> m Blake2b_256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b_256 -> m Blake2b_256 # | |
Data Blake2b_384 | |
Defined in Crypto.Hash.Blake2b Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2b_384 -> c Blake2b_384 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2b_384 # toConstr :: Blake2b_384 -> Constr # dataTypeOf :: Blake2b_384 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2b_384) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2b_384) # gmapT :: (forall b. Data b => b -> b) -> Blake2b_384 -> Blake2b_384 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b_384 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b_384 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2b_384 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2b_384 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2b_384 -> m Blake2b_384 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b_384 -> m Blake2b_384 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b_384 -> m Blake2b_384 # | |
Data Blake2b_512 | |
Defined in Crypto.Hash.Blake2b Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2b_512 -> c Blake2b_512 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2b_512 # toConstr :: Blake2b_512 -> Constr # dataTypeOf :: Blake2b_512 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2b_512) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2b_512) # gmapT :: (forall b. Data b => b -> b) -> Blake2b_512 -> Blake2b_512 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b_512 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b_512 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2b_512 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2b_512 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2b_512 -> m Blake2b_512 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b_512 -> m Blake2b_512 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b_512 -> m Blake2b_512 # | |
Data Blake2bp_512 | |
Defined in Crypto.Hash.Blake2bp Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2bp_512 -> c Blake2bp_512 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2bp_512 # toConstr :: Blake2bp_512 -> Constr # dataTypeOf :: Blake2bp_512 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2bp_512) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2bp_512) # gmapT :: (forall b. Data b => b -> b) -> Blake2bp_512 -> Blake2bp_512 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2bp_512 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2bp_512 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2bp_512 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2bp_512 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2bp_512 -> m Blake2bp_512 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2bp_512 -> m Blake2bp_512 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2bp_512 -> m Blake2bp_512 # | |
Data Blake2s_160 | |
Defined in Crypto.Hash.Blake2s Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2s_160 -> c Blake2s_160 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2s_160 # toConstr :: Blake2s_160 -> Constr # dataTypeOf :: Blake2s_160 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2s_160) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2s_160) # gmapT :: (forall b. Data b => b -> b) -> Blake2s_160 -> Blake2s_160 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2s_160 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2s_160 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2s_160 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2s_160 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2s_160 -> m Blake2s_160 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2s_160 -> m Blake2s_160 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2s_160 -> m Blake2s_160 # | |
Data Blake2s_224 | |
Defined in Crypto.Hash.Blake2s Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2s_224 -> c Blake2s_224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2s_224 # toConstr :: Blake2s_224 -> Constr # dataTypeOf :: Blake2s_224 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2s_224) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2s_224) # gmapT :: (forall b. Data b => b -> b) -> Blake2s_224 -> Blake2s_224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2s_224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2s_224 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2s_224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2s_224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2s_224 -> m Blake2s_224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2s_224 -> m Blake2s_224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2s_224 -> m Blake2s_224 # | |
Data Blake2s_256 | |
Defined in Crypto.Hash.Blake2s Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2s_256 -> c Blake2s_256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2s_256 # toConstr :: Blake2s_256 -> Constr # dataTypeOf :: Blake2s_256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2s_256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2s_256) # gmapT :: (forall b. Data b => b -> b) -> Blake2s_256 -> Blake2s_256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2s_256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2s_256 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2s_256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2s_256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2s_256 -> m Blake2s_256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2s_256 -> m Blake2s_256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2s_256 -> m Blake2s_256 # | |
Data Blake2sp_224 | |
Defined in Crypto.Hash.Blake2sp Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2sp_224 -> c Blake2sp_224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2sp_224 # toConstr :: Blake2sp_224 -> Constr # dataTypeOf :: Blake2sp_224 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2sp_224) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2sp_224) # gmapT :: (forall b. Data b => b -> b) -> Blake2sp_224 -> Blake2sp_224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2sp_224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2sp_224 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2sp_224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2sp_224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2sp_224 -> m Blake2sp_224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2sp_224 -> m Blake2sp_224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2sp_224 -> m Blake2sp_224 # | |
Data Blake2sp_256 | |
Defined in Crypto.Hash.Blake2sp Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2sp_256 -> c Blake2sp_256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Blake2sp_256 # toConstr :: Blake2sp_256 -> Constr # dataTypeOf :: Blake2sp_256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Blake2sp_256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Blake2sp_256) # gmapT :: (forall b. Data b => b -> b) -> Blake2sp_256 -> Blake2sp_256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2sp_256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2sp_256 -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2sp_256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2sp_256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2sp_256 -> m Blake2sp_256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2sp_256 -> m Blake2sp_256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2sp_256 -> m Blake2sp_256 # | |
Data Keccak_224 | |
Defined in Crypto.Hash.Keccak Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Keccak_224 -> c Keccak_224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Keccak_224 # toConstr :: Keccak_224 -> Constr # dataTypeOf :: Keccak_224 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Keccak_224) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Keccak_224) # gmapT :: (forall b. Data b => b -> b) -> Keccak_224 -> Keccak_224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Keccak_224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Keccak_224 -> r # gmapQ :: (forall d. Data d => d -> u) -> Keccak_224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Keccak_224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Keccak_224 -> m Keccak_224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Keccak_224 -> m Keccak_224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Keccak_224 -> m Keccak_224 # | |
Data Keccak_256 | |
Defined in Crypto.Hash.Keccak Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Keccak_256 -> c Keccak_256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Keccak_256 # toConstr :: Keccak_256 -> Constr # dataTypeOf :: Keccak_256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Keccak_256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Keccak_256) # gmapT :: (forall b. Data b => b -> b) -> Keccak_256 -> Keccak_256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Keccak_256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Keccak_256 -> r # gmapQ :: (forall d. Data d => d -> u) -> Keccak_256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Keccak_256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Keccak_256 -> m Keccak_256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Keccak_256 -> m Keccak_256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Keccak_256 -> m Keccak_256 # | |
Data Keccak_384 | |
Defined in Crypto.Hash.Keccak Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Keccak_384 -> c Keccak_384 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Keccak_384 # toConstr :: Keccak_384 -> Constr # dataTypeOf :: Keccak_384 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Keccak_384) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Keccak_384) # gmapT :: (forall b. Data b => b -> b) -> Keccak_384 -> Keccak_384 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Keccak_384 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Keccak_384 -> r # gmapQ :: (forall d. Data d => d -> u) -> Keccak_384 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Keccak_384 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Keccak_384 -> m Keccak_384 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Keccak_384 -> m Keccak_384 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Keccak_384 -> m Keccak_384 # | |
Data Keccak_512 | |
Defined in Crypto.Hash.Keccak Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Keccak_512 -> c Keccak_512 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Keccak_512 # toConstr :: Keccak_512 -> Constr # dataTypeOf :: Keccak_512 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Keccak_512) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Keccak_512) # gmapT :: (forall b. Data b => b -> b) -> Keccak_512 -> Keccak_512 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Keccak_512 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Keccak_512 -> r # gmapQ :: (forall d. Data d => d -> u) -> Keccak_512 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Keccak_512 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Keccak_512 -> m Keccak_512 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Keccak_512 -> m Keccak_512 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Keccak_512 -> m Keccak_512 # | |
Data SHA512t_224 | |
Defined in Crypto.Hash.SHA512t Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA512t_224 -> c SHA512t_224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA512t_224 # toConstr :: SHA512t_224 -> Constr # dataTypeOf :: SHA512t_224 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA512t_224) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA512t_224) # gmapT :: (forall b. Data b => b -> b) -> SHA512t_224 -> SHA512t_224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA512t_224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA512t_224 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA512t_224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA512t_224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA512t_224 -> m SHA512t_224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA512t_224 -> m SHA512t_224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA512t_224 -> m SHA512t_224 # | |
Data SHA512t_256 | |
Defined in Crypto.Hash.SHA512t Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA512t_256 -> c SHA512t_256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA512t_256 # toConstr :: SHA512t_256 -> Constr # dataTypeOf :: SHA512t_256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA512t_256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA512t_256) # gmapT :: (forall b. Data b => b -> b) -> SHA512t_256 -> SHA512t_256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA512t_256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA512t_256 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA512t_256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA512t_256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA512t_256 -> m SHA512t_256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA512t_256 -> m SHA512t_256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA512t_256 -> m SHA512t_256 # | |
Data ConstructorInfo | |
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConstructorInfo -> c ConstructorInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConstructorInfo # toConstr :: ConstructorInfo -> Constr # dataTypeOf :: ConstructorInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConstructorInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConstructorInfo) # gmapT :: (forall b. Data b => b -> b) -> ConstructorInfo -> ConstructorInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConstructorInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConstructorInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> ConstructorInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConstructorInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConstructorInfo -> m ConstructorInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstructorInfo -> m ConstructorInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstructorInfo -> m ConstructorInfo # | |
Data DatatypeVariant | |
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DatatypeVariant -> c DatatypeVariant # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DatatypeVariant # toConstr :: DatatypeVariant -> Constr # dataTypeOf :: DatatypeVariant -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DatatypeVariant) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DatatypeVariant) # gmapT :: (forall b. Data b => b -> b) -> DatatypeVariant -> DatatypeVariant # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DatatypeVariant -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DatatypeVariant -> r # gmapQ :: (forall d. Data d => d -> u) -> DatatypeVariant -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DatatypeVariant -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DatatypeVariant -> m DatatypeVariant # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DatatypeVariant -> m DatatypeVariant # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DatatypeVariant -> m DatatypeVariant # | |
Data Int54 | |
Defined in Text.JSON.Canonical Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int54 -> c Int54 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int54 # dataTypeOf :: Int54 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int54) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int54) # gmapT :: (forall b. Data b => b -> b) -> Int54 -> Int54 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int54 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int54 -> r # gmapQ :: (forall d. Data d => d -> u) -> Int54 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int54 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int54 -> m Int54 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int54 -> m Int54 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int54 -> m Int54 # | |
Data URI | |
Defined in Network.URI Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URI -> c URI # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URI # dataTypeOf :: URI -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URI) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URI) # gmapT :: (forall b. Data b => b -> b) -> URI -> URI # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r # gmapQ :: (forall d. Data d => d -> u) -> URI -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> URI -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> URI -> m URI # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI # | |
Data ByteRange | |
Defined in Network.HTTP.Types.Header Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteRange -> c ByteRange # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteRange # toConstr :: ByteRange -> Constr # dataTypeOf :: ByteRange -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteRange) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteRange) # gmapT :: (forall b. Data b => b -> b) -> ByteRange -> ByteRange # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteRange -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteRange -> r # gmapQ :: (forall d. Data d => d -> u) -> ByteRange -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteRange -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange # | |
Data Loc | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Loc -> c Loc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Loc # dataTypeOf :: Loc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Loc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Loc) # gmapT :: (forall b. Data b => b -> b) -> Loc -> Loc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r # gmapQ :: (forall d. Data d => d -> u) -> Loc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Loc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Loc -> m Loc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc # | |
Data URIAuth | |
Defined in Network.URI Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URIAuth -> c URIAuth # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URIAuth # toConstr :: URIAuth -> Constr # dataTypeOf :: URIAuth -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URIAuth) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URIAuth) # gmapT :: (forall b. Data b => b -> b) -> URIAuth -> URIAuth # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URIAuth -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URIAuth -> r # gmapQ :: (forall d. Data d => d -> u) -> URIAuth -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> URIAuth -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> URIAuth -> m URIAuth # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URIAuth -> m URIAuth # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URIAuth -> m URIAuth # | |
Data ByteArray | |
Defined in Data.Primitive.ByteArray Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteArray -> c ByteArray # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteArray # toConstr :: ByteArray -> Constr # dataTypeOf :: ByteArray -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteArray) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray) # gmapT :: (forall b. Data b => b -> b) -> ByteArray -> ByteArray # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteArray -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteArray -> r # gmapQ :: (forall d. Data d => d -> u) -> ByteArray -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteArray -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteArray -> m ByteArray # | |
Data Addr | |
Defined in Data.Primitive.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Addr -> c Addr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Addr # dataTypeOf :: Addr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Addr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Addr) # gmapT :: (forall b. Data b => b -> b) -> Addr -> Addr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r # gmapQ :: (forall d. Data d => d -> u) -> Addr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Addr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Addr -> m Addr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Addr -> m Addr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Addr -> m Addr # | |
Data Day | |
Defined in Data.Time.Calendar.Days Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Day -> c Day # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Day # dataTypeOf :: Day -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Day) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Day) # gmapT :: (forall b. Data b => b -> b) -> Day -> Day # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r # gmapQ :: (forall d. Data d => d -> u) -> Day -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Day -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Day -> m Day # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day # | |
Data NominalDiffTime | |
Defined in Data.Time.Clock.Internal.NominalDiffTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NominalDiffTime -> c NominalDiffTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NominalDiffTime # toConstr :: NominalDiffTime -> Constr # dataTypeOf :: NominalDiffTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NominalDiffTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NominalDiffTime) # gmapT :: (forall b. Data b => b -> b) -> NominalDiffTime -> NominalDiffTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NominalDiffTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NominalDiffTime -> r # gmapQ :: (forall d. Data d => d -> u) -> NominalDiffTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NominalDiffTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime # | |
Data UniversalTime | |
Defined in Data.Time.Clock.Internal.UniversalTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UniversalTime -> c UniversalTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UniversalTime # toConstr :: UniversalTime -> Constr # dataTypeOf :: UniversalTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UniversalTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UniversalTime) # gmapT :: (forall b. Data b => b -> b) -> UniversalTime -> UniversalTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UniversalTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UniversalTime -> r # gmapQ :: (forall d. Data d => d -> u) -> UniversalTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UniversalTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UniversalTime -> m UniversalTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UniversalTime -> m UniversalTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UniversalTime -> m UniversalTime # | |
Data TimeZone | |
Defined in Data.Time.LocalTime.Internal.TimeZone Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeZone -> c TimeZone # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeZone # toConstr :: TimeZone -> Constr # dataTypeOf :: TimeZone -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeZone) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeZone) # gmapT :: (forall b. Data b => b -> b) -> TimeZone -> TimeZone # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeZone -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeZone -> r # gmapQ :: (forall d. Data d => d -> u) -> TimeZone -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeZone -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone # | |
Data TimeOfDay | |
Defined in Data.Time.LocalTime.Internal.TimeOfDay Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeOfDay -> c TimeOfDay # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeOfDay # toConstr :: TimeOfDay -> Constr # dataTypeOf :: TimeOfDay -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeOfDay) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeOfDay) # gmapT :: (forall b. Data b => b -> b) -> TimeOfDay -> TimeOfDay # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r # gmapQ :: (forall d. Data d => d -> u) -> TimeOfDay -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeOfDay -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay # | |
Data LocalTime | |
Defined in Data.Time.LocalTime.Internal.LocalTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalTime -> c LocalTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalTime # toConstr :: LocalTime -> Constr # dataTypeOf :: LocalTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LocalTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalTime) # gmapT :: (forall b. Data b => b -> b) -> LocalTime -> LocalTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalTime -> r # gmapQ :: (forall d. Data d => d -> u) -> LocalTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime # | |
Data ZonedTime | |
Defined in Data.Time.LocalTime.Internal.ZonedTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZonedTime -> c ZonedTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ZonedTime # toConstr :: ZonedTime -> Constr # dataTypeOf :: ZonedTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ZonedTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ZonedTime) # gmapT :: (forall b. Data b => b -> b) -> ZonedTime -> ZonedTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZonedTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZonedTime -> r # gmapQ :: (forall d. Data d => d -> u) -> ZonedTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ZonedTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime # | |
Data FilePath | |
Defined in Filesystem.Path.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilePath -> c FilePath # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilePath # toConstr :: FilePath -> Constr # dataTypeOf :: FilePath -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FilePath) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilePath) # gmapT :: (forall b. Data b => b -> b) -> FilePath -> FilePath # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilePath -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilePath -> r # gmapQ :: (forall d. Data d => d -> u) -> FilePath -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FilePath -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath # | |
Data StoreVersion | |
Defined in Data.Store.Version Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StoreVersion -> c StoreVersion # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StoreVersion # toConstr :: StoreVersion -> Constr # dataTypeOf :: StoreVersion -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StoreVersion) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StoreVersion) # gmapT :: (forall b. Data b => b -> b) -> StoreVersion -> StoreVersion # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StoreVersion -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StoreVersion -> r # gmapQ :: (forall d. Data d => d -> u) -> StoreVersion -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StoreVersion -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StoreVersion -> m StoreVersion # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StoreVersion -> m StoreVersion # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StoreVersion -> m StoreVersion # | |
Data Root | |
Defined in Filesystem.Path.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Root -> c Root # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Root # dataTypeOf :: Root -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Root) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Root) # gmapT :: (forall b. Data b => b -> b) -> Root -> Root # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r # gmapQ :: (forall d. Data d => d -> u) -> Root -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Root -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Root -> m Root # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Root -> m Root # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Root -> m Root # | |
Data ModName | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModName -> c ModName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModName # toConstr :: ModName -> Constr # dataTypeOf :: ModName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModName) # gmapT :: (forall b. Data b => b -> b) -> ModName -> ModName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModName -> r # gmapQ :: (forall d. Data d => d -> u) -> ModName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModName -> m ModName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModName -> m ModName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModName -> m ModName # | |
Data PkgName | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PkgName -> c PkgName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PkgName # toConstr :: PkgName -> Constr # dataTypeOf :: PkgName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PkgName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PkgName) # gmapT :: (forall b. Data b => b -> b) -> PkgName -> PkgName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PkgName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PkgName -> r # gmapQ :: (forall d. Data d => d -> u) -> PkgName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PkgName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PkgName -> m PkgName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgName -> m PkgName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgName -> m PkgName # | |
Data Module | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module # toConstr :: Module -> Constr # dataTypeOf :: Module -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Module) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) # gmapT :: (forall b. Data b => b -> b) -> Module -> Module # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r # gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module # | |
Data OccName | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OccName -> c OccName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OccName # toConstr :: OccName -> Constr # dataTypeOf :: OccName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OccName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OccName) # gmapT :: (forall b. Data b => b -> b) -> OccName -> OccName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r # gmapQ :: (forall d. Data d => d -> u) -> OccName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OccName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OccName -> m OccName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName # | |
Data NameFlavour | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameFlavour -> c NameFlavour # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameFlavour # toConstr :: NameFlavour -> Constr # dataTypeOf :: NameFlavour -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NameFlavour) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameFlavour) # gmapT :: (forall b. Data b => b -> b) -> NameFlavour -> NameFlavour # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameFlavour -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameFlavour -> r # gmapQ :: (forall d. Data d => d -> u) -> NameFlavour -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NameFlavour -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameFlavour -> m NameFlavour # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameFlavour -> m NameFlavour # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameFlavour -> m NameFlavour # | |
Data NameSpace | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameSpace -> c NameSpace # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameSpace # toConstr :: NameSpace -> Constr # dataTypeOf :: NameSpace -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NameSpace) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameSpace) # gmapT :: (forall b. Data b => b -> b) -> NameSpace -> NameSpace # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameSpace -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameSpace -> r # gmapQ :: (forall d. Data d => d -> u) -> NameSpace -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NameSpace -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace # | |
Data Info | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Info -> c Info # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Info # dataTypeOf :: Info -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Info) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Info) # gmapT :: (forall b. Data b => b -> b) -> Info -> Info # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Info -> r # gmapQ :: (forall d. Data d => d -> u) -> Info -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Info -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Info -> m Info # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Info -> m Info # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Info -> m Info # | |
Data ModuleInfo | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleInfo -> c ModuleInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleInfo # toConstr :: ModuleInfo -> Constr # dataTypeOf :: ModuleInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleInfo) # gmapT :: (forall b. Data b => b -> b) -> ModuleInfo -> ModuleInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> ModuleInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleInfo -> m ModuleInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleInfo -> m ModuleInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleInfo -> m ModuleInfo # | |
Data Fixity | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixity -> c Fixity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixity # toConstr :: Fixity -> Constr # dataTypeOf :: Fixity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Fixity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity) # gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r # gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # | |
Data FixityDirection | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixityDirection -> c FixityDirection # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FixityDirection # toConstr :: FixityDirection -> Constr # dataTypeOf :: FixityDirection -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FixityDirection) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FixityDirection) # gmapT :: (forall b. Data b => b -> b) -> FixityDirection -> FixityDirection # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r # gmapQ :: (forall d. Data d => d -> u) -> FixityDirection -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FixityDirection -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # | |
Data Lit | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Lit -> c Lit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Lit # dataTypeOf :: Lit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Lit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lit) # gmapT :: (forall b. Data b => b -> b) -> Lit -> Lit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lit -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lit -> r # gmapQ :: (forall d. Data d => d -> u) -> Lit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Lit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Lit -> m Lit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Lit -> m Lit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Lit -> m Lit # | |
Data Body | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Body -> c Body # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Body # dataTypeOf :: Body -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Body) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Body) # gmapT :: (forall b. Data b => b -> b) -> Body -> Body # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Body -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Body -> r # gmapQ :: (forall d. Data d => d -> u) -> Body -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Body -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Body -> m Body # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Body -> m Body # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Body -> m Body # | |
Data Guard | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Guard -> c Guard # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Guard # dataTypeOf :: Guard -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Guard) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Guard) # gmapT :: (forall b. Data b => b -> b) -> Guard -> Guard # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Guard -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Guard -> r # gmapQ :: (forall d. Data d => d -> u) -> Guard -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Guard -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Guard -> m Guard # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Guard -> m Guard # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Guard -> m Guard # | |
Data Stmt | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stmt -> c Stmt # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stmt # dataTypeOf :: Stmt -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Stmt) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stmt) # gmapT :: (forall b. Data b => b -> b) -> Stmt -> Stmt # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stmt -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stmt -> r # gmapQ :: (forall d. Data d => d -> u) -> Stmt -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Stmt -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt # | |
Data Range | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Range -> c Range # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Range # dataTypeOf :: Range -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Range) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Range) # gmapT :: (forall b. Data b => b -> b) -> Range -> Range # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Range -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Range -> r # gmapQ :: (forall d. Data d => d -> u) -> Range -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Range -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Range -> m Range # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Range -> m Range # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Range -> m Range # | |
Data DerivClause | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivClause -> c DerivClause # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DerivClause # toConstr :: DerivClause -> Constr # dataTypeOf :: DerivClause -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DerivClause) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DerivClause) # gmapT :: (forall b. Data b => b -> b) -> DerivClause -> DerivClause # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivClause -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivClause -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivClause -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivClause -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivClause -> m DerivClause # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClause -> m DerivClause # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClause -> m DerivClause # | |
Data DerivStrategy | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivStrategy -> c DerivStrategy # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DerivStrategy # toConstr :: DerivStrategy -> Constr # dataTypeOf :: DerivStrategy -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DerivStrategy) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DerivStrategy) # gmapT :: (forall b. Data b => b -> b) -> DerivStrategy -> DerivStrategy # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy -> m DerivStrategy # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy -> m DerivStrategy # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy -> m DerivStrategy # | |
Data TypeFamilyHead | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeFamilyHead -> c TypeFamilyHead # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeFamilyHead # toConstr :: TypeFamilyHead -> Constr # dataTypeOf :: TypeFamilyHead -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeFamilyHead) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeFamilyHead) # gmapT :: (forall b. Data b => b -> b) -> TypeFamilyHead -> TypeFamilyHead # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeFamilyHead -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeFamilyHead -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeFamilyHead -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeFamilyHead -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeFamilyHead -> m TypeFamilyHead # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeFamilyHead -> m TypeFamilyHead # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeFamilyHead -> m TypeFamilyHead # | |
Data TySynEqn | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TySynEqn -> c TySynEqn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TySynEqn # toConstr :: TySynEqn -> Constr # dataTypeOf :: TySynEqn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TySynEqn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TySynEqn) # gmapT :: (forall b. Data b => b -> b) -> TySynEqn -> TySynEqn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TySynEqn -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TySynEqn -> r # gmapQ :: (forall d. Data d => d -> u) -> TySynEqn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TySynEqn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TySynEqn -> m TySynEqn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TySynEqn -> m TySynEqn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TySynEqn -> m TySynEqn # | |
Data Foreign | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Foreign -> c Foreign # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Foreign # toConstr :: Foreign -> Constr # dataTypeOf :: Foreign -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Foreign) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Foreign) # gmapT :: (forall b. Data b => b -> b) -> Foreign -> Foreign # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Foreign -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Foreign -> r # gmapQ :: (forall d. Data d => d -> u) -> Foreign -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Foreign -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Foreign -> m Foreign # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Foreign -> m Foreign # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Foreign -> m Foreign # | |
Data Callconv | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Callconv -> c Callconv # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Callconv # toConstr :: Callconv -> Constr # dataTypeOf :: Callconv -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Callconv) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Callconv) # gmapT :: (forall b. Data b => b -> b) -> Callconv -> Callconv # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Callconv -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Callconv -> r # gmapQ :: (forall d. Data d => d -> u) -> Callconv -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Callconv -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Callconv -> m Callconv # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Callconv -> m Callconv # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Callconv -> m Callconv # | |
Data Safety | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Safety -> c Safety # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Safety # toConstr :: Safety -> Constr # dataTypeOf :: Safety -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Safety) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Safety) # gmapT :: (forall b. Data b => b -> b) -> Safety -> Safety # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Safety -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Safety -> r # gmapQ :: (forall d. Data d => d -> u) -> Safety -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Safety -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Safety -> m Safety # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety -> m Safety # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety -> m Safety # | |
Data Pragma | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pragma -> c Pragma # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pragma # toConstr :: Pragma -> Constr # dataTypeOf :: Pragma -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pragma) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pragma) # gmapT :: (forall b. Data b => b -> b) -> Pragma -> Pragma # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pragma -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pragma -> r # gmapQ :: (forall d. Data d => d -> u) -> Pragma -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pragma -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pragma -> m Pragma # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pragma -> m Pragma # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pragma -> m Pragma # | |
Data Inline | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Inline -> c Inline # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Inline # toConstr :: Inline -> Constr # dataTypeOf :: Inline -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Inline) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline) # gmapT :: (forall b. Data b => b -> b) -> Inline -> Inline # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r # gmapQ :: (forall d. Data d => d -> u) -> Inline -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Inline -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Inline -> m Inline # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline # | |
Data RuleMatch | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleMatch -> c RuleMatch # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RuleMatch # toConstr :: RuleMatch -> Constr # dataTypeOf :: RuleMatch -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RuleMatch) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RuleMatch) # gmapT :: (forall b. Data b => b -> b) -> RuleMatch -> RuleMatch # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatch -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatch -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleMatch -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleMatch -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleMatch -> m RuleMatch # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatch -> m RuleMatch # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatch -> m RuleMatch # | |
Data Phases | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Phases -> c Phases # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Phases # toConstr :: Phases -> Constr # dataTypeOf :: Phases -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Phases) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Phases) # gmapT :: (forall b. Data b => b -> b) -> Phases -> Phases # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Phases -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Phases -> r # gmapQ :: (forall d. Data d => d -> u) -> Phases -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Phases -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Phases -> m Phases # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Phases -> m Phases # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Phases -> m Phases # | |
Data RuleBndr | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr -> c RuleBndr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RuleBndr # toConstr :: RuleBndr -> Constr # dataTypeOf :: RuleBndr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RuleBndr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RuleBndr) # gmapT :: (forall b. Data b => b -> b) -> RuleBndr -> RuleBndr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleBndr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr -> m RuleBndr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr -> m RuleBndr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr -> m RuleBndr # | |
Data AnnTarget | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnTarget -> c AnnTarget # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnTarget # toConstr :: AnnTarget -> Constr # dataTypeOf :: AnnTarget -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnTarget) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnTarget) # gmapT :: (forall b. Data b => b -> b) -> AnnTarget -> AnnTarget # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnTarget -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnTarget -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnTarget -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnTarget -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnTarget -> m AnnTarget # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnTarget -> m AnnTarget # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnTarget -> m AnnTarget # | |
Data SourceUnpackedness | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceUnpackedness -> c SourceUnpackedness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceUnpackedness # toConstr :: SourceUnpackedness -> Constr # dataTypeOf :: SourceUnpackedness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceUnpackedness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceUnpackedness) # gmapT :: (forall b. Data b => b -> b) -> SourceUnpackedness -> SourceUnpackedness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceUnpackedness -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceUnpackedness -> r # gmapQ :: (forall d. Data d => d -> u) -> SourceUnpackedness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceUnpackedness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceUnpackedness -> m SourceUnpackedness # | |
Data SourceStrictness | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceStrictness -> c SourceStrictness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceStrictness # toConstr :: SourceStrictness -> Constr # dataTypeOf :: SourceStrictness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceStrictness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceStrictness) # gmapT :: (forall b. Data b => b -> b) -> SourceStrictness -> SourceStrictness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceStrictness -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceStrictness -> r # gmapQ :: (forall d. Data d => d -> u) -> SourceStrictness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceStrictness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceStrictness -> m SourceStrictness # | |
Data DecidedStrictness | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DecidedStrictness -> c DecidedStrictness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DecidedStrictness # toConstr :: DecidedStrictness -> Constr # dataTypeOf :: DecidedStrictness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DecidedStrictness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DecidedStrictness) # gmapT :: (forall b. Data b => b -> b) -> DecidedStrictness -> DecidedStrictness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DecidedStrictness -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DecidedStrictness -> r # gmapQ :: (forall d. Data d => d -> u) -> DecidedStrictness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DecidedStrictness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DecidedStrictness -> m DecidedStrictness # | |
Data Bang | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bang -> c Bang # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bang # dataTypeOf :: Bang -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bang) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bang) # gmapT :: (forall b. Data b => b -> b) -> Bang -> Bang # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bang -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bang -> r # gmapQ :: (forall d. Data d => d -> u) -> Bang -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bang -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bang -> m Bang # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bang -> m Bang # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bang -> m Bang # | |
Data PatSynDir | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynDir -> c PatSynDir # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PatSynDir # toConstr :: PatSynDir -> Constr # dataTypeOf :: PatSynDir -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PatSynDir) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PatSynDir) # gmapT :: (forall b. Data b => b -> b) -> PatSynDir -> PatSynDir # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynDir -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynDir -> r # gmapQ :: (forall d. Data d => d -> u) -> PatSynDir -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynDir -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynDir -> m PatSynDir # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynDir -> m PatSynDir # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynDir -> m PatSynDir # | |
Data PatSynArgs | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynArgs -> c PatSynArgs # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PatSynArgs # toConstr :: PatSynArgs -> Constr # dataTypeOf :: PatSynArgs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PatSynArgs) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PatSynArgs) # gmapT :: (forall b. Data b => b -> b) -> PatSynArgs -> PatSynArgs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynArgs -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynArgs -> r # gmapQ :: (forall d. Data d => d -> u) -> PatSynArgs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynArgs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynArgs -> m PatSynArgs # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynArgs -> m PatSynArgs # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynArgs -> m PatSynArgs # | |
Data TyVarBndr | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyVarBndr -> c TyVarBndr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyVarBndr # toConstr :: TyVarBndr -> Constr # dataTypeOf :: TyVarBndr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyVarBndr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyVarBndr) # gmapT :: (forall b. Data b => b -> b) -> TyVarBndr -> TyVarBndr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyVarBndr -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyVarBndr -> r # gmapQ :: (forall d. Data d => d -> u) -> TyVarBndr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyVarBndr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyVarBndr -> m TyVarBndr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyVarBndr -> m TyVarBndr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyVarBndr -> m TyVarBndr # | |
Data FamilyResultSig | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyResultSig -> c FamilyResultSig # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FamilyResultSig # toConstr :: FamilyResultSig -> Constr # dataTypeOf :: FamilyResultSig -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FamilyResultSig) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FamilyResultSig) # gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig -> FamilyResultSig # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig -> r # gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig -> m FamilyResultSig # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig -> m FamilyResultSig # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig -> m FamilyResultSig # | |
Data TyLit | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyLit -> c TyLit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyLit # dataTypeOf :: TyLit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyLit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyLit) # gmapT :: (forall b. Data b => b -> b) -> TyLit -> TyLit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r # gmapQ :: (forall d. Data d => d -> u) -> TyLit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyLit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit # | |
Data Role | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Role # dataTypeOf :: Role -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Role) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Role) # gmapT :: (forall b. Data b => b -> b) -> Role -> Role # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r # gmapQ :: (forall d. Data d => d -> u) -> Role -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Role -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role -> m Role # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role # | |
Data AnnLookup | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnLookup -> c AnnLookup # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnLookup # toConstr :: AnnLookup -> Constr # dataTypeOf :: AnnLookup -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnLookup) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnLookup) # gmapT :: (forall b. Data b => b -> b) -> AnnLookup -> AnnLookup # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnLookup -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnLookup -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnLookup -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnLookup -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnLookup -> m AnnLookup # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnLookup -> m AnnLookup # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnLookup -> m AnnLookup # | |
Data DatatypeInfo | |
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DatatypeInfo -> c DatatypeInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DatatypeInfo # toConstr :: DatatypeInfo -> Constr # dataTypeOf :: DatatypeInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DatatypeInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DatatypeInfo) # gmapT :: (forall b. Data b => b -> b) -> DatatypeInfo -> DatatypeInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DatatypeInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DatatypeInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> DatatypeInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DatatypeInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DatatypeInfo -> m DatatypeInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DatatypeInfo -> m DatatypeInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DatatypeInfo -> m DatatypeInfo # | |
Data ConstructorVariant | |
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConstructorVariant -> c ConstructorVariant # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConstructorVariant # toConstr :: ConstructorVariant -> Constr # dataTypeOf :: ConstructorVariant -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConstructorVariant) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConstructorVariant) # gmapT :: (forall b. Data b => b -> b) -> ConstructorVariant -> ConstructorVariant # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConstructorVariant -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConstructorVariant -> r # gmapQ :: (forall d. Data d => d -> u) -> ConstructorVariant -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConstructorVariant -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConstructorVariant -> m ConstructorVariant # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstructorVariant -> m ConstructorVariant # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstructorVariant -> m ConstructorVariant # | |
Data FieldStrictness | |
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldStrictness -> c FieldStrictness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldStrictness # toConstr :: FieldStrictness -> Constr # dataTypeOf :: FieldStrictness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FieldStrictness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldStrictness) # gmapT :: (forall b. Data b => b -> b) -> FieldStrictness -> FieldStrictness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldStrictness -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldStrictness -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldStrictness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldStrictness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldStrictness -> m FieldStrictness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldStrictness -> m FieldStrictness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldStrictness -> m FieldStrictness # | |
Data Unpackedness | |
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Unpackedness -> c Unpackedness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Unpackedness # toConstr :: Unpackedness -> Constr # dataTypeOf :: Unpackedness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Unpackedness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unpackedness) # gmapT :: (forall b. Data b => b -> b) -> Unpackedness -> Unpackedness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Unpackedness -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Unpackedness -> r # gmapQ :: (forall d. Data d => d -> u) -> Unpackedness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Unpackedness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Unpackedness -> m Unpackedness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Unpackedness -> m Unpackedness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Unpackedness -> m Unpackedness # | |
Data Strictness | |
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Strictness -> c Strictness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Strictness # toConstr :: Strictness -> Constr # dataTypeOf :: Strictness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Strictness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Strictness) # gmapT :: (forall b. Data b => b -> b) -> Strictness -> Strictness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Strictness -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Strictness -> r # gmapQ :: (forall d. Data d => d -> u) -> Strictness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Strictness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Strictness -> m Strictness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Strictness -> m Strictness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Strictness -> m Strictness # | |
Data DataType | |
Defined in TH.ReifySimple Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataType -> c DataType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataType # toConstr :: DataType -> Constr # dataTypeOf :: DataType -> DataType0 # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataType) # gmapT :: (forall b. Data b => b -> b) -> DataType -> DataType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataType -> r # gmapQ :: (forall d. Data d => d -> u) -> DataType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataType -> m DataType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataType -> m DataType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataType -> m DataType # | |
Data DataCon | |
Defined in TH.ReifySimple Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataCon -> c DataCon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataCon # toConstr :: DataCon -> Constr # dataTypeOf :: DataCon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataCon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataCon) # gmapT :: (forall b. Data b => b -> b) -> DataCon -> DataCon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r # gmapQ :: (forall d. Data d => d -> u) -> DataCon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataCon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon # | |
Data DataFamily | |
Defined in TH.ReifySimple Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataFamily -> c DataFamily # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataFamily # toConstr :: DataFamily -> Constr # dataTypeOf :: DataFamily -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataFamily) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataFamily) # gmapT :: (forall b. Data b => b -> b) -> DataFamily -> DataFamily # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamily -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamily -> r # gmapQ :: (forall d. Data d => d -> u) -> DataFamily -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamily -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamily -> m DataFamily # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamily -> m DataFamily # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamily -> m DataFamily # | |
Data DataInst | |
Defined in TH.ReifySimple Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataInst -> c DataInst # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataInst # toConstr :: DataInst -> Constr # dataTypeOf :: DataInst -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataInst) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataInst) # gmapT :: (forall b. Data b => b -> b) -> DataInst -> DataInst # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataInst -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataInst -> r # gmapQ :: (forall d. Data d => d -> u) -> DataInst -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataInst -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataInst -> m DataInst # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataInst -> m DataInst # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataInst -> m DataInst # | |
Data TypeFamily | |
Defined in TH.ReifySimple Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeFamily -> c TypeFamily # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeFamily # toConstr :: TypeFamily -> Constr # dataTypeOf :: TypeFamily -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeFamily) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeFamily) # gmapT :: (forall b. Data b => b -> b) -> TypeFamily -> TypeFamily # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeFamily -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeFamily -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeFamily -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeFamily -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeFamily -> m TypeFamily # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeFamily -> m TypeFamily # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeFamily -> m TypeFamily # | |
Data TypeInst | |
Defined in TH.ReifySimple Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeInst -> c TypeInst # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeInst # toConstr :: TypeInst -> Constr # dataTypeOf :: TypeInst -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeInst) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeInst) # gmapT :: (forall b. Data b => b -> b) -> TypeInst -> TypeInst # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeInst -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeInst -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeInst -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeInst -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeInst -> m TypeInst # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeInst -> m TypeInst # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeInst -> m TypeInst # | |
Data UUID | |
Defined in Data.UUID.Types.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UUID -> c UUID # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UUID # dataTypeOf :: UUID -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UUID) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UUID) # gmapT :: (forall b. Data b => b -> b) -> UUID -> UUID # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r # gmapQ :: (forall d. Data d => d -> u) -> UUID -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UUID -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UUID -> m UUID # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID # | |
Data ZipException | |
Defined in Codec.Archive.Zip Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZipException -> c ZipException # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ZipException # toConstr :: ZipException -> Constr # dataTypeOf :: ZipException -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ZipException) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ZipException) # gmapT :: (forall b. Data b => b -> b) -> ZipException -> ZipException # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZipException -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZipException -> r # gmapQ :: (forall d. Data d => d -> u) -> ZipException -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ZipException -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZipException -> m ZipException # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipException -> m ZipException # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipException -> m ZipException # | |
Data Bytes128 Source # | |
Defined in Stack.StaticBytes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes128 -> c Bytes128 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes128 # toConstr :: Bytes128 -> Constr # dataTypeOf :: Bytes128 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes128) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes128) # gmapT :: (forall b. Data b => b -> b) -> Bytes128 -> Bytes128 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes128 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes128 -> r # gmapQ :: (forall d. Data d => d -> u) -> Bytes128 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes128 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128 # | |
Data Bytes64 Source # | |
Defined in Stack.StaticBytes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes64 -> c Bytes64 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes64 # toConstr :: Bytes64 -> Constr # dataTypeOf :: Bytes64 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes64) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes64) # gmapT :: (forall b. Data b => b -> b) -> Bytes64 -> Bytes64 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes64 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes64 -> r # gmapQ :: (forall d. Data d => d -> u) -> Bytes64 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes64 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64 # | |
Data Bytes32 Source # | |
Defined in Stack.StaticBytes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes32 -> c Bytes32 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes32 # toConstr :: Bytes32 -> Constr # dataTypeOf :: Bytes32 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes32) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes32) # gmapT :: (forall b. Data b => b -> b) -> Bytes32 -> Bytes32 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes32 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes32 -> r # gmapQ :: (forall d. Data d => d -> u) -> Bytes32 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes32 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32 # | |
Data Bytes16 Source # | |
Defined in Stack.StaticBytes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes16 -> c Bytes16 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes16 # toConstr :: Bytes16 -> Constr # dataTypeOf :: Bytes16 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes16) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes16) # gmapT :: (forall b. Data b => b -> b) -> Bytes16 -> Bytes16 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes16 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes16 -> r # gmapQ :: (forall d. Data d => d -> u) -> Bytes16 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes16 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16 # | |
Data Bytes8 Source # | |
Defined in Stack.StaticBytes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes8 -> c Bytes8 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes8 # toConstr :: Bytes8 -> Constr # dataTypeOf :: Bytes8 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes8) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes8) # gmapT :: (forall b. Data b => b -> b) -> Bytes8 -> Bytes8 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes8 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes8 -> r # gmapQ :: (forall d. Data d => d -> u) -> Bytes8 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes8 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8 # | |
Data FlagName Source # | |
Defined in Stack.Types.FlagName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FlagName -> c FlagName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FlagName # toConstr :: FlagName -> Constr # dataTypeOf :: FlagName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FlagName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FlagName) # gmapT :: (forall b. Data b => b -> b) -> FlagName -> FlagName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r # gmapQ :: (forall d. Data d => d -> u) -> FlagName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FlagName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # | |
Data GhcPkgId Source # | |
Defined in Stack.Types.GhcPkgId Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GhcPkgId -> c GhcPkgId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GhcPkgId # toConstr :: GhcPkgId -> Constr # dataTypeOf :: GhcPkgId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GhcPkgId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GhcPkgId) # gmapT :: (forall b. Data b => b -> b) -> GhcPkgId -> GhcPkgId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GhcPkgId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GhcPkgId -> r # gmapQ :: (forall d. Data d => d -> u) -> GhcPkgId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GhcPkgId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GhcPkgId -> m GhcPkgId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GhcPkgId -> m GhcPkgId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GhcPkgId -> m GhcPkgId # | |
Data PackageName Source # | |
Defined in Stack.Types.PackageName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageName -> c PackageName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageName # toConstr :: PackageName -> Constr # dataTypeOf :: PackageName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageName) # gmapT :: (forall b. Data b => b -> b) -> PackageName -> PackageName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageName -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName # | |
Data Version Source # | |
Defined in Stack.Types.Version Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version # toConstr :: Version -> Constr # dataTypeOf :: Version -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) # gmapT :: (forall b. Data b => b -> b) -> Version -> Version # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # | |
Data CabalFileInfo Source # | |
Defined in Stack.Types.PackageIdentifier Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CabalFileInfo -> c CabalFileInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CabalFileInfo # toConstr :: CabalFileInfo -> Constr # dataTypeOf :: CabalFileInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CabalFileInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CabalFileInfo) # gmapT :: (forall b. Data b => b -> b) -> CabalFileInfo -> CabalFileInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CabalFileInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CabalFileInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> CabalFileInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CabalFileInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CabalFileInfo -> m CabalFileInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CabalFileInfo -> m CabalFileInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CabalFileInfo -> m CabalFileInfo # | |
Data StaticSHA256 Source # | |
Defined in Stack.Types.PackageIdentifier Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StaticSHA256 -> c StaticSHA256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StaticSHA256 # toConstr :: StaticSHA256 -> Constr # dataTypeOf :: StaticSHA256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StaticSHA256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StaticSHA256) # gmapT :: (forall b. Data b => b -> b) -> StaticSHA256 -> StaticSHA256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StaticSHA256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StaticSHA256 -> r # gmapQ :: (forall d. Data d => d -> u) -> StaticSHA256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StaticSHA256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StaticSHA256 -> m StaticSHA256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StaticSHA256 -> m StaticSHA256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StaticSHA256 -> m StaticSHA256 # | |
Data CabalHash Source # | |
Defined in Stack.Types.PackageIdentifier Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CabalHash -> c CabalHash # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CabalHash # toConstr :: CabalHash -> Constr # dataTypeOf :: CabalHash -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CabalHash) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CabalHash) # gmapT :: (forall b. Data b => b -> b) -> CabalHash -> CabalHash # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CabalHash -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CabalHash -> r # gmapQ :: (forall d. Data d => d -> u) -> CabalHash -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CabalHash -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CabalHash -> m CabalHash # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CabalHash -> m CabalHash # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CabalHash -> m CabalHash # | |
Data PackageIdentifierRevision Source # | |
Defined in Stack.Types.PackageIdentifier Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageIdentifierRevision -> c PackageIdentifierRevision # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageIdentifierRevision # toConstr :: PackageIdentifierRevision -> Constr # dataTypeOf :: PackageIdentifierRevision -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageIdentifierRevision) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageIdentifierRevision) # gmapT :: (forall b. Data b => b -> b) -> PackageIdentifierRevision -> PackageIdentifierRevision # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifierRevision -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifierRevision -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageIdentifierRevision -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageIdentifierRevision -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageIdentifierRevision -> m PackageIdentifierRevision # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifierRevision -> m PackageIdentifierRevision # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifierRevision -> m PackageIdentifierRevision # | |
Data PackageIdentifier Source # | |
Defined in Stack.Types.PackageIdentifier Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageIdentifier -> c PackageIdentifier # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageIdentifier # toConstr :: PackageIdentifier -> Constr # dataTypeOf :: PackageIdentifier -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageIdentifier) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageIdentifier) # gmapT :: (forall b. Data b => b -> b) -> PackageIdentifier -> PackageIdentifier # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageIdentifier -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageIdentifier -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier # | |
Data PackageDownload Source # | |
Defined in Stack.Types.PackageIndex Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageDownload -> c PackageDownload # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageDownload # toConstr :: PackageDownload -> Constr # dataTypeOf :: PackageDownload -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageDownload) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageDownload) # gmapT :: (forall b. Data b => b -> b) -> PackageDownload -> PackageDownload # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageDownload -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageDownload -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageDownload -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageDownload -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageDownload -> m PackageDownload # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDownload -> m PackageDownload # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDownload -> m PackageDownload # | |
Data OffsetSize Source # | |
Defined in Stack.Types.PackageIndex Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OffsetSize -> c OffsetSize # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OffsetSize # toConstr :: OffsetSize -> Constr # dataTypeOf :: OffsetSize -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OffsetSize) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OffsetSize) # gmapT :: (forall b. Data b => b -> b) -> OffsetSize -> OffsetSize # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OffsetSize -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OffsetSize -> r # gmapQ :: (forall d. Data d => d -> u) -> OffsetSize -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OffsetSize -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OffsetSize -> m OffsetSize # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OffsetSize -> m OffsetSize # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OffsetSize -> m OffsetSize # | |
Data InstalledCacheEntry Source # | |
Defined in Stack.Types.PackageDump Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstalledCacheEntry -> c InstalledCacheEntry # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstalledCacheEntry # toConstr :: InstalledCacheEntry -> Constr # dataTypeOf :: InstalledCacheEntry -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InstalledCacheEntry) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstalledCacheEntry) # gmapT :: (forall b. Data b => b -> b) -> InstalledCacheEntry -> InstalledCacheEntry # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstalledCacheEntry -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstalledCacheEntry -> r # gmapQ :: (forall d. Data d => d -> u) -> InstalledCacheEntry -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InstalledCacheEntry -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstalledCacheEntry -> m InstalledCacheEntry # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstalledCacheEntry -> m InstalledCacheEntry # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstalledCacheEntry -> m InstalledCacheEntry # | |
Data InstalledCacheInner Source # | |
Defined in Stack.Types.PackageDump Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstalledCacheInner -> c InstalledCacheInner # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstalledCacheInner # toConstr :: InstalledCacheInner -> Constr # dataTypeOf :: InstalledCacheInner -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InstalledCacheInner) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstalledCacheInner) # gmapT :: (forall b. Data b => b -> b) -> InstalledCacheInner -> InstalledCacheInner # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstalledCacheInner -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstalledCacheInner -> r # gmapQ :: (forall d. Data d => d -> u) -> InstalledCacheInner -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InstalledCacheInner -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstalledCacheInner -> m InstalledCacheInner # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstalledCacheInner -> m InstalledCacheInner # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstalledCacheInner -> m InstalledCacheInner # | |
Data SnapshotHash Source # | |
Defined in Stack.Types.Resolver Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SnapshotHash -> c SnapshotHash # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SnapshotHash # toConstr :: SnapshotHash -> Constr # dataTypeOf :: SnapshotHash -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SnapshotHash) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SnapshotHash) # gmapT :: (forall b. Data b => b -> b) -> SnapshotHash -> SnapshotHash # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SnapshotHash -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SnapshotHash -> r # gmapQ :: (forall d. Data d => d -> u) -> SnapshotHash -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SnapshotHash -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SnapshotHash -> m SnapshotHash # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SnapshotHash -> m SnapshotHash # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SnapshotHash -> m SnapshotHash # | |
Data SnapName Source # | |
Defined in Stack.Types.Resolver Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SnapName -> c SnapName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SnapName # toConstr :: SnapName -> Constr # dataTypeOf :: SnapName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SnapName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SnapName) # gmapT :: (forall b. Data b => b -> b) -> SnapName -> SnapName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SnapName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SnapName -> r # gmapQ :: (forall d. Data d => d -> u) -> SnapName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SnapName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SnapName -> m SnapName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SnapName -> m SnapName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SnapName -> m SnapName # | |
Data VersionIntervals Source # | |
Defined in Stack.Types.VersionIntervals Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VersionIntervals -> c VersionIntervals # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VersionIntervals # toConstr :: VersionIntervals -> Constr # dataTypeOf :: VersionIntervals -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VersionIntervals) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VersionIntervals) # gmapT :: (forall b. Data b => b -> b) -> VersionIntervals -> VersionIntervals # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VersionIntervals -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VersionIntervals -> r # gmapQ :: (forall d. Data d => d -> u) -> VersionIntervals -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionIntervals -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VersionIntervals -> m VersionIntervals # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionIntervals -> m VersionIntervals # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionIntervals -> m VersionIntervals # | |
Data ModuleInfo Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleInfo -> c ModuleInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleInfo # toConstr :: ModuleInfo -> Constr # dataTypeOf :: ModuleInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleInfo) # gmapT :: (forall b. Data b => b -> b) -> ModuleInfo -> ModuleInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> ModuleInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleInfo -> m ModuleInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleInfo -> m ModuleInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleInfo -> m ModuleInfo # | |
Data ModuleName Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleName -> c ModuleName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleName # toConstr :: ModuleName -> Constr # dataTypeOf :: ModuleName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleName) # gmapT :: (forall b. Data b => b -> b) -> ModuleName -> ModuleName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r # gmapQ :: (forall d. Data d => d -> u) -> ModuleName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName # | |
Data LoadedSnapshot Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LoadedSnapshot -> c LoadedSnapshot # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LoadedSnapshot # toConstr :: LoadedSnapshot -> Constr # dataTypeOf :: LoadedSnapshot -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LoadedSnapshot) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LoadedSnapshot) # gmapT :: (forall b. Data b => b -> b) -> LoadedSnapshot -> LoadedSnapshot # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LoadedSnapshot -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LoadedSnapshot -> r # gmapQ :: (forall d. Data d => d -> u) -> LoadedSnapshot -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LoadedSnapshot -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LoadedSnapshot -> m LoadedSnapshot # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LoadedSnapshot -> m LoadedSnapshot # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LoadedSnapshot -> m LoadedSnapshot # | |
Data ExeName Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExeName -> c ExeName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExeName # toConstr :: ExeName -> Constr # dataTypeOf :: ExeName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExeName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExeName) # gmapT :: (forall b. Data b => b -> b) -> ExeName -> ExeName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExeName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExeName -> r # gmapQ :: (forall d. Data d => d -> u) -> ExeName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExeName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExeName -> m ExeName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExeName -> m ExeName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExeName -> m ExeName # | |
Data Subdirs Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Subdirs -> c Subdirs # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Subdirs # toConstr :: Subdirs -> Constr # dataTypeOf :: Subdirs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Subdirs) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Subdirs) # gmapT :: (forall b. Data b => b -> b) -> Subdirs -> Subdirs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Subdirs -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Subdirs -> r # gmapQ :: (forall d. Data d => d -> u) -> Subdirs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Subdirs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Subdirs -> m Subdirs # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Subdirs -> m Subdirs # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Subdirs -> m Subdirs # | |
Data RepoType Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoType -> c RepoType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoType # toConstr :: RepoType -> Constr # dataTypeOf :: RepoType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RepoType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoType) # gmapT :: (forall b. Data b => b -> b) -> RepoType -> RepoType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoType -> r # gmapQ :: (forall d. Data d => d -> u) -> RepoType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType # | |
Data SnapshotDef Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SnapshotDef -> c SnapshotDef # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SnapshotDef # toConstr :: SnapshotDef -> Constr # dataTypeOf :: SnapshotDef -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SnapshotDef) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SnapshotDef) # gmapT :: (forall b. Data b => b -> b) -> SnapshotDef -> SnapshotDef # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SnapshotDef -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SnapshotDef -> r # gmapQ :: (forall d. Data d => d -> u) -> SnapshotDef -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SnapshotDef -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SnapshotDef -> m SnapshotDef # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SnapshotDef -> m SnapshotDef # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SnapshotDef -> m SnapshotDef # | |
Data ModTime Source # | |
Defined in Stack.Types.Package Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModTime -> c ModTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModTime # toConstr :: ModTime -> Constr # dataTypeOf :: ModTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModTime) # gmapT :: (forall b. Data b => b -> b) -> ModTime -> ModTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModTime -> r # gmapQ :: (forall d. Data d => d -> u) -> ModTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModTime -> m ModTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModTime -> m ModTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModTime -> m ModTime # | |
Data FileCacheInfo Source # | |
Defined in Stack.Types.Package Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileCacheInfo -> c FileCacheInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FileCacheInfo # toConstr :: FileCacheInfo -> Constr # dataTypeOf :: FileCacheInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FileCacheInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FileCacheInfo) # gmapT :: (forall b. Data b => b -> b) -> FileCacheInfo -> FileCacheInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileCacheInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileCacheInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> FileCacheInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FileCacheInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileCacheInfo -> m FileCacheInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileCacheInfo -> m FileCacheInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileCacheInfo -> m FileCacheInfo # | |
Data PrecompiledCache Source # | |
Defined in Stack.Types.Build Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrecompiledCache -> c PrecompiledCache # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrecompiledCache # toConstr :: PrecompiledCache -> Constr # dataTypeOf :: PrecompiledCache -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrecompiledCache) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrecompiledCache) # gmapT :: (forall b. Data b => b -> b) -> PrecompiledCache -> PrecompiledCache # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrecompiledCache -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrecompiledCache -> r # gmapQ :: (forall d. Data d => d -> u) -> PrecompiledCache -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PrecompiledCache -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrecompiledCache -> m PrecompiledCache # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrecompiledCache -> m PrecompiledCache # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrecompiledCache -> m PrecompiledCache # | |
Data ConfigureOpts Source # | |
Defined in Stack.Types.Build Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConfigureOpts -> c ConfigureOpts # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConfigureOpts # toConstr :: ConfigureOpts -> Constr # dataTypeOf :: ConfigureOpts -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConfigureOpts) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConfigureOpts) # gmapT :: (forall b. Data b => b -> b) -> ConfigureOpts -> ConfigureOpts # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r # gmapQ :: (forall d. Data d => d -> u) -> ConfigureOpts -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConfigureOpts -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts # | |
Data CachePkgSrc Source # | |
Defined in Stack.Types.Build Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CachePkgSrc -> c CachePkgSrc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CachePkgSrc # toConstr :: CachePkgSrc -> Constr # dataTypeOf :: CachePkgSrc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CachePkgSrc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CachePkgSrc) # gmapT :: (forall b. Data b => b -> b) -> CachePkgSrc -> CachePkgSrc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CachePkgSrc -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CachePkgSrc -> r # gmapQ :: (forall d. Data d => d -> u) -> CachePkgSrc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CachePkgSrc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CachePkgSrc -> m CachePkgSrc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CachePkgSrc -> m CachePkgSrc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CachePkgSrc -> m CachePkgSrc # | |
Data ConfigCache Source # | |
Defined in Stack.Types.Build Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConfigCache -> c ConfigCache # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConfigCache # toConstr :: ConfigCache -> Constr # dataTypeOf :: ConfigCache -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConfigCache) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConfigCache) # gmapT :: (forall b. Data b => b -> b) -> ConfigCache -> ConfigCache # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConfigCache -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConfigCache -> r # gmapQ :: (forall d. Data d => d -> u) -> ConfigCache -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConfigCache -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConfigCache -> m ConfigCache # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigCache -> m ConfigCache # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigCache -> m ConfigCache # | |
Data BuildCache Source # | |
Defined in Stack.Types.Build Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuildCache -> c BuildCache # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuildCache # toConstr :: BuildCache -> Constr # dataTypeOf :: BuildCache -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BuildCache) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildCache) # gmapT :: (forall b. Data b => b -> b) -> BuildCache -> BuildCache # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuildCache -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuildCache -> r # gmapQ :: (forall d. Data d => d -> u) -> BuildCache -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BuildCache -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuildCache -> m BuildCache # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildCache -> m BuildCache # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildCache -> m BuildCache # | |
Data a => Data [a] | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> [a] -> c [a] # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c [a] # dataTypeOf :: [a] -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c [a]) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c [a]) # gmapT :: (forall b. Data b => b -> b) -> [a] -> [a] # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> [a] -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> [a] -> r # gmapQ :: (forall d. Data d => d -> u) -> [a] -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> [a] -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> [a] -> m [a] # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> [a] -> m [a] # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> [a] -> m [a] # | |
Data a => Data (Maybe a) | Since: base-4.0.0.0 |
Defined in Data.Data 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) # | |
(Data a, Integral a) => Data (Ratio a) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ratio a -> c (Ratio a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ratio a) # toConstr :: Ratio a -> Constr # dataTypeOf :: Ratio a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ratio a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ratio a)) # gmapT :: (forall b. Data b => b -> b) -> Ratio a -> Ratio a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ratio a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ratio a -> r # gmapQ :: (forall d. Data d => d -> u) -> Ratio a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ratio a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ratio a -> m (Ratio a) # | |
Data a => Data (Ptr a) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ptr a -> c (Ptr a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) # dataTypeOf :: Ptr a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) # gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r # gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) # | |
Data p => Data (Par1 p) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Par1 p -> c (Par1 p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Par1 p) # toConstr :: Par1 p -> Constr # dataTypeOf :: Par1 p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Par1 p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Par1 p)) # gmapT :: (forall b. Data b => b -> b) -> Par1 p -> Par1 p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Par1 p -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Par1 p -> r # gmapQ :: (forall d. Data d => d -> u) -> Par1 p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Par1 p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Par1 p -> m (Par1 p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Par1 p -> m (Par1 p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Par1 p -> m (Par1 p) # | |
Data a => Data (Last a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Last a -> c (Last a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Last a) # toConstr :: Last a -> Constr # dataTypeOf :: Last a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Last a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Last a)) # gmapT :: (forall b. Data b => b -> b) -> Last a -> Last a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQ :: (forall d. Data d => d -> u) -> Last a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Last a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # | |
Data a => Data (VersionRangeF a) | |
Defined in Distribution.Types.VersionRange Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VersionRangeF a -> c (VersionRangeF a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VersionRangeF a) # toConstr :: VersionRangeF a -> Constr # dataTypeOf :: VersionRangeF a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (VersionRangeF a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VersionRangeF a)) # gmapT :: (forall b. Data b => b -> b) -> VersionRangeF a -> VersionRangeF a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r # gmapQ :: (forall d. Data d => d -> u) -> VersionRangeF a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionRangeF a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VersionRangeF a -> m (VersionRangeF a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRangeF a -> m (VersionRangeF a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRangeF a -> m (VersionRangeF a) # | |
Data c => Data (Condition c) | |
Defined in Distribution.Types.Condition Methods gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> Condition c -> c0 (Condition c) # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (Condition c) # toConstr :: Condition c -> Constr # dataTypeOf :: Condition c -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (Condition c)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (Condition c)) # gmapT :: (forall b. Data b => b -> b) -> Condition c -> Condition c # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Condition c -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Condition c -> r # gmapQ :: (forall d. Data d => d -> u) -> Condition c -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Condition c -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Condition c -> m (Condition c) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition c -> m (Condition c) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition c -> m (Condition c) # | |
Data vertex => Data (SCC vertex) | Since: containers-0.5.9 |
Defined in Data.Graph Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SCC vertex -> c (SCC vertex) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SCC vertex) # toConstr :: SCC vertex -> Constr # dataTypeOf :: SCC vertex -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SCC vertex)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SCC vertex)) # gmapT :: (forall b. Data b => b -> b) -> SCC vertex -> SCC vertex # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r # gmapQ :: (forall d. Data d => d -> u) -> SCC vertex -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SCC vertex -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) # | |
Data a => Data (ForeignPtr a) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignPtr a -> c (ForeignPtr a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignPtr a) # toConstr :: ForeignPtr a -> Constr # dataTypeOf :: ForeignPtr a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignPtr a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignPtr a)) # gmapT :: (forall b. Data b => b -> b) -> ForeignPtr a -> ForeignPtr a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignPtr a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignPtr a -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignPtr a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignPtr a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignPtr a -> m (ForeignPtr a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignPtr a -> m (ForeignPtr a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignPtr a -> m (ForeignPtr a) # | |
Data a => Data (Complex a) | Since: base-2.1 |
Defined in Data.Complex Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Complex a -> c (Complex a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Complex a) # toConstr :: Complex a -> Constr # dataTypeOf :: Complex a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Complex a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Complex a)) # gmapT :: (forall b. Data b => b -> b) -> Complex a -> Complex a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Complex a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Complex a -> r # gmapQ :: (forall d. Data d => d -> u) -> Complex a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Complex a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) # | |
Typeable a => Data (Fixed a) | Since: base-4.1.0.0 |
Defined in Data.Fixed Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixed a -> c (Fixed a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Fixed a) # toConstr :: Fixed a -> Constr # dataTypeOf :: Fixed a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Fixed a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Fixed a)) # gmapT :: (forall b. Data b => b -> b) -> Fixed a -> Fixed a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixed a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixed a -> r # gmapQ :: (forall d. Data d => d -> u) -> Fixed a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixed a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixed a -> m (Fixed a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixed a -> m (Fixed a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixed a -> m (Fixed a) # | |
Data a => Data (Min a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Min a -> c (Min a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Min a) # dataTypeOf :: Min a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Min a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Min a)) # gmapT :: (forall b. Data b => b -> b) -> Min a -> Min a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r # gmapQ :: (forall d. Data d => d -> u) -> Min a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Min a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # | |
Data a => Data (Max a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Max a -> c (Max a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Max a) # dataTypeOf :: Max a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Max a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Max a)) # gmapT :: (forall b. Data b => b -> b) -> Max a -> Max a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r # gmapQ :: (forall d. Data d => d -> u) -> Max a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Max a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # | |
Data a => Data (First a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> First a -> c (First a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (First a) # toConstr :: First a -> Constr # dataTypeOf :: First a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (First a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (First a)) # gmapT :: (forall b. Data b => b -> b) -> First a -> First a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQ :: (forall d. Data d => d -> u) -> First a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> First a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # | |
Data m => Data (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WrappedMonoid m -> c (WrappedMonoid m) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WrappedMonoid m) # toConstr :: WrappedMonoid m -> Constr # dataTypeOf :: WrappedMonoid m -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WrappedMonoid m)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WrappedMonoid m)) # gmapT :: (forall b. Data b => b -> b) -> WrappedMonoid m -> WrappedMonoid m # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WrappedMonoid m -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WrappedMonoid m -> r # gmapQ :: (forall d. Data d => d -> u) -> WrappedMonoid m -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WrappedMonoid m -> u # gmapM :: Monad m0 => (forall d. Data d => d -> m0 d) -> WrappedMonoid m -> m0 (WrappedMonoid m) # gmapMp :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> WrappedMonoid m -> m0 (WrappedMonoid m) # gmapMo :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> WrappedMonoid m -> m0 (WrappedMonoid m) # | |
Data a => Data (Option a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Option a -> c (Option a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Option a) # toConstr :: Option a -> Constr # dataTypeOf :: Option a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Option a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Option a)) # gmapT :: (forall b. Data b => b -> b) -> Option a -> Option a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Option a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Option a -> r # gmapQ :: (forall d. Data d => d -> u) -> Option a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Option a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Option a -> m (Option a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Option a -> m (Option a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Option a -> m (Option a) # | |
Data a => Data (Identity a) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identity a -> c (Identity a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Identity a) # toConstr :: Identity a -> Constr # dataTypeOf :: Identity a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Identity a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Identity a)) # gmapT :: (forall b. Data b => b -> b) -> Identity a -> Identity a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r # gmapQ :: (forall d. Data d => d -> u) -> Identity a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Identity a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) # | |
Data a => Data (First a) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> First a -> c (First a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (First a) # toConstr :: First a -> Constr # dataTypeOf :: First a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (First a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (First a)) # gmapT :: (forall b. Data b => b -> b) -> First a -> First a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQ :: (forall d. Data d => d -> u) -> First a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> First a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # | |
Data a => Data (Last a) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Last a -> c (Last a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Last a) # toConstr :: Last a -> Constr # dataTypeOf :: Last a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Last a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Last a)) # gmapT :: (forall b. Data b => b -> b) -> Last a -> Last a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQ :: (forall d. Data d => d -> u) -> Last a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Last a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # | |
Data a => Data (Dual a) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dual a -> c (Dual a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dual a) # toConstr :: Dual a -> Constr # dataTypeOf :: Dual a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dual a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dual a)) # gmapT :: (forall b. Data b => b -> b) -> Dual a -> Dual a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dual a -> r # gmapQ :: (forall d. Data d => d -> u) -> Dual a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dual a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dual a -> m (Dual a) # | |
Data a => Data (Sum a) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum a -> c (Sum a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum a) # dataTypeOf :: Sum a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum a)) # gmapT :: (forall b. Data b => b -> b) -> Sum a -> Sum a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r # gmapQ :: (forall d. Data d => d -> u) -> Sum a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # | |
Data a => Data (Product a) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Product a -> c (Product a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product a) # toConstr :: Product a -> Constr # dataTypeOf :: Product a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product a)) # gmapT :: (forall b. Data b => b -> b) -> Product a -> Product a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product a -> r # gmapQ :: (forall d. Data d => d -> u) -> Product a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Product a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Product a -> m (Product a) # | |
Data a => Data (Down a) | Since: base-4.12.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Down a -> c (Down a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Down a) # toConstr :: Down a -> Constr # dataTypeOf :: Down a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Down a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Down a)) # gmapT :: (forall b. Data b => b -> b) -> Down a -> Down a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Down a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Down a -> r # gmapQ :: (forall d. Data d => d -> u) -> Down a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Down a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) # | |
Data a => Data (NonEmpty a) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonEmpty a -> c (NonEmpty a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonEmpty a) # toConstr :: NonEmpty a -> Constr # dataTypeOf :: NonEmpty a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NonEmpty a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonEmpty a)) # gmapT :: (forall b. Data b => b -> b) -> NonEmpty a -> NonEmpty a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r # gmapQ :: (forall d. Data d => d -> u) -> NonEmpty a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NonEmpty a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) # | |
Data ty => Data (UArray ty) | |
Defined in Basement.UArray.Base Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UArray ty -> c (UArray ty) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (UArray ty) # toConstr :: UArray ty -> Constr # dataTypeOf :: UArray ty -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (UArray ty)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (UArray ty)) # gmapT :: (forall b. Data b => b -> b) -> UArray ty -> UArray ty # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UArray ty -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UArray ty -> r # gmapQ :: (forall d. Data d => d -> u) -> UArray ty -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UArray ty -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) # | |
Data ty => Data (Block ty) | |
Defined in Basement.Block.Base Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block ty -> c (Block ty) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Block ty) # toConstr :: Block ty -> Constr # dataTypeOf :: Block ty -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Block ty)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Block ty)) # gmapT :: (forall b. Data b => b -> b) -> Block ty -> Block ty # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block ty -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block ty -> r # gmapQ :: (forall d. Data d => d -> u) -> Block ty -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Block ty -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Block ty -> m (Block ty) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Block ty -> m (Block ty) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Block ty -> m (Block ty) # | |
Data s => Data (CI s) | |
Defined in Data.CaseInsensitive.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CI s -> c (CI s) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CI s) # dataTypeOf :: CI s -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CI s)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CI s)) # gmapT :: (forall b. Data b => b -> b) -> CI s -> CI s # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CI s -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CI s -> r # gmapQ :: (forall d. Data d => d -> u) -> CI s -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CI s -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CI s -> m (CI s) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CI s -> m (CI s) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CI s -> m (CI s) # | |
Data a => Data (IntMap a) | |
Defined in Data.IntMap.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntMap a -> c (IntMap a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IntMap a) # toConstr :: IntMap a -> Constr # dataTypeOf :: IntMap a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IntMap a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IntMap a)) # gmapT :: (forall b. Data b => b -> b) -> IntMap a -> IntMap a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntMap a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntMap a -> r # gmapQ :: (forall d. Data d => d -> u) -> IntMap a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IntMap a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntMap a -> m (IntMap a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntMap a -> m (IntMap a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntMap a -> m (IntMap a) # | |
Data a => Data (Tree a) | |
Defined in Data.Tree Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tree a -> c (Tree a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tree a) # toConstr :: Tree a -> Constr # dataTypeOf :: Tree a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tree a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tree a)) # gmapT :: (forall b. Data b => b -> b) -> Tree a -> Tree a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r # gmapQ :: (forall d. Data d => d -> u) -> Tree a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tree a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) # | |
Data a => Data (Seq a) | |
Defined in Data.Sequence.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) # dataTypeOf :: Seq a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) # gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # | |
Data a => Data (ViewL a) | |
Defined in Data.Sequence.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ViewL a -> c (ViewL a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ViewL a) # toConstr :: ViewL a -> Constr # dataTypeOf :: ViewL a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ViewL a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ViewL a)) # gmapT :: (forall b. Data b => b -> b) -> ViewL a -> ViewL a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ViewL a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ViewL a -> r # gmapQ :: (forall d. Data d => d -> u) -> ViewL a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ViewL a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ViewL a -> m (ViewL a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewL a -> m (ViewL a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewL a -> m (ViewL a) # | |
Data a => Data (ViewR a) | |
Defined in Data.Sequence.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ViewR a -> c (ViewR a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ViewR a) # toConstr :: ViewR a -> Constr # dataTypeOf :: ViewR a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ViewR a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ViewR a)) # gmapT :: (forall b. Data b => b -> b) -> ViewR a -> ViewR a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ViewR a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ViewR a -> r # gmapQ :: (forall d. Data d => d -> u) -> ViewR a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ViewR a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ViewR a -> m (ViewR a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewR a -> m (ViewR a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewR a -> m (ViewR a) # | |
(Data a, Ord a) => Data (Set a) | |
Defined in Data.Set.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) # dataTypeOf :: Set a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) # gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # | |
Data a => Data (LenientData a) | |
Defined in Web.Internal.HttpApiData Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LenientData a -> c (LenientData a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LenientData a) # toConstr :: LenientData a -> Constr # dataTypeOf :: LenientData a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LenientData a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LenientData a)) # gmapT :: (forall b. Data b => b -> b) -> LenientData a -> LenientData a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LenientData a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LenientData a -> r # gmapQ :: (forall d. Data d => d -> u) -> LenientData a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LenientData a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LenientData a -> m (LenientData a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LenientData a -> m (LenientData a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LenientData a -> m (LenientData a) # | |
Data mono => Data (NonNull mono) | |
Defined in Data.NonNull Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonNull mono -> c (NonNull mono) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonNull mono) # toConstr :: NonNull mono -> Constr # dataTypeOf :: NonNull mono -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NonNull mono)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonNull mono)) # gmapT :: (forall b. Data b => b -> b) -> NonNull mono -> NonNull mono # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonNull mono -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonNull mono -> r # gmapQ :: (forall d. Data d => d -> u) -> NonNull mono -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NonNull mono -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono) # | |
Typeable s => Data (MutableByteArray s) | |
Defined in Data.Primitive.ByteArray Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MutableByteArray s -> c (MutableByteArray s) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MutableByteArray s) # toConstr :: MutableByteArray s -> Constr # dataTypeOf :: MutableByteArray s -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MutableByteArray s)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MutableByteArray s)) # gmapT :: (forall b. Data b => b -> b) -> MutableByteArray s -> MutableByteArray s # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MutableByteArray s -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MutableByteArray s -> r # gmapQ :: (forall d. Data d => d -> u) -> MutableByteArray s -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MutableByteArray s -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MutableByteArray s -> m (MutableByteArray s) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableByteArray s -> m (MutableByteArray s) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableByteArray s -> m (MutableByteArray s) # | |
Data a => Data (SmallArray a) | |
Defined in Data.Primitive.SmallArray Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SmallArray a -> c (SmallArray a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SmallArray a) # toConstr :: SmallArray a -> Constr # dataTypeOf :: SmallArray a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SmallArray a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SmallArray a)) # gmapT :: (forall b. Data b => b -> b) -> SmallArray a -> SmallArray a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SmallArray a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SmallArray a -> r # gmapQ :: (forall d. Data d => d -> u) -> SmallArray a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SmallArray a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SmallArray a -> m (SmallArray a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallArray a -> m (SmallArray a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallArray a -> m (SmallArray a) # | |
Data a => Data (Array a) | |
Defined in Data.Primitive.Array Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Array a -> c (Array a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array a) # toConstr :: Array a -> Constr # dataTypeOf :: Array a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Array a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array a)) # gmapT :: (forall b. Data b => b -> b) -> Array a -> Array a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array a -> r # gmapQ :: (forall d. Data d => d -> u) -> Array a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Array a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # | |
Data a => Data (Vector a) | |
Defined in Data.Vector Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) # toConstr :: Vector a -> Constr # dataTypeOf :: Vector a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) # gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # | |
(Data a, Storable a) => Data (Vector a) | |
Defined in Data.Vector.Storable Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) # toConstr :: Vector a -> Constr # dataTypeOf :: Vector a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) # gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # | |
(Data a, Unbox a) => Data (Vector a) | |
Defined in Data.Vector.Unboxed.Base Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) # toConstr :: Vector a -> Constr # dataTypeOf :: Vector a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) # gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # | |
(Data a, Eq a, Hashable a) => Data (HashSet a) | |
Defined in Data.HashSet Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashSet a -> c (HashSet a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashSet a) # toConstr :: HashSet a -> Constr # dataTypeOf :: HashSet a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HashSet a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashSet a)) # gmapT :: (forall b. Data b => b -> b) -> HashSet a -> HashSet a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashSet a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashSet a -> r # gmapQ :: (forall d. Data d => d -> u) -> HashSet a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HashSet a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # | |
Data a => Data (VersionConfig a) | |
Defined in Data.Store.Version Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VersionConfig a -> c (VersionConfig a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VersionConfig a) # toConstr :: VersionConfig a -> Constr # dataTypeOf :: VersionConfig a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (VersionConfig a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VersionConfig a)) # gmapT :: (forall b. Data b => b -> b) -> VersionConfig a -> VersionConfig a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VersionConfig a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VersionConfig a -> r # gmapQ :: (forall d. Data d => d -> u) -> VersionConfig a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionConfig a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VersionConfig a -> m (VersionConfig a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionConfig a -> m (VersionConfig a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionConfig a -> m (VersionConfig a) # | |
(Data a, Prim a) => Data (Vector a) | |
Defined in Data.Vector.Primitive Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) # toConstr :: Vector a -> Constr # dataTypeOf :: Vector a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) # gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # | |
Data index => Data (PackageCache index) Source # | |
Defined in Stack.Types.PackageIndex Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageCache index -> c (PackageCache index) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PackageCache index) # toConstr :: PackageCache index -> Constr # dataTypeOf :: PackageCache index -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PackageCache index)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PackageCache index)) # gmapT :: (forall b. Data b => b -> b) -> PackageCache index -> PackageCache index # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageCache index -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageCache index -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageCache index -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageCache index -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageCache index -> m (PackageCache index) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageCache index -> m (PackageCache index) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageCache index -> m (PackageCache index) # | |
Typeable cvType => Data (CompilerVersion cvType) Source # | |
Defined in Stack.Types.Compiler Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompilerVersion cvType -> c (CompilerVersion cvType) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CompilerVersion cvType) # toConstr :: CompilerVersion cvType -> Constr # dataTypeOf :: CompilerVersion cvType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CompilerVersion cvType)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CompilerVersion cvType)) # gmapT :: (forall b. Data b => b -> b) -> CompilerVersion cvType -> CompilerVersion cvType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompilerVersion cvType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompilerVersion cvType -> r # gmapQ :: (forall d. Data d => d -> u) -> CompilerVersion cvType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CompilerVersion cvType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompilerVersion cvType -> m (CompilerVersion cvType) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompilerVersion cvType -> m (CompilerVersion cvType) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompilerVersion cvType -> m (CompilerVersion cvType) # | |
Data customContents => Data (ResolverWith customContents) Source # | |
Defined in Stack.Types.Resolver Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResolverWith customContents -> c (ResolverWith customContents) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ResolverWith customContents) # toConstr :: ResolverWith customContents -> Constr # dataTypeOf :: ResolverWith customContents -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ResolverWith customContents)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ResolverWith customContents)) # gmapT :: (forall b. Data b => b -> b) -> ResolverWith customContents -> ResolverWith customContents # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResolverWith customContents -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResolverWith customContents -> r # gmapQ :: (forall d. Data d => d -> u) -> ResolverWith customContents -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ResolverWith customContents -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResolverWith customContents -> m (ResolverWith customContents) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResolverWith customContents -> m (ResolverWith customContents) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResolverWith customContents -> m (ResolverWith customContents) # | |
Data loc => Data (LoadedPackageInfo loc) Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LoadedPackageInfo loc -> c (LoadedPackageInfo loc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LoadedPackageInfo loc) # toConstr :: LoadedPackageInfo loc -> Constr # dataTypeOf :: LoadedPackageInfo loc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LoadedPackageInfo loc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LoadedPackageInfo loc)) # gmapT :: (forall b. Data b => b -> b) -> LoadedPackageInfo loc -> LoadedPackageInfo loc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LoadedPackageInfo loc -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LoadedPackageInfo loc -> r # gmapQ :: (forall d. Data d => d -> u) -> LoadedPackageInfo loc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LoadedPackageInfo loc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LoadedPackageInfo loc -> m (LoadedPackageInfo loc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LoadedPackageInfo loc -> m (LoadedPackageInfo loc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LoadedPackageInfo loc -> m (LoadedPackageInfo loc) # | |
Data subdirs => Data (Repo subdirs) Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Repo subdirs -> c (Repo subdirs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Repo subdirs) # toConstr :: Repo subdirs -> Constr # dataTypeOf :: Repo subdirs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Repo subdirs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Repo subdirs)) # gmapT :: (forall b. Data b => b -> b) -> Repo subdirs -> Repo subdirs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Repo subdirs -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Repo subdirs -> r # gmapQ :: (forall d. Data d => d -> u) -> Repo subdirs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Repo subdirs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Repo subdirs -> m (Repo subdirs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Repo subdirs -> m (Repo subdirs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Repo subdirs -> m (Repo subdirs) # | |
Data subdirs => Data (Archive subdirs) Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Archive subdirs -> c (Archive subdirs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Archive subdirs) # toConstr :: Archive subdirs -> Constr # dataTypeOf :: Archive subdirs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Archive subdirs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Archive subdirs)) # gmapT :: (forall b. Data b => b -> b) -> Archive subdirs -> Archive subdirs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Archive subdirs -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Archive subdirs -> r # gmapQ :: (forall d. Data d => d -> u) -> Archive subdirs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Archive subdirs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Archive subdirs -> m (Archive subdirs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Archive subdirs -> m (Archive subdirs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Archive subdirs -> m (Archive subdirs) # | |
Data subdirs => Data (PackageLocationIndex subdirs) Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageLocationIndex subdirs -> c (PackageLocationIndex subdirs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PackageLocationIndex subdirs) # toConstr :: PackageLocationIndex subdirs -> Constr # dataTypeOf :: PackageLocationIndex subdirs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PackageLocationIndex subdirs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PackageLocationIndex subdirs)) # gmapT :: (forall b. Data b => b -> b) -> PackageLocationIndex subdirs -> PackageLocationIndex subdirs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageLocationIndex subdirs -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageLocationIndex subdirs -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageLocationIndex subdirs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageLocationIndex subdirs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageLocationIndex subdirs -> m (PackageLocationIndex subdirs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageLocationIndex subdirs -> m (PackageLocationIndex subdirs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageLocationIndex subdirs -> m (PackageLocationIndex subdirs) # | |
Data subdirs => Data (PackageLocation subdirs) Source # | |
Defined in Stack.Types.BuildPlan Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageLocation subdirs -> c (PackageLocation subdirs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PackageLocation subdirs) # toConstr :: PackageLocation subdirs -> Constr # dataTypeOf :: PackageLocation subdirs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PackageLocation subdirs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PackageLocation subdirs)) # gmapT :: (forall b. Data b => b -> b) -> PackageLocation subdirs -> PackageLocation subdirs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageLocation subdirs -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageLocation subdirs -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageLocation subdirs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageLocation subdirs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageLocation subdirs -> m (PackageLocation subdirs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageLocation subdirs -> m (PackageLocation subdirs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageLocation subdirs -> m (PackageLocation subdirs) # | |
(Data a, Data b) => Data (Either a b) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Either a b -> c (Either a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) # toConstr :: Either a b -> Constr # dataTypeOf :: Either a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r # gmapQr :: (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) # | |
Data p => Data (V1 p) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V1 p -> c (V1 p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V1 p) # dataTypeOf :: V1 p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V1 p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 p)) # gmapT :: (forall b. Data b => b -> b) -> V1 p -> V1 p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r # gmapQ :: (forall d. Data d => d -> u) -> V1 p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> V1 p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) # | |
Data p => Data (U1 p) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> U1 p -> c (U1 p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (U1 p) # dataTypeOf :: U1 p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (U1 p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (U1 p)) # gmapT :: (forall b. Data b => b -> b) -> U1 p -> U1 p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r # gmapQ :: (forall d. Data d => d -> u) -> U1 p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> U1 p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) # | |
(Data a, Data b) => Data (a, b) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a, b) -> c (a, b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a, b) # toConstr :: (a, b) -> Constr # dataTypeOf :: (a, b) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a, b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a, b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b) -> (a, b) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a, b) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a, b) -> r # gmapQ :: (forall d. Data d => d -> u) -> (a, b) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a, b) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a, b) -> m (a, b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a, b) -> m (a, b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a, b) -> m (a, b) # | |
(Data k, Data a, Ord k) => Data (Map k a) | |
Defined in Data.Map.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) # toConstr :: Map k a -> Constr # dataTypeOf :: Map k a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a)) # gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # | |
(Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) | |
Defined in Data.HashMap.Base Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashMap k v -> c (HashMap k v) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashMap k v) # toConstr :: HashMap k v -> Constr # dataTypeOf :: HashMap k v -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HashMap k v)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashMap k v)) # gmapT :: (forall b. Data b => b -> b) -> HashMap k v -> HashMap k v # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r # gmapQ :: (forall d. Data d => d -> u) -> HashMap k v -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HashMap k v -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # | |
(Data a, Data b, Ix a) => Data (Array a b) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Array a b -> c (Array a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array a b) # toConstr :: Array a b -> Constr # dataTypeOf :: Array a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Array a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Array a b -> Array a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Array a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Array a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array a b -> m (Array a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a b -> m (Array a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a b -> m (Array a b) # | |
(Data a, Data b) => Data (Arg a b) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Arg a b -> c (Arg a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Arg a b) # toConstr :: Arg a b -> Constr # dataTypeOf :: Arg a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Arg a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Arg a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Arg a b -> Arg a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arg a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arg a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Arg a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Arg a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) # | |
Data t => Data (Proxy t) | Since: base-4.7.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) # toConstr :: Proxy t -> Constr # dataTypeOf :: Proxy t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) # gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r # gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # | |
(Typeable s, Typeable a) => Data (SmallMutableArray s a) | |
Defined in Data.Primitive.SmallArray Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SmallMutableArray s a -> c (SmallMutableArray s a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SmallMutableArray s a) # toConstr :: SmallMutableArray s a -> Constr # dataTypeOf :: SmallMutableArray s a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SmallMutableArray s a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SmallMutableArray s a)) # gmapT :: (forall b. Data b => b -> b) -> SmallMutableArray s a -> SmallMutableArray s a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SmallMutableArray s a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SmallMutableArray s a -> r # gmapQ :: (forall d. Data d => d -> u) -> SmallMutableArray s a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SmallMutableArray s a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SmallMutableArray s a -> m (SmallMutableArray s a) # | |
(Typeable s, Typeable a) => Data (MutableArray s a) | |
Defined in Data.Primitive.Array Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MutableArray s a -> c (MutableArray s a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MutableArray s a) # toConstr :: MutableArray s a -> Constr # dataTypeOf :: MutableArray s a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MutableArray s a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MutableArray s a)) # gmapT :: (forall b. Data b => b -> b) -> MutableArray s a -> MutableArray s a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MutableArray s a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MutableArray s a -> r # gmapQ :: (forall d. Data d => d -> u) -> MutableArray s a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MutableArray s a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MutableArray s a -> m (MutableArray s a) # | |
(KnownNat n, Data a) => Data (StaticSize n a) | |
Defined in Data.Store.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StaticSize n a -> c (StaticSize n a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StaticSize n a) # toConstr :: StaticSize n a -> Constr # dataTypeOf :: StaticSize n a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StaticSize n a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StaticSize n a)) # gmapT :: (forall b. Data b => b -> b) -> StaticSize n a -> StaticSize n a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r # gmapQ :: (forall d. Data d => d -> u) -> StaticSize n a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StaticSize n a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StaticSize n a -> m (StaticSize n a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StaticSize n a -> m (StaticSize n a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StaticSize n a -> m (StaticSize n a) # | |
(Data (f p), Typeable f, Data p) => Data (Rec1 f p) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rec1 f p -> c (Rec1 f p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Rec1 f p) # toConstr :: Rec1 f p -> Constr # dataTypeOf :: Rec1 f p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Rec1 f p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Rec1 f p)) # gmapT :: (forall b. Data b => b -> b) -> Rec1 f p -> Rec1 f p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r # gmapQ :: (forall d. Data d => d -> u) -> Rec1 f p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rec1 f p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) # | |
(Data a, Data b, Data c) => Data (a, b, c) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c0 (d -> b0) -> d -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c) -> c0 (a, b, c) # gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c) # toConstr :: (a, b, c) -> Constr # dataTypeOf :: (a, b, c) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (a, b, c)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (a, b, c)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b, c) -> (a, b, c) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a, b, c) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a, b, c) -> r # gmapQ :: (forall d. Data d => d -> u) -> (a, b, c) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a, b, c) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a, b, c) -> m (a, b, c) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a, b, c) -> m (a, b, c) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a, b, c) -> m (a, b, c) # | |
(Data v, Data c, Data a) => Data (CondTree v c a) | |
Defined in Distribution.Types.CondTree Methods gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> CondTree v c a -> c0 (CondTree v c a) # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (CondTree v c a) # toConstr :: CondTree v c a -> Constr # dataTypeOf :: CondTree v c a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (CondTree v c a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (CondTree v c a)) # gmapT :: (forall b. Data b => b -> b) -> CondTree v c a -> CondTree v c a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r # gmapQ :: (forall d. Data d => d -> u) -> CondTree v c a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CondTree v c a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CondTree v c a -> m (CondTree v c a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CondTree v c a -> m (CondTree v c a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CondTree v c a -> m (CondTree v c a) # | |
(Data v, Data c, Data a) => Data (CondBranch v c a) | |
Defined in Distribution.Types.CondTree Methods gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> CondBranch v c a -> c0 (CondBranch v c a) # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (CondBranch v c a) # toConstr :: CondBranch v c a -> Constr # dataTypeOf :: CondBranch v c a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (CondBranch v c a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (CondBranch v c a)) # gmapT :: (forall b. Data b => b -> b) -> CondBranch v c a -> CondBranch v c a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r # gmapQ :: (forall d. Data d => d -> u) -> CondBranch v c a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CondBranch v c a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CondBranch v c a -> m (CondBranch v c a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CondBranch v c a -> m (CondBranch v c a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CondBranch v c a -> m (CondBranch v c a) # | |
(Typeable k, Data a, Typeable b) => Data (Const a b) | Since: base-4.10.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Const a b -> c (Const a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const a b) # toConstr :: Const a b -> Constr # dataTypeOf :: Const a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Const a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Const a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Const a b -> Const a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Const a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Const a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) # | |
(Data (f a), Data a, Typeable f) => Data (Ap f a) | Since: base-4.12.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ap f a -> c (Ap f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ap f a) # toConstr :: Ap f a -> Constr # dataTypeOf :: Ap f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ap f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ap f a)) # gmapT :: (forall b. Data b => b -> b) -> Ap f a -> Ap f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Ap f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ap f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) # | |
(Data (f a), Data a, Typeable f) => Data (Alt f a) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt f a -> c (Alt f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Alt f a) # toConstr :: Alt f a -> Constr # dataTypeOf :: Alt f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Alt f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Alt f a)) # gmapT :: (forall b. Data b => b -> b) -> Alt f a -> Alt f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Alt f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) # | |
(Coercible a b, Data a, Data b) => Data (Coercion a b) | Since: base-4.7.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Coercion a b -> c (Coercion a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Coercion a b) # toConstr :: Coercion a b -> Constr # dataTypeOf :: Coercion a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Coercion a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Coercion a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Coercion a b -> Coercion a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coercion a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coercion a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Coercion a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Coercion a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) # | |
(a ~ b, Data a) => Data (a :~: b) | Since: base-4.7.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~: b) -> c (a :~: b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~: b) # toConstr :: (a :~: b) -> Constr # dataTypeOf :: (a :~: b) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~: b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~: b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r # gmapQ :: (forall d. Data d => d -> u) -> (a :~: b) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~: b) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) # | |
(Data s, Data b) => Data (Tagged s b) | |
Defined in Data.Tagged Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Tagged s b -> c (Tagged s b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tagged s b) # toConstr :: Tagged s b -> Constr # dataTypeOf :: Tagged s b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tagged s b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tagged s b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Tagged s b -> Tagged s b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tagged s b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tagged s b -> r # gmapQ :: (forall d. Data d => d -> u) -> Tagged s b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tagged s b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tagged s b -> m (Tagged s b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagged s b -> m (Tagged s b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagged s b -> m (Tagged s b) # | |
(Typeable i, Data p, Data c) => Data (K1 i c p) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> K1 i c p -> c0 (K1 i c p) # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (K1 i c p) # toConstr :: K1 i c p -> Constr # dataTypeOf :: K1 i c p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (K1 i c p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (K1 i c p)) # gmapT :: (forall b. Data b => b -> b) -> K1 i c p -> K1 i c p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r # gmapQ :: (forall d. Data d => d -> u) -> K1 i c p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> K1 i c p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) # | |
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :+: g) p) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :+: g) p -> c ((f :+: g) p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :+: g) p) # toConstr :: (f :+: g) p -> Constr # dataTypeOf :: (f :+: g) p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :+: g) p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :+: g) p)) # gmapT :: (forall b. Data b => b -> b) -> (f :+: g) p -> (f :+: g) p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r # gmapQ :: (forall d. Data d => d -> u) -> (f :+: g) p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :+: g) p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) # | |
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :*: g) p) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :*: g) p -> c ((f :*: g) p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :*: g) p) # toConstr :: (f :*: g) p -> Constr # dataTypeOf :: (f :*: g) p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :*: g) p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :*: g) p)) # gmapT :: (forall b. Data b => b -> b) -> (f :*: g) p -> (f :*: g) p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r # gmapQ :: (forall d. Data d => d -> u) -> (f :*: g) p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :*: g) p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) # | |
(Data a, Data b, Data c, Data d) => Data (a, b, c, d) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d0 b0. Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c, d) -> c0 (a, b, c, d) # gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d) # toConstr :: (a, b, c, d) -> Constr # dataTypeOf :: (a, b, c, d) -> DataType # dataCast1 :: Typeable t => (forall d0. Data d0 => c0 (t d0)) -> Maybe (c0 (a, b, c, d)) # dataCast2 :: Typeable t => (forall d0 e. (Data d0, Data e) => c0 (t d0 e)) -> Maybe (c0 (a, b, c, d)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b, c, d) -> (a, b, c, d) # gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d) -> r # gmapQ :: (forall d0. Data d0 => d0 -> u) -> (a, b, c, d) -> [u] # gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> (a, b, c, d) -> u # gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d) -> m (a, b, c, d) # gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d) -> m (a, b, c, d) # gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d) -> m (a, b, c, d) # | |
(Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Data (Product f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> Product f g a -> c (Product f g a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product f g a) # toConstr :: Product f g a -> Constr # dataTypeOf :: Product f g a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product f g a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product f g a)) # gmapT :: (forall b. Data b => b -> b) -> Product f g a -> Product f g a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product f g a -> r # gmapQ :: (forall d. Data d => d -> u) -> Product f g a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Product f g a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Product f g a -> m (Product f g a) # | |
(Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Data (Sum f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> Sum f g a -> c (Sum f g a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum f g a) # toConstr :: Sum f g a -> Constr # dataTypeOf :: Sum f g a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum f g a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum f g a)) # gmapT :: (forall b. Data b => b -> b) -> Sum f g a -> Sum f g a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum f g a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum f g a -> r # gmapQ :: (forall d. Data d => d -> u) -> Sum f g a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum f g a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) # | |
(Typeable i, Typeable j, Typeable a, Typeable b, a ~~ b) => Data (a :~~: b) | Since: base-4.10.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~~: b) -> c (a :~~: b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~~: b) # toConstr :: (a :~~: b) -> Constr # dataTypeOf :: (a :~~: b) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~~: b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~~: b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~~: b) -> a :~~: b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~~: b) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~~: b) -> r # gmapQ :: (forall d. Data d => d -> u) -> (a :~~: b) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~~: b) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~~: b) -> m (a :~~: b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~~: b) -> m (a :~~: b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~~: b) -> m (a :~~: b) # | |
(Data p, Data (f p), Typeable c, Typeable i, Typeable f) => Data (M1 i c f p) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> M1 i c f p -> c0 (M1 i c f p) # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (M1 i c f p) # toConstr :: M1 i c f p -> Constr # dataTypeOf :: M1 i c f p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (M1 i c f p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (M1 i c f p)) # gmapT :: (forall b. Data b => b -> b) -> M1 i c f p -> M1 i c f p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r # gmapQ :: (forall d. Data d => d -> u) -> M1 i c f p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> M1 i c f p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) # | |
(Typeable f, Typeable g, Data p, Data (f (g p))) => Data ((f :.: g) p) | Since: base-4.9.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :.: g) p -> c ((f :.: g) p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :.: g) p) # toConstr :: (f :.: g) p -> Constr # dataTypeOf :: (f :.: g) p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :.: g) p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :.: g) p)) # gmapT :: (forall b. Data b => b -> b) -> (f :.: g) p -> (f :.: g) p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r # gmapQ :: (forall d. Data d => d -> u) -> (f :.: g) p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :.: g) p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) # | |
(Data a, Data b, Data c, Data d, Data e) => Data (a, b, c, d, e) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d0 b0. Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c, d, e) -> c0 (a, b, c, d, e) # gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d, e) # toConstr :: (a, b, c, d, e) -> Constr # dataTypeOf :: (a, b, c, d, e) -> DataType # dataCast1 :: Typeable t => (forall d0. Data d0 => c0 (t d0)) -> Maybe (c0 (a, b, c, d, e)) # dataCast2 :: Typeable t => (forall d0 e0. (Data d0, Data e0) => c0 (t d0 e0)) -> Maybe (c0 (a, b, c, d, e)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b, c, d, e) -> (a, b, c, d, e) # gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e) -> r # gmapQ :: (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e) -> [u] # gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e) -> u # gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e) -> m (a, b, c, d, e) # gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e) -> m (a, b, c, d, e) # gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e) -> m (a, b, c, d, e) # | |
(Typeable a, Typeable f, Typeable g, Typeable k1, Typeable k2, Data (f (g a))) => Data (Compose f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> Compose f g a -> c (Compose f g a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Compose f g a) # toConstr :: Compose f g a -> Constr # dataTypeOf :: Compose f g a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Compose f g a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Compose f g a)) # gmapT :: (forall b. Data b => b -> b) -> Compose f g a -> Compose f g a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r # gmapQ :: (forall d. Data d => d -> u) -> Compose f g a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Compose f g a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) # | |
(Data a, Data b, Data c, Data d, Data e, Data f) => Data (a, b, c, d, e, f) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d0 b0. Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c, d, e, f) -> c0 (a, b, c, d, e, f) # gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d, e, f) # toConstr :: (a, b, c, d, e, f) -> Constr # dataTypeOf :: (a, b, c, d, e, f) -> DataType # dataCast1 :: Typeable t => (forall d0. Data d0 => c0 (t d0)) -> Maybe (c0 (a, b, c, d, e, f)) # dataCast2 :: Typeable t => (forall d0 e0. (Data d0, Data e0) => c0 (t d0 e0)) -> Maybe (c0 (a, b, c, d, e, f)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) # gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e, f) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e, f) -> r # gmapQ :: (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e, f) -> [u] # gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e, f) -> u # gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f) -> m (a, b, c, d, e, f) # gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f) -> m (a, b, c, d, e, f) # gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f) -> m (a, b, c, d, e, f) # | |
(Data a, Data b, Data c, Data d, Data e, Data f, Data g) => Data (a, b, c, d, e, f, g) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d0 b0. Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g0. g0 -> c0 g0) -> (a, b, c, d, e, f, g) -> c0 (a, b, c, d, e, f, g) # gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d, e, f, g) # toConstr :: (a, b, c, d, e, f, g) -> Constr # dataTypeOf :: (a, b, c, d, e, f, g) -> DataType # dataCast1 :: Typeable t => (forall d0. Data d0 => c0 (t d0)) -> Maybe (c0 (a, b, c, d, e, f, g)) # dataCast2 :: Typeable t => (forall d0 e0. (Data d0, Data e0) => c0 (t d0 e0)) -> Maybe (c0 (a, b, c, d, e, f, g)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) # gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e, f, g) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e, f, g) -> r # gmapQ :: (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e, f, g) -> [u] # gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e, f, g) -> u # gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g) # gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g) # gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g) # |
class Functor (f :: Type -> Type) 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
Basic numeric class.
The Haskell Report defines no laws for Num
. However, '(+)' and '(*)' are
customarily expected to define a ring and have the following properties:
- Associativity of (+)
(x + y) + z
=x + (y + z)
- Commutativity of (+)
x + y
=y + x
fromInteger 0
is the additive identityx + fromInteger 0
=x
negate
gives the additive inversex + negate x
=fromInteger 0
- Associativity of (*)
(x * y) * z
=x * (y * z)
fromInteger 1
is the multiplicative identityx * fromInteger 1
=x
andfromInteger 1 * x
=x
- Distributivity of (*) with respect to (+)
a * (b + c)
=(a * b) + (a * c)
and(b + c) * a
=(b * a) + (c * a)
Note that it isn't customarily expected that a type instance of both Num
and Ord
implement an ordered ring. Indeed, in base
only Integer
and
Rational
do.
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
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.
The Haskell Report defines no laws for Ord
. However, <=
is customarily
expected to implement a non-strict partial order and have the following
properties:
- Transitivity
- if
x <= y && y <= z
=True
, thenx <= z
=True
- Reflexivity
x <= x
=True
- Antisymmetry
- if
x <= y && y <= x
=True
, thenx == y
=True
Note that the following operator interactions are expected to hold:
x >= y
=y <= x
x < y
=x <= y && x /= y
x > y
=y < x
x < y
=compare x y == LT
x > y
=compare x y == GT
x == y
=compare x y == EQ
min x y == if x <= y then x else y
=True
max x y == if x >= y then x else y
=True
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
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
Instances
class (Num a, Ord a) => Real a where #
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 Scientific | WARNING: the methods of the |
Defined in Data.Scientific Methods properFraction :: Integral b => Scientific -> (b, Scientific) # truncate :: Integral b => Scientific -> b # round :: Integral b => Scientific -> b # ceiling :: Integral b => Scientific -> b # floor :: Integral b => Scientific -> b # | |
RealFrac Number | |
RealFrac CFloat | |
RealFrac CDouble | |
RealFrac DiffTime | |
RealFrac NominalDiffTime | |
Defined in Data.Time.Clock.Internal.NominalDiffTime Methods properFraction :: Integral b => NominalDiffTime -> (b, NominalDiffTime) # truncate :: Integral b => NominalDiffTime -> b # round :: Integral b => NominalDiffTime -> b # ceiling :: Integral b => NominalDiffTime -> b # floor :: Integral b => NominalDiffTime -> b # | |
Integral a => RealFrac (Ratio a) | Since: base-2.0.1 |
HasResolution a => RealFrac (Fixed a) | Since: base-2.1 |
RealFrac a => RealFrac (Identity a) | Since: base-4.9.0.0 |
RealFrac a => RealFrac (Const a b) | Since: base-4.9.0.0 |
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
Instances
The class Typeable
allows a concrete representation of a type to
be calculated.
Minimal complete definition
typeRep#
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
Methods
fromString :: String -> a #
Instances
class Functor f => Applicative (f :: Type -> Type) 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.
liftA2 :: (a -> b -> c) -> f a -> f b -> f c #
Lift a binary function to actions.
Some functors support an implementation of liftA2
that is more
efficient than the default one. In particular, if fmap
is an
expensive operation, it is likely better to use liftA2
than to
fmap
over the structure and then use <*>
.
(*>) :: 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: base-2.1 |
Applicative Maybe | Since: base-2.1 |
Applicative IO | Since: base-2.1 |
Applicative Par1 | Since: base-4.9.0.0 |
Applicative Q | |
Applicative Last | Since: base-4.9.0.0 |
Applicative ParseResult | |
Defined in Distribution.Parsec.ParseResult Methods pure :: a -> ParseResult a # (<*>) :: ParseResult (a -> b) -> ParseResult a -> ParseResult b # liftA2 :: (a -> b -> c) -> ParseResult a -> ParseResult b -> ParseResult c # (*>) :: ParseResult a -> ParseResult b -> ParseResult b # (<*) :: ParseResult a -> ParseResult b -> ParseResult a # | |
Applicative ParseResult | |
Defined in Distribution.ParseUtils Methods pure :: a -> ParseResult a # (<*>) :: ParseResult (a -> b) -> ParseResult a -> ParseResult b # liftA2 :: (a -> b -> c) -> ParseResult a -> ParseResult b -> ParseResult c # (*>) :: ParseResult a -> ParseResult b -> ParseResult b # (<*) :: ParseResult a -> ParseResult b -> ParseResult a # | |
Applicative Condition | |
Defined in Distribution.Types.Condition | |
Applicative Flag | |
Applicative Last' | |
Applicative IResult | |
Applicative Result | |
Applicative Parser | |
Applicative Concurrently | |
Defined in Control.Concurrent.Async Methods pure :: a -> Concurrently a # (<*>) :: Concurrently (a -> b) -> Concurrently a -> Concurrently b # liftA2 :: (a -> b -> c) -> Concurrently a -> Concurrently b -> Concurrently c # (*>) :: Concurrently a -> Concurrently b -> Concurrently b # (<*) :: Concurrently a -> Concurrently b -> Concurrently a # | |
Applicative Complex | Since: base-4.9.0.0 |
Applicative Min | Since: base-4.9.0.0 |
Applicative Max | Since: base-4.9.0.0 |
Applicative First | Since: base-4.9.0.0 |
Applicative Option | Since: base-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: base-2.1 |
Applicative Identity | Since: base-4.8.0.0 |
Applicative STM | Since: base-4.8.0.0 |
Applicative First | Since: base-4.8.0.0 |
Applicative Last | Since: base-4.8.0.0 |
Applicative Dual | Since: base-4.8.0.0 |
Applicative Sum | Since: base-4.8.0.0 |
Applicative Product | Since: base-4.8.0.0 |
Applicative Down | Since: base-4.11.0.0 |
Applicative ReadPrec | Since: base-4.6.0.0 |
Applicative ReadP | Since: base-4.6.0.0 |
Applicative NonEmpty | Since: base-4.9.0.0 |
Applicative Put | |
Applicative Tree | |
Applicative Seq | Since: containers-0.5.4 |
Applicative CryptoFailable | |
Defined in Crypto.Error.Types Methods pure :: a -> CryptoFailable a # (<*>) :: CryptoFailable (a -> b) -> CryptoFailable a -> CryptoFailable b # liftA2 :: (a -> b -> c) -> CryptoFailable a -> CryptoFailable b -> CryptoFailable c # (*>) :: CryptoFailable a -> CryptoFailable b -> CryptoFailable b # (<*) :: CryptoFailable a -> CryptoFailable b -> CryptoFailable a # | |
Applicative DList | |
Applicative SubM | |
Applicative ReadM | |
Applicative Parser | |
Applicative ParserM | |
Applicative ParserResult | |
Defined in Options.Applicative.Types Methods pure :: a -> ParserResult a # (<*>) :: ParserResult (a -> b) -> ParserResult a -> ParserResult b # liftA2 :: (a -> b -> c) -> ParserResult a -> ParserResult b -> ParserResult c # (*>) :: ParserResult a -> ParserResult b -> ParserResult b # (<*) :: ParserResult a -> ParserResult b -> ParserResult a # | |
Applicative Chunk | |
Applicative SmallArray | |
Defined in Data.Primitive.SmallArray Methods pure :: a -> SmallArray a # (<*>) :: SmallArray (a -> b) -> SmallArray a -> SmallArray b # liftA2 :: (a -> b -> c) -> SmallArray a -> SmallArray b -> SmallArray c # (*>) :: SmallArray a -> SmallArray b -> SmallArray b # (<*) :: SmallArray a -> SmallArray b -> SmallArray a # | |
Applicative Array | |
Applicative Memoized | |
Applicative Vector | |
Applicative Sh | |
Applicative Peek | |
Applicative Poke | |
Applicative Cleanup | |
Applicative Id | |
Applicative Box | |
Applicative Stream | |
Applicative P | Since: base-4.5.0.0 |
Applicative (Either e) | Since: base-3.0 |
Applicative (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Monoid a => Applicative ((,) a) | For tuples, the ("hello ", (+15)) <*> ("world!", 2002) ("hello world!",2017) Since: base-2.1 |
Applicative (ST s) | Since: base-4.4.0.0 |
Applicative (Parser i) | |
Monad m => Applicative (WrappedMonad m) | Since: base-2.1 |
Defined in Control.Applicative 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: base-4.6.0.0 |
Defined in Control.Arrow 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 :: Type -> Type) | Since: base-4.7.0.0 |
(Functor m, Monad m) => Applicative (MaybeT m) | |
Monad m => Applicative (ZipSource m) | |
Defined in Data.Conduit.Internal.Conduit | |
Applicative m => Applicative (ResourceT m) | |
Defined in Control.Monad.Trans.Resource.Internal | |
Applicative m => Applicative (ListT m) | |
Applicative m => Applicative (NoLoggingT m) | |
Defined in Control.Monad.Logger Methods pure :: a -> NoLoggingT m a # (<*>) :: NoLoggingT m (a -> b) -> NoLoggingT m a -> NoLoggingT m b # liftA2 :: (a -> b -> c) -> NoLoggingT m a -> NoLoggingT m b -> NoLoggingT m c # (*>) :: NoLoggingT m a -> NoLoggingT m b -> NoLoggingT m b # (<*) :: NoLoggingT m a -> NoLoggingT m b -> NoLoggingT m a # | |
Applicative m => Applicative (WriterLoggingT m) | |
Defined in Control.Monad.Logger Methods pure :: a -> WriterLoggingT m a # (<*>) :: WriterLoggingT m (a -> b) -> WriterLoggingT m a -> WriterLoggingT m b # liftA2 :: (a -> b -> c) -> WriterLoggingT m a -> WriterLoggingT m b -> WriterLoggingT m c # (*>) :: WriterLoggingT m a -> WriterLoggingT m b -> WriterLoggingT m b # (<*) :: WriterLoggingT m a -> WriterLoggingT m b -> WriterLoggingT m a # | |
Applicative m => Applicative (LoggingT m) | |
Defined in Control.Monad.Logger | |
MonadUnliftIO m => Applicative (Concurrently m) | Since: unliftio-0.1.0.0 |
Defined in UnliftIO.Async Methods pure :: a -> Concurrently m a # (<*>) :: Concurrently m (a -> b) -> Concurrently m a -> Concurrently m b # liftA2 :: (a -> b -> c) -> Concurrently m a -> Concurrently m b -> Concurrently m c # (*>) :: Concurrently m a -> Concurrently m b -> Concurrently m b # (<*) :: Concurrently m a -> Concurrently m b -> Concurrently m a # | |
Applicative (RIO env) | |
Applicative (IParser t) | |
Applicative (Partial e) | |
Applicative (SetM s) | |
Applicative f => Applicative (Rec1 f) | Since: base-4.9.0.0 |
Arrow a => Applicative (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative 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 :: Type -> Type) | Since: base-2.0.1 |
Applicative f => Applicative (Ap f) | Since: base-4.12.0.0 |
Applicative f => Applicative (Alt f) | Since: base-4.8.0.0 |
Applicative m => Applicative (IdentityT m) | |
Defined in Control.Monad.Trans.Identity | |
(Monoid w, Applicative m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Strict | |
(Monoid w, Applicative m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Lazy | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Lazy | |
(Functor m, Monad m) => Applicative (ExceptT e m) | |
Defined in Control.Monad.Trans.Except | |
Monad m => Applicative (ZipSink i m) | |
Defined in Data.Conduit.Internal.Conduit | |
(Applicative f, Monad f) => Applicative (WhenMissing f x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal 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) | |
Defined in Control.Monad.Trans.Error | |
Applicative (Tagged s) | |
(Monoid w, Functor m, Monad m) => Applicative (AccumT w m) | |
Defined in Control.Monad.Trans.Accum | |
(Functor m, Monad m) => Applicative (SelectT r m) | |
Defined in Control.Monad.Trans.Select | |
Applicative (Bazaar a b) | |
Defined in Lens.Micro | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Applicative ((->) a :: Type -> Type) | Since: base-2.1 |
Monoid c => Applicative (K1 i c :: Type -> Type) | Since: base-4.12.0.0 |
(Applicative f, Applicative g) => Applicative (f :*: g) | Since: base-4.9.0.0 |
(Applicative f, Applicative g) => Applicative (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
Applicative m => Applicative (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
Applicative (ConduitT i o m) | |
Defined in Data.Conduit.Internal.Conduit Methods pure :: a -> ConduitT i o m a # (<*>) :: ConduitT i o m (a -> b) -> ConduitT i o m a -> ConduitT i o m b # liftA2 :: (a -> b -> c) -> ConduitT i o m a -> ConduitT i o m b -> ConduitT i o m c # (*>) :: ConduitT i o m a -> ConduitT i o m b -> ConduitT i o m b # (<*) :: ConduitT i o m a -> ConduitT i o m b -> ConduitT i o m a # | |
Monad m => Applicative (ZipConduit i o m) | |
Defined in Data.Conduit.Internal.Conduit Methods pure :: a -> ZipConduit i o m a # (<*>) :: ZipConduit i o m (a -> b) -> ZipConduit i o m a -> ZipConduit i o m b # liftA2 :: (a -> b -> c) -> ZipConduit i o m a -> ZipConduit i o m b -> ZipConduit i o m c # (*>) :: ZipConduit i o m a -> ZipConduit i o m b -> ZipConduit i o m b # (<*) :: ZipConduit i o m a -> ZipConduit i o m b -> ZipConduit i o m a # | |
(Monad f, Applicative f) => Applicative (WhenMatched f x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal 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: containers-0.5.9 |
Defined in Data.Map.Internal 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 (ContT r m) | |
Defined in Control.Monad.Trans.Cont | |
Applicative f => Applicative (M1 i c f) | Since: base-4.9.0.0 |
(Applicative f, Applicative g) => Applicative (f :.: g) | Since: base-4.9.0.0 |
(Applicative f, Applicative g) => Applicative (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Strict | |
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Lazy | |
(Monad f, Applicative f) => Applicative (WhenMatched f k x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal 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 # | |
Monad state => Applicative (Builder collection mutCollection step state err) | |
Defined in Basement.MutableBuilder Methods pure :: a -> Builder collection mutCollection step state err a # (<*>) :: Builder collection mutCollection step state err (a -> b) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b # liftA2 :: (a -> b -> c) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err c # (*>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b # (<*) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err a # | |
Monad m => Applicative (Pipe l i o u m) | |
Defined in Data.Conduit.Internal.Pipe Methods pure :: a -> Pipe l i o u m a # (<*>) :: Pipe l i o u m (a -> b) -> Pipe l i o u m a -> Pipe l i o u m b # liftA2 :: (a -> b -> c) -> Pipe l i o u m a -> Pipe l i o u m b -> Pipe l i o u m c # (*>) :: Pipe l i o u m a -> Pipe l i o u m b -> Pipe l i o u m b # (<*) :: Pipe l i o u m a -> Pipe l i o u m b -> Pipe l i o u m a # |
class Foldable (t :: Type -> Type) 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
fold :: Monoid m => t m -> m #
Combine the elements of a structure using a monoid.
foldMap :: Monoid m => (a -> m) -> t a -> m #
Map each element of the structure to a monoid, and combine the results.
foldr :: (a -> b -> b) -> b -> t a -> b #
Right-associative fold of a structure.
In the case of lists, foldr
, when applied to a binary operator, a
starting value (typically the right-identity of the operator), and a
list, reduces the list using the binary operator, from right to left:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
Note that, since the head of the resulting expression is produced by
an application of the operator to the first element of the list,
foldr
can produce a terminating expression from an infinite list.
For a general Foldable
structure this should be semantically identical
to,
foldr f z =foldr
f z .toList
foldl' :: (b -> a -> b) -> b -> t a -> b #
Left-associative fold of a structure but with strict application of the operator.
This ensures that each step of the fold is forced to weak head normal
form before being applied, avoiding the collection of thunks that would
otherwise occur. This is often what you want to strictly reduce a finite
list to a single, monolithic result (e.g. length
).
For a general Foldable
structure this should be semantically identical
to,
foldl f z =foldl'
f z .toList
List of elements of a structure, from left to right.
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.
Returns the size/length of a finite structure as an Int
. 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?
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: base-2.1 |
Defined in Data.Foldable 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: base-2.1 |
Defined in Data.Foldable 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 | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 Last | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 VersionRangeF | |
Defined in Distribution.Types.VersionRange Methods fold :: Monoid m => VersionRangeF m -> m # foldMap :: Monoid m => (a -> m) -> VersionRangeF a -> m # foldr :: (a -> b -> b) -> b -> VersionRangeF a -> b # foldr' :: (a -> b -> b) -> b -> VersionRangeF a -> b # foldl :: (b -> a -> b) -> b -> VersionRangeF a -> b # foldl' :: (b -> a -> b) -> b -> VersionRangeF a -> b # foldr1 :: (a -> a -> a) -> VersionRangeF a -> a # foldl1 :: (a -> a -> a) -> VersionRangeF a -> a # toList :: VersionRangeF a -> [a] # null :: VersionRangeF a -> Bool # length :: VersionRangeF a -> Int # elem :: Eq a => a -> VersionRangeF a -> Bool # maximum :: Ord a => VersionRangeF a -> a # minimum :: Ord a => VersionRangeF a -> a # sum :: Num a => VersionRangeF a -> a # product :: Num a => VersionRangeF a -> a # | |
Foldable Condition | |
Defined in Distribution.Types.Condition Methods fold :: Monoid m => Condition m -> m # foldMap :: Monoid m => (a -> m) -> Condition a -> m # foldr :: (a -> b -> b) -> b -> Condition a -> b # foldr' :: (a -> b -> b) -> b -> Condition a -> b # foldl :: (b -> a -> b) -> b -> Condition a -> b # foldl' :: (b -> a -> b) -> b -> Condition a -> b # foldr1 :: (a -> a -> a) -> Condition a -> a # foldl1 :: (a -> a -> a) -> Condition a -> a # toList :: Condition a -> [a] # length :: Condition a -> Int # elem :: Eq a => a -> Condition a -> Bool # maximum :: Ord a => Condition a -> a # minimum :: Ord a => Condition a -> a # | |
Foldable Graph | |
Defined in Distribution.Compat.Graph Methods fold :: Monoid m => Graph m -> m # foldMap :: Monoid m => (a -> m) -> Graph a -> m # foldr :: (a -> b -> b) -> b -> Graph a -> b # foldr' :: (a -> b -> b) -> b -> Graph a -> b # foldl :: (b -> a -> b) -> b -> Graph a -> b # foldl' :: (b -> a -> b) -> b -> Graph a -> b # foldr1 :: (a -> a -> a) -> Graph a -> a # foldl1 :: (a -> a -> a) -> Graph a -> a # elem :: Eq a => a -> Graph a -> Bool # maximum :: Ord a => Graph a -> a # minimum :: Ord a => Graph a -> a # | |
Foldable SCC | Since: containers-0.5.9 |
Defined in Data.Graph Methods fold :: Monoid m => SCC m -> m # foldMap :: Monoid m => (a -> m) -> SCC a -> m # foldr :: (a -> b -> b) -> b -> SCC a -> b # foldr' :: (a -> b -> b) -> b -> SCC a -> b # foldl :: (b -> a -> b) -> b -> SCC a -> b # foldl' :: (b -> a -> b) -> b -> SCC a -> b # foldr1 :: (a -> a -> a) -> SCC a -> a # foldl1 :: (a -> a -> a) -> SCC a -> a # elem :: Eq a => a -> SCC a -> Bool # maximum :: Ord a => SCC a -> a # | |
Foldable IResult | |
Defined in Data.Aeson.Types.Internal Methods fold :: Monoid m => IResult m -> m # foldMap :: Monoid m => (a -> m) -> IResult a -> m # foldr :: (a -> b -> b) -> b -> IResult a -> b # foldr' :: (a -> b -> b) -> b -> IResult a -> b # foldl :: (b -> a -> b) -> b -> IResult a -> b # foldl' :: (b -> a -> b) -> b -> IResult a -> b # foldr1 :: (a -> a -> a) -> IResult a -> a # foldl1 :: (a -> a -> a) -> IResult a -> a # elem :: Eq a => a -> IResult a -> Bool # maximum :: Ord a => IResult a -> a # minimum :: Ord a => IResult a -> a # | |
Foldable Result | |
Defined in Data.Aeson.Types.Internal Methods fold :: Monoid m => Result m -> m # foldMap :: Monoid m => (a -> m) -> Result a -> m # foldr :: (a -> b -> b) -> b -> Result a -> b # foldr' :: (a -> b -> b) -> b -> Result a -> b # foldl :: (b -> a -> b) -> b -> Result a -> b # foldl' :: (b -> a -> b) -> b -> Result a -> b # foldr1 :: (a -> a -> a) -> Result a -> a # foldl1 :: (a -> a -> a) -> Result a -> a # elem :: Eq a => a -> Result a -> Bool # maximum :: Ord a => Result a -> a # minimum :: Ord a => Result a -> a # | |
Foldable Complex | Since: base-4.9.0.0 |
Defined in Data.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: base-4.9.0.0 |
Defined in Data.Semigroup 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: base-4.9.0.0 |
Defined in Data.Semigroup 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: base-4.9.0.0 |
Defined in Data.Semigroup 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 Option | Since: base-4.9.0.0 |
Defined in Data.Semigroup 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 | Since: base-4.9.0.0 |
Defined in Control.Applicative 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: base-4.8.0.0 |
Defined in Data.Functor.Identity 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: base-4.8.0.0 |
Defined in Data.Foldable 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: base-4.8.0.0 |
Defined in Data.Foldable 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: base-4.8.0.0 |
Defined in Data.Foldable 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: base-4.8.0.0 |
Defined in Data.Foldable 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: base-4.8.0.0 |
Defined in Data.Foldable 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 Down | Since: base-4.12.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Down m -> m # foldMap :: Monoid m => (a -> m) -> Down a -> m # foldr :: (a -> b -> b) -> b -> Down a -> b # foldr' :: (a -> b -> b) -> b -> Down a -> b # foldl :: (b -> a -> b) -> b -> Down a -> b # foldl' :: (b -> a -> b) -> b -> Down a -> b # foldr1 :: (a -> a -> a) -> Down a -> a # foldl1 :: (a -> a -> a) -> Down a -> a # elem :: Eq a => a -> Down a -> Bool # maximum :: Ord a => Down a -> a # | |
Foldable NonEmpty | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 | |
Defined in Data.IntMap.Internal 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 | |
Defined in Data.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 | |
Defined in Data.Sequence.Internal 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 | |
Defined in Data.Sequence.Internal 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 | |
Defined in Data.Sequence.Internal 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 | |
Defined in Data.Sequence.Internal 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 | |
Defined in Data.Sequence.Internal 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 | |
Defined in Data.Sequence.Internal 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 | |
Defined in Data.Sequence.Internal 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 | |
Defined in Data.Set.Internal 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 | |
Defined in Data.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 Hashed | |
Defined in Data.Hashable.Class Methods fold :: Monoid m => Hashed m -> m # foldMap :: Monoid m => (a -> m) -> Hashed a -> m # foldr :: (a -> b -> b) -> b -> Hashed a -> b # foldr' :: (a -> b -> b) -> b -> Hashed a -> b # foldl :: (b -> a -> b) -> b -> Hashed a -> b # foldl' :: (b -> a -> b) -> b -> Hashed a -> b # foldr1 :: (a -> a -> a) -> Hashed a -> a # foldl1 :: (a -> a -> a) -> Hashed a -> a # elem :: Eq a => a -> Hashed a -> Bool # maximum :: Ord a => Hashed a -> a # minimum :: Ord a => Hashed a -> a # | |
Foldable List | |
Defined in Data.Aeson.Config.Types Methods fold :: Monoid m => List m -> m # foldMap :: Monoid m => (a -> m) -> List a -> m # foldr :: (a -> b -> b) -> b -> List a -> b # foldr' :: (a -> b -> b) -> b -> List a -> b # foldl :: (b -> a -> b) -> b -> List a -> b # foldl' :: (b -> a -> b) -> b -> List a -> b # foldr1 :: (a -> a -> a) -> List a -> a # foldl1 :: (a -> a -> a) -> List a -> a # elem :: Eq a => a -> List a -> Bool # maximum :: Ord a => List a -> a # | |
Foldable Section | |
Defined in Hpack.Config Methods fold :: Monoid m => Section m -> m # foldMap :: Monoid m => (a -> m) -> Section a -> m # foldr :: (a -> b -> b) -> b -> Section a -> b # foldr' :: (a -> b -> b) -> b -> Section a -> b # foldl :: (b -> a -> b) -> b -> Section a -> b # foldl' :: (b -> a -> b) -> b -> Section a -> b # foldr1 :: (a -> a -> a) -> Section a -> a # foldl1 :: (a -> a -> a) -> Section a -> a # elem :: Eq a => a -> Section a -> Bool # maximum :: Ord a => Section a -> a # minimum :: Ord a => Section a -> a # | |
Foldable Conditional | |
Defined in Hpack.Config Methods fold :: Monoid m => Conditional m -> m # foldMap :: Monoid m => (a -> m) -> Conditional a -> m # foldr :: (a -> b -> b) -> b -> Conditional a -> b # foldr' :: (a -> b -> b) -> b -> Conditional a -> b # foldl :: (b -> a -> b) -> b -> Conditional a -> b # foldl' :: (b -> a -> b) -> b -> Conditional a -> b # foldr1 :: (a -> a -> a) -> Conditional a -> a # foldl1 :: (a -> a -> a) -> Conditional a -> a # toList :: Conditional a -> [a] # null :: Conditional a -> Bool # length :: Conditional a -> Int # elem :: Eq a => a -> Conditional a -> Bool # maximum :: Ord a => Conditional a -> a # minimum :: Ord a => Conditional a -> a # sum :: Num a => Conditional a -> a # product :: Num a => Conditional a -> a # | |
Foldable LenientData | |
Defined in Web.Internal.HttpApiData Methods fold :: Monoid m => LenientData m -> m # foldMap :: Monoid m => (a -> m) -> LenientData a -> m # foldr :: (a -> b -> b) -> b -> LenientData a -> b # foldr' :: (a -> b -> b) -> b -> LenientData a -> b # foldl :: (b -> a -> b) -> b -> LenientData a -> b # foldl' :: (b -> a -> b) -> b -> LenientData a -> b # foldr1 :: (a -> a -> a) -> LenientData a -> a # foldl1 :: (a -> a -> a) -> LenientData a -> a # toList :: LenientData a -> [a] # null :: LenientData a -> Bool # length :: LenientData a -> Int # elem :: Eq a => a -> LenientData a -> Bool # maximum :: Ord a => LenientData a -> a # minimum :: Ord a => LenientData a -> a # sum :: Num a => LenientData a -> a # product :: Num a => LenientData a -> a # | |
Foldable PoolList | |
Defined in Data.KeyedPool Methods fold :: Monoid m => PoolList m -> m # foldMap :: Monoid m => (a -> m) -> PoolList a -> m # foldr :: (a -> b -> b) -> b -> PoolList a -> b # foldr' :: (a -> b -> b) -> b -> PoolList a -> b # foldl :: (b -> a -> b) -> b -> PoolList a -> b # foldl' :: (b -> a -> b) -> b -> PoolList a -> b # foldr1 :: (a -> a -> a) -> PoolList a -> a # foldl1 :: (a -> a -> a) -> PoolList a -> a # elem :: Eq a => a -> PoolList a -> Bool # maximum :: Ord a => PoolList a -> a # minimum :: Ord a => PoolList a -> a # | |
Foldable HistoriedResponse | |
Defined in Network.HTTP.Client Methods fold :: Monoid m => HistoriedResponse m -> m # foldMap :: Monoid m => (a -> m) -> HistoriedResponse a -> m # foldr :: (a -> b -> b) -> b -> HistoriedResponse a -> b # foldr' :: (a -> b -> b) -> b -> HistoriedResponse a -> b # foldl :: (b -> a -> b) -> b -> HistoriedResponse a -> b # foldl' :: (b -> a -> b) -> b -> HistoriedResponse a -> b # foldr1 :: (a -> a -> a) -> HistoriedResponse a -> a # foldl1 :: (a -> a -> a) -> HistoriedResponse a -> a # toList :: HistoriedResponse a -> [a] # null :: HistoriedResponse a -> Bool # length :: HistoriedResponse a -> Int # elem :: Eq a => a -> HistoriedResponse a -> Bool # maximum :: Ord a => HistoriedResponse a -> a # minimum :: Ord a => HistoriedResponse a -> a # sum :: Num a => HistoriedResponse a -> a # product :: Num a => HistoriedResponse a -> a # | |
Foldable Response | |
Defined in Network.HTTP.Client.Types Methods fold :: Monoid m => Response m -> m # foldMap :: Monoid m => (a -> m) -> Response a -> m # foldr :: (a -> b -> b) -> b -> Response a -> b # foldr' :: (a -> b -> b) -> b -> Response a -> b # foldl :: (b -> a -> b) -> b -> Response a -> b # foldl' :: (b -> a -> b) -> b -> Response a -> b # foldr1 :: (a -> a -> a) -> Response a -> a # foldl1 :: (a -> a -> a) -> Response a -> a # elem :: Eq a => a -> Response a -> Bool # maximum :: Ord a => Response a -> a # minimum :: Ord a => Response a -> a # | |
Foldable SmallArray | |
Defined in Data.Primitive.SmallArray Methods fold :: Monoid m => SmallArray m -> m # foldMap :: Monoid m => (a -> m) -> SmallArray a -> m # foldr :: (a -> b -> b) -> b -> SmallArray a -> b # foldr' :: (a -> b -> b) -> b -> SmallArray a -> b # foldl :: (b -> a -> b) -> b -> SmallArray a -> b # foldl' :: (b -> a -> b) -> b -> SmallArray a -> b # foldr1 :: (a -> a -> a) -> SmallArray a -> a # foldl1 :: (a -> a -> a) -> SmallArray a -> a # toList :: SmallArray a -> [a] # null :: SmallArray a -> Bool # length :: SmallArray a -> Int # elem :: Eq a => a -> SmallArray a -> Bool # maximum :: Ord a => SmallArray a -> a # minimum :: Ord a => SmallArray a -> a # sum :: Num a => SmallArray a -> a # product :: Num a => SmallArray a -> a # | |
Foldable Array | |
Defined in Data.Primitive.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 Vector | |
Defined in Data.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 HashSet | |
Defined in Data.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 ResolverWith Source # | |
Defined in Stack.Types.Resolver Methods fold :: Monoid m => ResolverWith m -> m # foldMap :: Monoid m => (a -> m) -> ResolverWith a -> m # foldr :: (a -> b -> b) -> b -> ResolverWith a -> b # foldr' :: (a -> b -> b) -> b -> ResolverWith a -> b # foldl :: (b -> a -> b) -> b -> ResolverWith a -> b # foldl' :: (b -> a -> b) -> b -> ResolverWith a -> b # foldr1 :: (a -> a -> a) -> ResolverWith a -> a # foldl1 :: (a -> a -> a) -> ResolverWith a -> a # toList :: ResolverWith a -> [a] # null :: ResolverWith a -> Bool # length :: ResolverWith a -> Int # elem :: Eq a => a -> ResolverWith a -> Bool # maximum :: Ord a => ResolverWith a -> a # minimum :: Ord a => ResolverWith a -> a # sum :: Num a => ResolverWith a -> a # product :: Num a => ResolverWith a -> a # | |
Foldable StackYamlLoc Source # | |
Defined in Stack.Types.Config Methods fold :: Monoid m => StackYamlLoc m -> m # foldMap :: Monoid m => (a -> m) -> StackYamlLoc a -> m # foldr :: (a -> b -> b) -> b -> StackYamlLoc a -> b # foldr' :: (a -> b -> b) -> b -> StackYamlLoc a -> b # foldl :: (b -> a -> b) -> b -> StackYamlLoc a -> b # foldl' :: (b -> a -> b) -> b -> StackYamlLoc a -> b # foldr1 :: (a -> a -> a) -> StackYamlLoc a -> a # foldl1 :: (a -> a -> a) -> StackYamlLoc a -> a # toList :: StackYamlLoc a -> [a] # null :: StackYamlLoc a -> Bool # length :: StackYamlLoc a -> Int # elem :: Eq a => a -> StackYamlLoc a -> Bool # maximum :: Ord a => StackYamlLoc a -> a # minimum :: Ord a => StackYamlLoc a -> a # sum :: Num a => StackYamlLoc a -> a # product :: Num a => StackYamlLoc a -> a # | |
Foldable LocalConfigStatus Source # | |
Defined in Stack.Config Methods fold :: Monoid m => LocalConfigStatus m -> m # foldMap :: Monoid m => (a -> m) -> LocalConfigStatus a -> m # foldr :: (a -> b -> b) -> b -> LocalConfigStatus a -> b # foldr' :: (a -> b -> b) -> b -> LocalConfigStatus a -> b # foldl :: (b -> a -> b) -> b -> LocalConfigStatus a -> b # foldl' :: (b -> a -> b) -> b -> LocalConfigStatus a -> b # foldr1 :: (a -> a -> a) -> LocalConfigStatus a -> a # foldl1 :: (a -> a -> a) -> LocalConfigStatus a -> a # toList :: LocalConfigStatus a -> [a] # null :: LocalConfigStatus a -> Bool # length :: LocalConfigStatus a -> Int # elem :: Eq a => a -> LocalConfigStatus a -> Bool # maximum :: Ord a => LocalConfigStatus a -> a # minimum :: Ord a => LocalConfigStatus a -> a # sum :: Num a => LocalConfigStatus a -> a # product :: Num a => LocalConfigStatus a -> a # | |
Foldable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Either a m -> m # foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m # 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 :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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: base-4.7.0.0 |
Defined in Data.Foldable 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 (Map k) | |
Defined in Data.Map.Internal 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 # | |
Foldable (HashMap k) | |
Defined in Data.HashMap.Base 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 (Array i) | Since: base-4.8.0.0 |
Defined in Data.Foldable 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: base-4.9.0.0 |
Defined in Data.Semigroup 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 :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable 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 f => Foldable (MaybeT f) | |
Defined in Control.Monad.Trans.Maybe Methods fold :: Monoid m => MaybeT f m -> m # foldMap :: Monoid m => (a -> m) -> MaybeT f a -> m # foldr :: (a -> b -> b) -> b -> MaybeT f a -> b # foldr' :: (a -> b -> b) -> b -> MaybeT f a -> b # foldl :: (b -> a -> b) -> b -> MaybeT f a -> b # foldl' :: (b -> a -> b) -> b -> MaybeT f a -> b # foldr1 :: (a -> a -> a) -> MaybeT f a -> a # foldl1 :: (a -> a -> a) -> MaybeT f a -> a # elem :: Eq a => a -> MaybeT f a -> Bool # maximum :: Ord a => MaybeT f a -> a # minimum :: Ord a => MaybeT f a -> a # | |
Foldable (Product a) | |
Defined in Data.Aeson.Config.Types Methods fold :: Monoid m => Product a m -> m # foldMap :: Monoid m => (a0 -> m) -> Product a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Product a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Product a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Product a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Product a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Product a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Product a a0 -> a0 # toList :: Product a a0 -> [a0] # null :: Product a a0 -> Bool # length :: Product a a0 -> Int # elem :: Eq a0 => a0 -> Product a a0 -> Bool # maximum :: Ord a0 => Product a a0 -> a0 # minimum :: Ord a0 => Product a a0 -> a0 # | |
Foldable f => Foldable (ListT f) | |
Defined in Control.Monad.Trans.List Methods fold :: Monoid m => ListT f m -> m # foldMap :: Monoid m => (a -> m) -> ListT f a -> m # foldr :: (a -> b -> b) -> b -> ListT f a -> b # foldr' :: (a -> b -> b) -> b -> ListT f a -> b # foldl :: (b -> a -> b) -> b -> ListT f a -> b # foldl' :: (b -> a -> b) -> b -> ListT f a -> b # foldr1 :: (a -> a -> a) -> ListT f a -> a # foldl1 :: (a -> a -> a) -> ListT f a -> a # elem :: Eq a => a -> ListT f a -> Bool # maximum :: Ord a => ListT f a -> a # minimum :: Ord a => ListT f a -> a # | |
Foldable (PoolMap key) | |
Defined in Data.KeyedPool Methods fold :: Monoid m => PoolMap key m -> m # foldMap :: Monoid m => (a -> m) -> PoolMap key a -> m # foldr :: (a -> b -> b) -> b -> PoolMap key a -> b # foldr' :: (a -> b -> b) -> b -> PoolMap key a -> b # foldl :: (b -> a -> b) -> b -> PoolMap key a -> b # foldl' :: (b -> a -> b) -> b -> PoolMap key a -> b # foldr1 :: (a -> a -> a) -> PoolMap key a -> a # foldl1 :: (a -> a -> a) -> PoolMap key a -> a # toList :: PoolMap key a -> [a] # null :: PoolMap key a -> Bool # length :: PoolMap key a -> Int # elem :: Eq a => a -> PoolMap key a -> Bool # maximum :: Ord a => PoolMap key a -> a # minimum :: Ord a => PoolMap key a -> a # | |
Foldable f => Foldable (Rec1 f) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 ()) :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 (CondTree v c) | |
Defined in Distribution.Types.CondTree Methods fold :: Monoid m => CondTree v c m -> m # foldMap :: Monoid m => (a -> m) -> CondTree v c a -> m # foldr :: (a -> b -> b) -> b -> CondTree v c a -> b # foldr' :: (a -> b -> b) -> b -> CondTree v c a -> b # foldl :: (b -> a -> b) -> b -> CondTree v c a -> b # foldl' :: (b -> a -> b) -> b -> CondTree v c a -> b # foldr1 :: (a -> a -> a) -> CondTree v c a -> a # foldl1 :: (a -> a -> a) -> CondTree v c a -> a # toList :: CondTree v c a -> [a] # null :: CondTree v c a -> Bool # length :: CondTree v c a -> Int # elem :: Eq a => a -> CondTree v c a -> Bool # maximum :: Ord a => CondTree v c a -> a # minimum :: Ord a => CondTree v c a -> a # | |
Foldable (CondBranch v c) | |
Defined in Distribution.Types.CondTree Methods fold :: Monoid m => CondBranch v c m -> m # foldMap :: Monoid m => (a -> m) -> CondBranch v c a -> m # foldr :: (a -> b -> b) -> b -> CondBranch v c a -> b # foldr' :: (a -> b -> b) -> b -> CondBranch v c a -> b # foldl :: (b -> a -> b) -> b -> CondBranch v c a -> b # foldl' :: (b -> a -> b) -> b -> CondBranch v c a -> b # foldr1 :: (a -> a -> a) -> CondBranch v c a -> a # foldl1 :: (a -> a -> a) -> CondBranch v c a -> a # toList :: CondBranch v c a -> [a] # null :: CondBranch v c a -> Bool # length :: CondBranch v c a -> Int # elem :: Eq a => a -> CondBranch v c a -> Bool # maximum :: Ord a => CondBranch v c a -> a # minimum :: Ord a => CondBranch v c a -> a # sum :: Num a => CondBranch v c a -> a # product :: Num a => CondBranch v c a -> a # | |
Foldable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const 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 (Ap f) | Since: base-4.12.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Ap f m -> m # foldMap :: Monoid m => (a -> m) -> Ap f a -> m # foldr :: (a -> b -> b) -> b -> Ap f a -> b # foldr' :: (a -> b -> b) -> b -> Ap f a -> b # foldl :: (b -> a -> b) -> b -> Ap f a -> b # foldl' :: (b -> a -> b) -> b -> Ap f a -> b # foldr1 :: (a -> a -> a) -> Ap f a -> a # foldl1 :: (a -> a -> a) -> Ap f a -> a # elem :: Eq a => a -> Ap f a -> Bool # maximum :: Ord a => Ap f a -> a # | |
Foldable f => Foldable (Alt f) | Since: base-4.12.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Alt f m -> m # foldMap :: Monoid m => (a -> m) -> Alt f a -> m # foldr :: (a -> b -> b) -> b -> Alt f a -> b # foldr' :: (a -> b -> b) -> b -> Alt f a -> b # foldl :: (b -> a -> b) -> b -> Alt f a -> b # foldl' :: (b -> a -> b) -> b -> Alt f a -> b # foldr1 :: (a -> a -> a) -> Alt f a -> a # foldl1 :: (a -> a -> a) -> Alt f a -> a # elem :: Eq a => a -> Alt f a -> Bool # maximum :: Ord a => Alt f a -> a # minimum :: Ord a => Alt f a -> a # | |
Foldable f => Foldable (IdentityT f) | |
Defined in Control.Monad.Trans.Identity Methods fold :: Monoid m => IdentityT f m -> m # foldMap :: Monoid m => (a -> m) -> IdentityT f a -> m # foldr :: (a -> b -> b) -> b -> IdentityT f a -> b # foldr' :: (a -> b -> b) -> b -> IdentityT f a -> b # foldl :: (b -> a -> b) -> b -> IdentityT f a -> b # foldl' :: (b -> a -> b) -> b -> IdentityT f a -> b # foldr1 :: (a -> a -> a) -> IdentityT f a -> a # foldl1 :: (a -> a -> a) -> IdentityT f a -> a # toList :: IdentityT f a -> [a] # null :: IdentityT f a -> Bool # length :: IdentityT f a -> Int # elem :: Eq a => a -> IdentityT f a -> Bool # maximum :: Ord a => IdentityT f a -> a # minimum :: Ord a => IdentityT f a -> a # | |
Foldable f => Foldable (WriterT w f) | |
Defined in Control.Monad.Trans.Writer.Strict Methods fold :: Monoid m => WriterT w f m -> m # foldMap :: Monoid m => (a -> m) -> WriterT w f a -> m # foldr :: (a -> b -> b) -> b -> WriterT w f a -> b # foldr' :: (a -> b -> b) -> b -> WriterT w f a -> b # foldl :: (b -> a -> b) -> b -> WriterT w f a -> b # foldl' :: (b -> a -> b) -> b -> WriterT w f a -> b # foldr1 :: (a -> a -> a) -> WriterT w f a -> a # foldl1 :: (a -> a -> a) -> WriterT w f a -> a # toList :: WriterT w f a -> [a] # null :: WriterT w f a -> Bool # length :: WriterT w f a -> Int # elem :: Eq a => a -> WriterT w f a -> Bool # maximum :: Ord a => WriterT w f a -> a # minimum :: Ord a => WriterT w f a -> a # | |
Foldable f => Foldable (WriterT w f) | |
Defined in Control.Monad.Trans.Writer.Lazy Methods fold :: Monoid m => WriterT w f m -> m # foldMap :: Monoid m => (a -> m) -> WriterT w f a -> m # foldr :: (a -> b -> b) -> b -> WriterT w f a -> b # foldr' :: (a -> b -> b) -> b -> WriterT w f a -> b # foldl :: (b -> a -> b) -> b -> WriterT w f a -> b # foldl' :: (b -> a -> b) -> b -> WriterT w f a -> b # foldr1 :: (a -> a -> a) -> WriterT w f a -> a # foldl1 :: (a -> a -> a) -> WriterT w f a -> a # toList :: WriterT w f a -> [a] # null :: WriterT w f a -> Bool # length :: WriterT w f a -> Int # elem :: Eq a => a -> WriterT w f a -> Bool # maximum :: Ord a => WriterT w f a -> a # minimum :: Ord a => WriterT w f a -> a # | |
Foldable f => Foldable (ExceptT e f) | |
Defined in Control.Monad.Trans.Except Methods fold :: Monoid m => ExceptT e f m -> m # foldMap :: Monoid m => (a -> m) -> ExceptT e f a -> m # foldr :: (a -> b -> b) -> b -> ExceptT e f a -> b # foldr' :: (a -> b -> b) -> b -> ExceptT e f a -> b # foldl :: (b -> a -> b) -> b -> ExceptT e f a -> b # foldl' :: (b -> a -> b) -> b -> ExceptT e f a -> b # foldr1 :: (a -> a -> a) -> ExceptT e f a -> a # foldl1 :: (a -> a -> a) -> ExceptT e f a -> a # toList :: ExceptT e f a -> [a] # null :: ExceptT e f a -> Bool # length :: ExceptT e f a -> Int # elem :: Eq a => a -> ExceptT e f a -> Bool # maximum :: Ord a => ExceptT e f a -> a # minimum :: Ord a => ExceptT e f a -> a # | |
Foldable f => Foldable (ErrorT e f) | |
Defined in Control.Monad.Trans.Error 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 (Tagged s) | |
Defined in Data.Tagged 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 # | |
Foldable (K1 i c :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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: base-4.9.0.0 |
Defined in Data.Functor.Product 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: base-4.9.0.0 |
Defined in Data.Functor.Sum 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 f => Foldable (M1 i c f) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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) | Since: base-4.9.0.0 |
Defined in Data.Foldable 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: base-4.9.0.0 |
Defined in Data.Functor.Compose 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 # |
class (Functor t, Foldable t) => Traversable (t :: Type -> Type) 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
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
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Instances
The class of semigroups (types with an associative binary operation).
Instances should satisfy the associativity law:
Since: base-4.9.0.0
Minimal complete definition
Methods
(<>) :: a -> a -> a infixr 6 #
An associative operation.
Reduce a non-empty list with <>
The default definition should be sufficient, but this can be overridden for efficiency.
stimes :: Integral b => b -> a -> a #
Repeat a value n
times.
Given that this works on a Semigroup
it is allowed to fail if
you request 0 or fewer repetitions, and the default definition
will do so.
By making this a member of the class, idempotent semigroups
and monoids can upgrade this to execute in O(1) by
picking stimes =
or stimesIdempotent
stimes =
respectively.stimesIdempotentMonoid
Instances
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
Instances
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
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
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
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
8-bit signed integer type
Instances
16-bit signed integer type
Instances
32-bit signed integer type
Instances
64-bit signed integer type
Instances
Invariant: Jn#
and Jp#
are used iff value doesn't fit in S#
Useful properties resulting from the invariants:
Instances
Type representing arbitrary-precision non-negative integers.
>>>
2^100 :: Natural
1267650600228229401496703205376
Operations whose result would be negative
,throw
(Underflow
:: ArithException
)
>>>
-1 :: Natural
*** Exception: arithmetic underflow
Since: base-4.8.0.0
Instances
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: base-2.1 |
Functor Maybe | Since: base-2.1 |
MonadFix Maybe | Since: base-2.1 |
Defined in Control.Monad.Fix | |
MonadFail Maybe | Since: base-4.9.0.0 |
Defined in Control.Monad.Fail | |
Applicative Maybe | Since: base-2.1 |
Foldable Maybe | Since: base-2.1 |
Defined in Data.Foldable 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: base-2.1 |
MonadPlus Maybe | Since: base-2.1 |
Alternative Maybe | Since: base-2.1 |
ToJSON1 Maybe | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Maybe a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Maybe a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Maybe a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Maybe a] -> Encoding # | |
FromJSON1 Maybe | |
MonadThrow Maybe | |
Defined in Control.Monad.Catch | |
Eq1 Maybe | Since: base-4.9.0.0 |
Ord1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 Maybe | Since: base-4.9.0.0 |
MonadFailure Maybe | |
NFData1 Maybe | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable1 Maybe | |
Defined in Data.Hashable.Class | |
FromValue ParsePackageConfig | |
Defined in Hpack.Config | |
MonadBaseControl Maybe Maybe | |
(Selector s, GToJSON enc arity (K1 i (Maybe a) :: Type -> Type), KeyValuePair enc pairs, Monoid pairs) => RecordToPairs enc pairs arity (S1 s (K1 i (Maybe a) :: Type -> Type)) | |
Defined in Data.Aeson.Types.ToJSON | |
(Selector s, FromJSON a) => FromRecord arity (S1 s (K1 i (Maybe a) :: Type -> Type)) | |
Defined in Data.Aeson.Types.FromJSON | |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Data a => Data (Maybe a) | Since: base-4.0.0.0 |
Defined in Data.Data 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) | Since: base-2.1 |
Read a => Read (Maybe a) | Since: base-2.1 |
Show a => Show (Maybe a) | Since: base-2.1 |
Generic (Maybe a) | |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Lift a => Lift (Maybe a) | |
NFData a => NFData (Maybe a) | |
Defined in Control.DeepSeq | |
Hashable a => Hashable (Maybe a) | |
Defined in Data.Hashable.Class | |
ToJSON a => ToJSON (Maybe a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (Maybe a) | |
Pretty a => Pretty (Maybe a) | |
Defined in Text.PrettyPrint.ANSI.Leijen.Internal | |
SingKind a => SingKind (Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
GMonoid a => GMonoid (Maybe a) | |
FromValue a => FromValue (ParseCommonOptions a) | |
Defined in Hpack.Config | |
FromValue a => FromValue (ParseConditionalSection a) | |
Defined in Hpack.Config | |
FromValue a => FromValue (ParseThenElse a) | |
Defined in Hpack.Config | |
ToHttpApiData a => ToHttpApiData (Maybe a) |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Maybe a -> Text # toEncodedUrlPiece :: Maybe a -> Builder # toHeader :: Maybe a -> ByteString # toQueryParam :: Maybe a -> Text # | |
FromHttpApiData a => FromHttpApiData (Maybe a) |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Maybe a) # parseHeader :: ByteString -> Either Text (Maybe a) # | |
MonoFunctor (Maybe a) | |
MonoFoldable (Maybe a) | |
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element (Maybe a) -> m) -> Maybe a -> m # ofoldr :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b # ofoldl' :: (a0 -> Element (Maybe a) -> a0) -> a0 -> Maybe a -> a0 # otoList :: Maybe a -> [Element (Maybe a)] # oall :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool # oany :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool # olength64 :: Maybe a -> Int64 # ocompareLength :: Integral i => Maybe a -> i -> Ordering # otraverse_ :: Applicative f => (Element (Maybe a) -> f b) -> Maybe a -> f () # ofor_ :: Applicative f => Maybe a -> (Element (Maybe a) -> f b) -> f () # omapM_ :: Applicative m => (Element (Maybe a) -> m ()) -> Maybe a -> m () # oforM_ :: Applicative m => Maybe a -> (Element (Maybe a) -> m ()) -> m () # ofoldlM :: Monad m => (a0 -> Element (Maybe a) -> m a0) -> a0 -> Maybe a -> m a0 # ofoldMap1Ex :: Semigroup m => (Element (Maybe a) -> m) -> Maybe a -> m # ofoldr1Ex :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) # ofoldl1Ex' :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) # headEx :: Maybe a -> Element (Maybe a) # lastEx :: Maybe a -> Element (Maybe a) # unsafeHead :: Maybe a -> Element (Maybe a) # unsafeLast :: Maybe a -> Element (Maybe a) # maximumByEx :: (Element (Maybe a) -> Element (Maybe a) -> Ordering) -> Maybe a -> Element (Maybe a) # minimumByEx :: (Element (Maybe a) -> Element (Maybe a) -> Ordering) -> Maybe a -> Element (Maybe a) # | |
MonoTraversable (Maybe a) | |
MonoPointed (Maybe a) | |
ToMustache ω => ToMustache (Maybe ω) | |
Defined in Text.Mustache.Internal.Types | |
PathPiece a => PathPiece (Maybe a) | |
Defined in Web.PathPieces | |
RawSql a => RawSql (Maybe a) | Since: persistent-1.0.1 |
Defined in Database.Persist.Sql.Class Methods rawSqlCols :: (DBName -> Text) -> Maybe a -> (Int, [Text]) # rawSqlColCountReason :: Maybe a -> String # rawSqlProcessRow :: [PersistValue] -> Either Text (Maybe a) # | |
PersistField a => PersistField (Maybe a) | |
Defined in Database.Persist.Class.PersistField Methods toPersistValue :: Maybe a -> PersistValue # fromPersistValue :: PersistValue -> Either Text (Maybe a) # | |
Generic1 Maybe | |
SingI (Nothing :: Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Each (Maybe a) (Maybe b) a b | |
SingI a2 => SingI (Just a2 :: Maybe a1) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Failure Maybe | |
Defined in Basement.Monad | |
type StM Maybe a | |
Defined in Control.Monad.Trans.Control | |
type Rep (Maybe a) | Since: base-4.6.0.0 |
data Sing (b :: Maybe a) | |
type DemoteRep (Maybe a) | |
Defined in GHC.Generics | |
type Element (Maybe a) | |
Defined in Data.MonoTraversable | |
type Rep1 Maybe | Since: base-4.6.0.0 |
Instances
Bounded Ordering | Since: base-2.1 |
Enum Ordering | Since: base-2.1 |
Eq Ordering | |
Data Ordering | Since: base-4.0.0.0 |
Defined in Data.Data 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 | |
Defined in GHC.Classes | |
Read Ordering | Since: base-2.1 |
Show Ordering | Since: base-2.1 |
Ix Ordering | Since: base-2.1 |
Defined in GHC.Arr | |
Generic Ordering | |
Semigroup Ordering | Since: base-4.9.0.0 |
Monoid Ordering | Since: base-2.1 |
NFData Ordering | |
Defined in Control.DeepSeq | |
Hashable Ordering | |
Defined in Data.Hashable.Class | |
ToJSON Ordering | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON Ordering | |
GMonoid Ordering | |
ToHttpApiData Ordering | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Ordering -> Text # toEncodedUrlPiece :: Ordering -> Builder # toHeader :: Ordering -> ByteString # toQueryParam :: Ordering -> Text # | |
FromHttpApiData Ordering | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text Ordering # parseHeader :: ByteString -> Either Text Ordering # | |
type Rep Ordering | Since: base-4.6.0.0 |
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
8-bit unsigned integer type
Instances
16-bit unsigned integer type
Instances
32-bit unsigned integer type
Instances
64-bit unsigned integer type
Instances
The Either
type represents values with two possibilities: a value of
type
is either Either
a b
or Left
a
.Right
b
The Either
type is sometimes used to represent a value which is
either correct or an error; by convention, the Left
constructor is
used to hold an error value and the Right
constructor is used to
hold a correct value (mnemonic: "right" also means "correct").
Examples
The type
is the type of values which can be either
a Either
String
Int
String
or an Int
. The Left
constructor can be used only on
String
s, and the Right
constructor can be used only on Int
s:
>>>
let s = Left "foo" :: Either String Int
>>>
s
Left "foo">>>
let n = Right 3 :: Either String Int
>>>
n
Right 3>>>
:type s
s :: Either String Int>>>
:type n
n :: Either String Int
The fmap
from our Functor
instance will ignore Left
values, but
will apply the supplied function to values contained in a Right
:
>>>
let s = Left "foo" :: Either String Int
>>>
let n = Right 3 :: Either String Int
>>>
fmap (*2) s
Left "foo">>>
fmap (*2) n
Right 6
The Monad
instance for Either
allows us to chain together multiple
actions which may fail, and fail overall if any of the individual
steps failed. First we'll write a function that can either parse an
Int
from a Char
, or fail.
>>>
import Data.Char ( digitToInt, isDigit )
>>>
:{
let parseEither :: Char -> Either String Int parseEither c | isDigit c = Right (digitToInt c) | otherwise = Left "parse error">>>
:}
The following should work, since both '1'
and '2'
can be
parsed as Int
s.
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither '1' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Right 3
But the following should fail overall, since the first operation where
we attempt to parse 'm'
as an Int
will fail:
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither 'm' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Left "parse error"
Instances
ToJSON2 Either | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Either a b -> Value # liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Either a b] -> Value # liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Either a b -> Encoding # liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Either a b] -> Encoding # | |
FromJSON2 Either | |
Defined in Data.Aeson.Types.FromJSON | |
Eq2 Either | Since: base-4.9.0.0 |
Ord2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] # | |
Show2 Either | Since: base-4.9.0.0 |
NFData2 Either | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable2 Either | |
Defined in Data.Hashable.Class | |
Monad (Either e) | Since: base-4.4.0.0 |
Functor (Either a) | Since: base-3.0 |
MonadFix (Either e) | Since: base-4.3.0.0 |
Defined in Control.Monad.Fix | |
Applicative (Either e) | Since: base-3.0 |
Foldable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Either a m -> m # foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m # 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: base-4.7.0.0 |
Defined in Data.Traversable | |
ToJSON a => ToJSON1 (Either a) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a0 -> Value) -> ([a0] -> Value) -> Either a a0 -> Value # liftToJSONList :: (a0 -> Value) -> ([a0] -> Value) -> [Either a a0] -> Value # liftToEncoding :: (a0 -> Encoding) -> ([a0] -> Encoding) -> Either a a0 -> Encoding # liftToEncodingList :: (a0 -> Encoding) -> ([a0] -> Encoding) -> [Either a a0] -> Encoding # | |
FromJSON a => FromJSON1 (Either a) | |
e ~ SomeException => MonadThrow (Either e) | |
Defined in Control.Monad.Catch | |
Eq a => Eq1 (Either a) | Since: base-4.9.0.0 |
Ord a => Ord1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read a => Read1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] # | |
Show a => Show1 (Either a) | Since: base-4.9.0.0 |
MonadFailure (Either a) | |
NFData a => NFData1 (Either a) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
e ~ SomeException => MonadCatch (Either e) | Since: exceptions-0.8.3 |
e ~ SomeException => MonadMask (Either e) | Since: exceptions-0.8.3 |
Defined in Control.Monad.Catch | |
Hashable a => Hashable1 (Either a) | |
Defined in Data.Hashable.Class | |
Generic1 (Either a :: Type -> Type) | |
MonadBaseControl (Either e) (Either e) | |
(Eq a, Eq b) => Eq (Either a b) | Since: base-2.1 |
(Data a, Data b) => Data (Either a b) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Either a b -> c (Either a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) # toConstr :: Either a b -> Constr # dataTypeOf :: Either a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r # gmapQr :: (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) | Since: base-2.1 |
(Read a, Read b) => Read (Either a b) | Since: base-3.0 |
(Show a, Show b) => Show (Either a b) | Since: base-3.0 |
Generic (Either a b) | |
Semigroup (Either a b) | Since: base-4.9.0.0 |
(Lift a, Lift b) => Lift (Either a b) | |
(IsNode a, IsNode b, Key a ~ Key b) => IsNode (Either a b) | |
(NFData a, NFData b) => NFData (Either a b) | |
Defined in Control.DeepSeq | |
(Hashable a, Hashable b) => Hashable (Either a b) | |
Defined in Data.Hashable.Class | |
(ToJSON a, ToJSON b) => ToJSON (Either a b) | |
Defined in Data.Aeson.Types.ToJSON | |
(FromJSON a, FromJSON b) => FromJSON (Either a b) | |
(ToHttpApiData a, ToHttpApiData b) => ToHttpApiData (Either a b) |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Either a b -> Text # toEncodedUrlPiece :: Either a b -> Builder # toHeader :: Either a b -> ByteString # toQueryParam :: Either a b -> Text # | |
(FromHttpApiData a, FromHttpApiData b) => FromHttpApiData (Either a b) |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Either a b) # parseHeader :: ByteString -> Either Text (Either a b) # | |
MonoFunctor (Either a b) | |
MonoFoldable (Either a b) | |
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element (Either a b) -> m) -> Either a b -> m # ofoldr :: (Element (Either a b) -> b0 -> b0) -> b0 -> Either a b -> b0 # ofoldl' :: (a0 -> Element (Either a b) -> a0) -> a0 -> Either a b -> a0 # otoList :: Either a b -> [Element (Either a b)] # oall :: (Element (Either a b) -> Bool) -> Either a b -> Bool # oany :: (Element (Either a b) -> Bool) -> Either a b -> Bool # olength :: Either a b -> Int # olength64 :: Either a b -> Int64 # ocompareLength :: Integral i => Either a b -> i -> Ordering # otraverse_ :: Applicative f => (Element (Either a b) -> f b0) -> Either a b -> f () # ofor_ :: Applicative f => Either a b -> (Element (Either a b) -> f b0) -> f () # omapM_ :: Applicative m => (Element (Either a b) -> m ()) -> Either a b -> m () # oforM_ :: Applicative m => Either a b -> (Element (Either a b) -> m ()) -> m () # ofoldlM :: Monad m => (a0 -> Element (Either a b) -> m a0) -> a0 -> Either a b -> m a0 # ofoldMap1Ex :: Semigroup m => (Element (Either a b) -> m) -> Either a b -> m # ofoldr1Ex :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Element (Either a b) # ofoldl1Ex' :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Element (Either a b) # headEx :: Either a b -> Element (Either a b) # lastEx :: Either a b -> Element (Either a b) # unsafeHead :: Either a b -> Element (Either a b) # unsafeLast :: Either a b -> Element (Either a b) # maximumByEx :: (Element (Either a b) -> Element (Either a b) -> Ordering) -> Either a b -> Element (Either a b) # minimumByEx :: (Element (Either a b) -> Element (Either a b) -> Ordering) -> Either a b -> Element (Either a b) # | |
MonoTraversable (Either a b) | |
MonoPointed (Either a b) | |
(PersistConfig c1, PersistConfig c2, PersistConfigPool c1 ~ PersistConfigPool c2, PersistConfigBackend c1 ~ PersistConfigBackend c2) => PersistConfig (Either c1 c2) | |
Defined in Database.Persist.Class.PersistConfig Associated Types type PersistConfigBackend (Either c1 c2) :: (Type -> Type) -> Type -> Type # type PersistConfigPool (Either c1 c2) :: Type # Methods loadConfig :: Value -> Parser (Either c1 c2) # applyEnv :: Either c1 c2 -> IO (Either c1 c2) # createPoolConfig :: Either c1 c2 -> IO (PersistConfigPool (Either c1 c2)) # runPool :: MonadUnliftIO m => Either c1 c2 -> PersistConfigBackend (Either c1 c2) m a -> PersistConfigPool (Either c1 c2) -> m a # | |
type Failure (Either a) | |
Defined in Basement.Monad | |
type StM (Either e) a | |
Defined in Control.Monad.Trans.Control | |
type Rep1 (Either a :: Type -> Type) | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 (Either a :: Type -> Type) = D1 (MetaData "Either" "Data.Either" "base" False) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
type Rep (Either a b) | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep (Either a b) = D1 (MetaData "Either" "Data.Either" "base" False) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b))) | |
type Key (Either a b) | |
Defined in Distribution.Compat.Graph | |
type Element (Either a b) | |
Defined in Data.MonoTraversable | |
type PersistConfigPool (Either c1 c2) | |
Defined in Database.Persist.Class.PersistConfig | |
type PersistConfigBackend (Either c1 c2) | |
Defined in Database.Persist.Class.PersistConfig |
CallStack
s are a lightweight method of obtaining a
partial call-stack at any point in the program.
A function can request its call-site with the HasCallStack
constraint.
For example, we can define
putStrLnWithCallStack :: HasCallStack => String -> IO ()
as a variant of putStrLn
that will get its call-site and print it,
along with the string given as argument. We can access the
call-stack inside putStrLnWithCallStack
with callStack
.
putStrLnWithCallStack :: HasCallStack => String -> IO () putStrLnWithCallStack msg = do putStrLn msg putStrLn (prettyCallStack callStack)
Thus, if we call putStrLnWithCallStack
we will get a formatted call-stack
alongside our string.
>>>
putStrLnWithCallStack "hello"
hello CallStack (from HasCallStack): putStrLnWithCallStack, called at <interactive>:2:1 in interactive:Ghci1
GHC solves HasCallStack
constraints in three steps:
- If there is a
CallStack
in scope -- i.e. the enclosing function has aHasCallStack
constraint -- GHC will append the new call-site to the existingCallStack
. - If there is no
CallStack
in scope -- e.g. in the GHCi session above -- and the enclosing definition does not have an explicit type signature, GHC will infer aHasCallStack
constraint for the enclosing definition (subject to the monomorphism restriction). - If there is no
CallStack
in scope and the enclosing definition has an explicit type signature, GHC will solve theHasCallStack
constraint for the singletonCallStack
containing just the current call-site.
CallStack
s do not interact with the RTS and do not require compilation
with -prof
. On the other hand, as they are built up explicitly via the
HasCallStack
constraints, they will generally not contain as much
information as the simulated call-stacks maintained by the RTS.
A CallStack
is a [(String, SrcLoc)]
. The String
is the name of
function that was called, the SrcLoc
is the call-site. The list is
ordered with the most recently called function at the head.
NOTE: The intrepid user may notice that HasCallStack
is just an
alias for an implicit parameter ?callStack :: CallStack
. This is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.8.1.0
data ShortByteString #
A compact representation of a Word8
vector.
It has a lower memory overhead than a ByteString
and and does not
contribute to heap fragmentation. It can be converted to or from a
ByteString
(at the cost of copying the string data). It supports very few
other operations.
It is suitable for use as an internal representation for code that needs
to keep many short strings in memory, but it should not be used as an
interchange type. That is, it should not generally be used in public APIs.
The ByteString
type is usually more suitable for use in interfaces; it is
more flexible and it supports a wide range of operations.
Instances
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
byteSwap16 :: Word16 -> Word16 #
Swap bytes in Word16
.
Since: base-4.7.0.0
byteSwap32 :: Word32 -> Word32 #
Reverse order of bytes in Word32
.
Since: base-4.7.0.0
byteSwap64 :: Word64 -> Word64 #
Reverse order of bytes in Word64
.
Since: base-4.7.0.0
A class of types that can be fully evaluated.
Since: deepseq-1.1.0.0
Minimal complete definition
Nothing
Methods
rnf
should reduce its argument to normal form (that is, fully
evaluate all sub-components), and then return '()'.
Generic
NFData
deriving
Starting with GHC 7.2, you can automatically derive instances
for types possessing a Generic
instance.
Note: Generic1
can be auto-derived starting with GHC 7.4
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics (Generic, Generic1) import Control.DeepSeq data Foo a = Foo a String deriving (Eq, Generic, Generic1) instance NFData a => NFData (Foo a) instance NFData1 Foo data Colour = Red | Green | Blue deriving Generic instance NFData Colour
Starting with GHC 7.10, the example above can be written more
concisely by enabling the new DeriveAnyClass
extension:
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} import GHC.Generics (Generic) import Control.DeepSeq data Foo a = Foo a String deriving (Eq, Generic, Generic1, NFData, NFData1) data Colour = Red | Green | Blue deriving (Generic, NFData)
Compatibility with previous deepseq
versions
Prior to version 1.4.0.0, the default implementation of the rnf
method was defined as
rnf
a =seq
a ()
However, starting with deepseq-1.4.0.0
, the default
implementation is based on DefaultSignatures
allowing for
more accurate auto-derived NFData
instances. If you need the
previously used exact default rnf
method implementation
semantics, use
instance NFData Colour where rnf x = seq x ()
or alternatively
instance NFData Colour where rnf = rwhnf
or
{-# LANGUAGE BangPatterns #-} instance NFData Colour where rnf !_ = ()
Instances
A Map from keys k
to values a
.
Instances
Eq2 Map | Since: containers-0.5.9 |
Ord2 Map | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
Show2 Map | Since: containers-0.5.9 |
BiPolyMap Map | |
Defined in Data.Containers Associated Types type BPMKeyConstraint Map key :: Constraint # Methods mapKeysWith :: (BPMKeyConstraint Map k1, BPMKeyConstraint Map k2) => (v -> v -> v) -> (k1 -> k2) -> Map k1 v -> Map k2 v # | |
Functor (Map k) | |
Foldable (Map k) | |
Defined in Data.Map.Internal 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 # | |
Traversable (Map k) | |
ToJSONKey k => ToJSON1 (Map k) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Map k a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Map k a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Map k a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Map k a] -> Encoding # | |
(FromJSONKey k, Ord k) => FromJSON1 (Map k) | |
Eq k => Eq1 (Map k) | Since: containers-0.5.9 |
Ord k => Ord1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
(Ord k, Read k) => Read1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
Show k => Show1 (Map k) | Since: containers-0.5.9 |
Ord key => PolyMap (Map key) | This instance uses the functions from Data.Map.Strict. |
Defined in Data.Containers Methods differenceMap :: Map key value1 -> Map key value2 -> Map key value1 # intersectionMap :: Map key value1 -> Map key value2 -> Map key value1 # intersectionWithMap :: (value1 -> value2 -> value3) -> Map key value1 -> Map key value2 -> Map key value3 # | |
Ord k => IsList (Map k v) | Since: containers-0.5.6.2 |
(Eq k, Eq a) => Eq (Map k a) | |
(Data k, Data a, Ord k) => Data (Map k a) | |
Defined in Data.Map.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) # toConstr :: Map k a -> Constr # dataTypeOf :: Map k a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a)) # gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # | |
(Ord k, Ord v) => Ord (Map k v) | |
(Ord k, Read k, Read e) => Read (Map k e) | |
(Show k, Show a) => Show (Map k a) | |
Ord k => Semigroup (Map k v) | |
Ord k => Monoid (Map k v) | |
(NFData k, NFData a) => NFData (Map k a) | |
Defined in Data.Map.Internal | |
(ToJSON v, ToJSONKey k) => ToJSON (Map k v) | |
Defined in Data.Aeson.Types.ToJSON | |
(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) | |
Ord k => SetContainer (Map k v) | This instance uses the functions from Data.Map.Strict. |
Defined in Data.Containers Associated Types type ContainerKey (Map k v) :: Type # Methods member :: ContainerKey (Map k v) -> Map k v -> Bool # notMember :: ContainerKey (Map k v) -> Map k v -> Bool # union :: Map k v -> Map k v -> Map k v # unions :: (MonoFoldable mono, Element mono ~ Map k v) => mono -> Map k v # difference :: Map k v -> Map k v -> Map k v # intersection :: Map k v -> Map k v -> Map k v # keys :: Map k v -> [ContainerKey (Map k v)] # | |
Ord key => IsMap (Map key value) | This instance uses the functions from Data.Map.Strict. |
Defined in Data.Containers Methods lookup :: ContainerKey (Map key value) -> Map key value -> Maybe (MapValue (Map key value)) # insertMap :: ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> Map key value # deleteMap :: ContainerKey (Map key value) -> Map key value -> Map key value # singletonMap :: ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value # mapFromList :: [(ContainerKey (Map key value), MapValue (Map key value))] -> Map key value # mapToList :: Map key value -> [(ContainerKey (Map key value), MapValue (Map key value))] # findWithDefault :: MapValue (Map key value) -> ContainerKey (Map key value) -> Map key value -> MapValue (Map key value) # insertWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> Map key value # insertWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> Map key value # insertLookupWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> MapValue (Map key value) -> Map key value -> (Maybe (MapValue (Map key value)), Map key value) # adjustMap :: (MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> Map key value -> Map key value # adjustWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> ContainerKey (Map key value) -> Map key value -> Map key value # updateMap :: (MapValue (Map key value) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> Map key value # updateWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> Map key value # updateLookupWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> (Maybe (MapValue (Map key value)), Map key value) # alterMap :: (Maybe (MapValue (Map key value)) -> Maybe (MapValue (Map key value))) -> ContainerKey (Map key value) -> Map key value -> Map key value # unionWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> Map key value -> Map key value -> Map key value # unionWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> Map key value -> Map key value -> Map key value # unionsWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> [Map key value] -> Map key value # mapWithKey :: (ContainerKey (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> Map key value -> Map key value # omapKeysWith :: (MapValue (Map key value) -> MapValue (Map key value) -> MapValue (Map key value)) -> (ContainerKey (Map key value) -> ContainerKey (Map key value)) -> Map key value -> Map key value # filterMap :: (MapValue (Map key value) -> Bool) -> Map key value -> Map key value # | |
Ord k => HasKeysSet (Map k v) | |
MonoFunctor (Map k v) | |
MonoFoldable (Map k v) | |
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element (Map k v) -> m) -> Map k v -> m # ofoldr :: (Element (Map k v) -> b -> b) -> b -> Map k v -> b # ofoldl' :: (a -> Element (Map k v) -> a) -> a -> Map k v -> a # otoList :: Map k v -> [Element (Map k v)] # oall :: (Element (Map k v) -> Bool) -> Map k v -> Bool # oany :: (Element (Map k v) -> Bool) -> Map k v -> Bool # olength64 :: Map k v -> Int64 # ocompareLength :: Integral i => Map k v -> i -> Ordering # otraverse_ :: Applicative f => (Element (Map k v) -> f b) -> Map k v -> f () # ofor_ :: Applicative f => Map k v -> (Element (Map k v) -> f b) -> f () # omapM_ :: Applicative m => (Element (Map k v) -> m ()) -> Map k v -> m () # oforM_ :: Applicative m => Map k v -> (Element (Map k v) -> m ()) -> m () # ofoldlM :: Monad m => (a -> Element (Map k v) -> m a) -> a -> Map k v -> m a # ofoldMap1Ex :: Semigroup m => (Element (Map k v) -> m) -> Map k v -> m # ofoldr1Ex :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) # ofoldl1Ex' :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) # headEx :: Map k v -> Element (Map k v) # lastEx :: Map k v -> Element (Map k v) # unsafeHead :: Map k v -> Element (Map k v) # unsafeLast :: Map k v -> Element (Map k v) # maximumByEx :: (Element (Map k v) -> Element (Map k v) -> Ordering) -> Map k v -> Element (Map k v) # minimumByEx :: (Element (Map k v) -> Element (Map k v) -> Ordering) -> Map k v -> Element (Map k v) # | |
MonoTraversable (Map k v) | |
Ord k => GrowingAppend (Map k v) | |
Defined in Data.MonoTraversable | |
ToMustache ω => ToMustache (Map String ω) | |
Defined in Text.Mustache.Internal.Types | |
ToMustache ω => ToMustache (Map Text ω) | |
Defined in Text.Mustache.Internal.Types | |
ToMustache ω => ToMustache (Map Text ω) | |
Defined in Text.Mustache.Internal.Types | |
PersistFieldSql v => PersistFieldSql (Map Text v) | |
PersistField v => PersistField (Map Text v) | |
Defined in Database.Persist.Class.PersistField Methods toPersistValue :: Map Text v -> PersistValue # fromPersistValue :: PersistValue -> Either Text (Map Text v) # | |
(Lift' k, Lift' v) => Lift' (Map k v) | |
Defined in Database.Persist.TH | |
type BPMKeyConstraint Map key | |
Defined in Data.Containers | |
type Item (Map k v) | |
Defined in Data.Map.Internal | |
type ContainerKey (Map k v) | |
Defined in Data.Containers | |
type MapValue (Map key value) | |
Defined in Data.Containers | |
type KeySet (Map k v) | |
Defined in Data.Containers | |
type Element (Map k v) | |
Defined in Data.MonoTraversable |
error :: HasCallStack => [Char] -> a #
error
stops execution and displays an error message.
undefined :: HasCallStack => a #
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where #
Monads that also support choice and failure.
Minimal complete definition
Nothing
Methods
The identity of mplus
. It should also satisfy the equations
mzero >>= f = mzero v >> mzero = mzero
The default definition is
mzero = empty
An associative operation. The default definition is
mplus = (<|>
)
Instances
class Applicative f => Alternative (f :: Type -> Type) where #
A monoid on applicative functors.
If defined, some
and many
should be the least solutions
of the equations:
Methods
(<|>) :: f a -> f a -> f a infixl 3 #
An associative binary operation
One or more.
Zero or more.
Instances
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 #
Same as >>=
, but with the arguments interchanged.
when :: Applicative f => Bool -> f () -> f () #
Conditional execution of Applicative
expressions. For example,
when debug (putStrLn "Debugging")
will output the string Debugging
if the Boolean value debug
is True
, and otherwise do nothing.
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r #
Promote a function to a monad, scanning the monadic arguments from left to right. For example,
liftM2 (+) [0,1] [0,2] = [0,2,1,3] liftM2 (+) (Just 1) Nothing = Nothing
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]
flip :: (a -> b -> c) -> b -> a -> c #
takes its (first) two arguments in the reverse order of flip
ff
.
>>>
flip (++) "hello" "world"
"worldhello"
($!) :: (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.
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]
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
""
fromMaybe :: a -> Maybe a -> a #
The fromMaybe
function takes a default value and and Maybe
value. If the Maybe
is Nothing
, it returns the default values;
otherwise, it returns the value contained in the Maybe
.
Examples
Basic usage:
>>>
fromMaybe "" (Just "Hello, World!")
"Hello, World!"
>>>
fromMaybe "" Nothing
""
Read an integer from a string using readMaybe
. If we fail to
parse an integer, we want to return 0
by default:
>>>
import Text.Read ( readMaybe )
>>>
fromMaybe 0 (readMaybe "5")
5>>>
fromMaybe 0 (readMaybe "")
0
maybeToList :: Maybe a -> [a] #
The maybeToList
function returns an empty list when given
Nothing
or a singleton list when not given Nothing
.
Examples
Basic usage:
>>>
maybeToList (Just 7)
[7]
>>>
maybeToList Nothing
[]
One can use maybeToList
to avoid pattern matching when combined
with a function that (safely) works on lists:
>>>
import Text.Read ( readMaybe )
>>>
sum $ maybeToList (readMaybe "3")
3>>>
sum $ maybeToList (readMaybe "")
0
listToMaybe :: [a] -> Maybe a #
The listToMaybe
function returns Nothing
on an empty list
or
where Just
aa
is the first element of the list.
Examples
Basic usage:
>>>
listToMaybe []
Nothing
>>>
listToMaybe [9]
Just 9
>>>
listToMaybe [1,2,3]
Just 1
Composing maybeToList
with listToMaybe
should be the identity
on singleton/empty lists:
>>>
maybeToList $ listToMaybe [5]
[5]>>>
maybeToList $ listToMaybe []
[]
But not on lists with more than one element:
>>>
maybeToList $ listToMaybe [1,2,3]
[1]
catMaybes :: [Maybe a] -> [a] #
The catMaybes
function takes a list of Maybe
s and returns
a list of all the Just
values.
Examples
Basic usage:
>>>
catMaybes [Just 1, Nothing, Just 3]
[1,3]
When constructing a list of Maybe
values, catMaybes
can be used
to return all of the "success" results (if the list is the result
of a map
, then mapMaybe
would be more appropriate):
>>>
import Text.Read ( readMaybe )
>>>
[readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
[Just 1,Nothing,Just 3]>>>
catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
[1,3]
mapMaybe :: (a -> Maybe b) -> [a] -> [b] #
The mapMaybe
function is a version of map
which can throw
out elements. In particular, the functional argument returns
something of type
. If this is Maybe
bNothing
, no element
is added on to the result list. If it is
, then Just
bb
is
included in the result list.
Examples
Using
is a shortcut for mapMaybe
f x
in most cases:catMaybes
$ map
f x
>>>
import Text.Read ( readMaybe )
>>>
let readMaybeInt = readMaybe :: String -> Maybe Int
>>>
mapMaybe readMaybeInt ["1", "Foo", "3"]
[1,3]>>>
catMaybes $ map readMaybeInt ["1", "Foo", "3"]
[1,3]
If we map the Just
constructor, the entire list should be returned:
>>>
mapMaybe Just [1,2,3]
[1,2,3]
replicate :: Int -> a -> [a] #
replicate
n x
is a list of length n
with x
the value of
every element.
It is an instance of the more general genericReplicate
,
in which n
may be of any integral type.
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] == []
take
n
, applied to a list xs
, returns the prefix of xs
of length n
, or xs
itself if n >
:length
xs
take 5 "Hello World!" == "Hello" take 3 [1,2,3,4,5] == [1,2,3] take 3 [1,2] == [1,2] take 3 [] == [] take (-1) [1,2] == [] take 0 [1,2] == []
It is an instance of the more general genericTake
,
in which n
may be of any integral type.
drop
n xs
returns the suffix of xs
after the first n
elements, or []
if n >
:length
xs
drop 6 "Hello World!" == "World!" drop 3 [1,2,3,4,5] == [4,5] drop 3 [1,2] == [] drop 3 [] == [] drop (-1) [1,2] == [1,2] drop 0 [1,2] == [1,2]
It is an instance of the more general genericDrop
,
in which n
may be of any integral type.
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])
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],[])
lookup :: Eq a => a -> [(a, b)] -> Maybe b #
lookup
key assocs
looks up a key in an association list.
(^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 #
raise a number to an integral power
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
lcm :: Integral a => a -> a -> a #
is the smallest positive integer that both lcm
x yx
and y
divide.
(<$>) :: 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)
void :: Functor f => f a -> f () #
discards or ignores the result of evaluation, such
as the return value of an void
valueIO
action.
Examples
Replace the contents of a
with unit:Maybe
Int
>>>
void Nothing
Nothing>>>
void (Just 3)
Just ()
Replace the contents of an
with unit,
resulting in an Either
Int
Int
:Either
Int
'()'
>>>
void (Left 8675309)
Left 8675309>>>
void (Right 8675309)
Right ()
Replace every element of a list with unit:
>>>
void [1,2,3]
[(),(),()]
Replace the second element of a pair with unit:
>>>
void (1,2)
(1,())
Discard the result of an IO
action:
>>>
mapM print [1,2]
1 2 [(),()]>>>
void $ mapM print [1,2]
1 2
comparing :: Ord a => (b -> a) -> b -> b -> Ordering #
comparing p x y = compare (p x) (p y)
Useful combinator for use in conjunction with the xxxBy
family
of functions from Data.List, for example:
... sortBy (comparing fst) ...
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
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
.
words
breaks a string up into a list of words, which were delimited
by white space.
>>>
words "Lorem ipsum\ndolor"
["Lorem","ipsum","dolor"]
Boolean monoid under disjunction (||
).
>>>
getAny (Any True <> mempty <> Any False)
True
>>>
getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))
True
Instances
Bounded Any | Since: base-2.1 |
Eq Any | Since: base-2.1 |
Data Any | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Any -> c Any # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Any # dataTypeOf :: Any -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Any) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Any) # gmapT :: (forall b. Data b => b -> b) -> Any -> Any # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r # gmapQ :: (forall d. Data d => d -> u) -> Any -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Any -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Any -> m Any # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m Any # | |
Ord Any | Since: base-2.1 |
Read Any | Since: base-2.1 |
Show Any | Since: base-2.1 |
Generic Any | |
Semigroup Any | Since: base-4.9.0.0 |
Monoid Any | Since: base-2.1 |
NFData Any | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
GMonoid Any | |
ToHttpApiData Any | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Any -> Text # toEncodedUrlPiece :: Any -> Builder # toHeader :: Any -> ByteString # toQueryParam :: Any -> Text # | |
FromHttpApiData Any | |
Defined in Web.Internal.HttpApiData | |
type Rep Any | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () #
Map each element of a structure to an action, evaluate these
actions from left to right, and ignore the results. For a version
that doesn't ignore the results see traverse
.
for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () #
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
.
concat :: Foldable t => t [a] -> [a] #
The concatenation of all the elements of a container of lists.
concatMap :: Foldable t => (a -> [b]) -> t a -> [b] #
Map a function over all the elements of a container and concatenate the resulting lists.
any :: Foldable t => (a -> Bool) -> t a -> Bool #
Determines whether any element of the structure satisfies the predicate.
all :: Foldable t => (a -> Bool) -> t a -> Bool #
Determines whether all elements of the structure satisfy the predicate.
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.
optional :: Alternative f => f a -> f (Maybe a) #
One or none.
for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) #
filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] #
This generalizes the list-based filter
function.
foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #
The foldM
function is analogous to foldl
, except that its result is
encapsulated in a monad. Note that foldM
works from left-to-right over
the list arguments. This could be an issue where (
and the `folded
function' are not commutative.>>
)
foldM f a1 [x1, x2, ..., xm] == do a2 <- f a1 x1 a3 <- f a2 x2 ... f am xm
If right-to-left evaluation is required, the input list should be reversed.
unless :: Applicative f => Bool -> f () -> f () #
The reverse of when
.
Builder
s denote sequences of bytes.
They are Monoid
s where
mempty
is the zero-length sequence and
mappend
is concatenation, which runs in O(1).
The class of types that can be converted to a hash value.
Minimal implementation: hashWithSalt
.
Instances
A space efficient, packed, unboxed Unicode text type.
Instances
A map from keys to values. A map cannot contain duplicate keys; each key can map to at most one value.
Instances
Lift TemplateCache | |
Defined in Text.Mustache.Internal.Types Methods lift :: TemplateCache -> Q Exp # | |
KeyValue Object | Constructs a singleton |
Eq2 HashMap | |
Ord2 HashMap | |
Defined in Data.HashMap.Base | |
Show2 HashMap | |
Hashable2 HashMap | |
Defined in Data.HashMap.Base | |
BiPolyMap HashMap | |
Defined in Data.Containers Associated Types type BPMKeyConstraint HashMap key :: Constraint # Methods mapKeysWith :: (BPMKeyConstraint HashMap k1, BPMKeyConstraint HashMap k2) => (v -> v -> v) -> (k1 -> k2) -> HashMap k1 v -> HashMap k2 v # | |
Functor (HashMap k) | |
Foldable (HashMap k) | |
Defined in Data.HashMap.Base 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 # | |
Traversable (HashMap k) | |
Defined in Data.HashMap.Base | |
ToJSONKey k => ToJSON1 (HashMap k) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> HashMap k a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [HashMap k a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> HashMap k a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [HashMap k a] -> Encoding # | |
(FromJSONKey k, Eq k, Hashable k) => FromJSON1 (HashMap k) | |
Eq k => Eq1 (HashMap k) | |
Ord k => Ord1 (HashMap k) | |
Defined in Data.HashMap.Base | |
(Eq k, Hashable k, Read k) => Read1 (HashMap k) | |
Defined in Data.HashMap.Base | |
Show k => Show1 (HashMap k) | |
Hashable k => Hashable1 (HashMap k) | |
Defined in Data.HashMap.Base | |
(Eq key, Hashable key) => PolyMap (HashMap key) | This instance uses the functions from Data.HashMap.Strict. |
Defined in Data.Containers Methods differenceMap :: HashMap key value1 -> HashMap key value2 -> HashMap key value1 # intersectionMap :: HashMap key value1 -> HashMap key value2 -> HashMap key value1 # intersectionWithMap :: (value1 -> value2 -> value3) -> HashMap key value1 -> HashMap key value2 -> HashMap key value3 # | |
(Eq k, Hashable k) => IsList (HashMap k v) | |
(Eq k, Eq v) => Eq (HashMap k v) | |
(Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) | |
Defined in Data.HashMap.Base Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashMap k v -> c (HashMap k v) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashMap k v) # toConstr :: HashMap k v -> Constr # dataTypeOf :: HashMap k v -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HashMap k v)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashMap k v)) # gmapT :: (forall b. Data b => b -> b) -> HashMap k v -> HashMap k v # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r # gmapQ :: (forall d. Data d => d -> u) -> HashMap k v -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HashMap k v -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # | |
(Ord k, Ord v) => Ord (HashMap k v) | The order is total. Note: Because the hash is not guaranteed to be stable across library
versions, OSes, or architectures, neither is an actual order of elements in
|
Defined in Data.HashMap.Base | |
(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) | |
(Show k, Show v) => Show (HashMap k v) | |
(Eq k, Hashable k) => Semigroup (HashMap k v) | |
(Eq k, Hashable k) => Monoid (HashMap k v) | |
(NFData k, NFData v) => NFData (HashMap k v) | |
Defined in Data.HashMap.Base | |
(Hashable k, Hashable v) => Hashable (HashMap k v) | |
Defined in Data.HashMap.Base | |
(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) | |
Defined in Data.Aeson.Types.ToJSON | |
(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (HashMap k v) | |
(Eq key, Hashable key) => SetContainer (HashMap key value) | This instance uses the functions from Data.HashMap.Strict. |
Defined in Data.Containers Associated Types type ContainerKey (HashMap key value) :: Type # Methods member :: ContainerKey (HashMap key value) -> HashMap key value -> Bool # notMember :: ContainerKey (HashMap key value) -> HashMap key value -> Bool # union :: HashMap key value -> HashMap key value -> HashMap key value # unions :: (MonoFoldable mono, Element mono ~ HashMap key value) => mono -> HashMap key value # difference :: HashMap key value -> HashMap key value -> HashMap key value # intersection :: HashMap key value -> HashMap key value -> HashMap key value # keys :: HashMap key value -> [ContainerKey (HashMap key value)] # | |
(Eq key, Hashable key) => IsMap (HashMap key value) | This instance uses the functions from Data.HashMap.Strict. |
Defined in Data.Containers Methods lookup :: ContainerKey (HashMap key value) -> HashMap key value -> Maybe (MapValue (HashMap key value)) # insertMap :: ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> HashMap key value -> HashMap key value # deleteMap :: ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value # singletonMap :: ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> HashMap key value # mapFromList :: [(ContainerKey (HashMap key value), MapValue (HashMap key value))] -> HashMap key value # mapToList :: HashMap key value -> [(ContainerKey (HashMap key value), MapValue (HashMap key value))] # findWithDefault :: MapValue (HashMap key value) -> ContainerKey (HashMap key value) -> HashMap key value -> MapValue (HashMap key value) # insertWith :: (MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> HashMap key value -> HashMap key value # insertWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> HashMap key value -> HashMap key value # insertLookupWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> HashMap key value -> (Maybe (MapValue (HashMap key value)), HashMap key value) # adjustMap :: (MapValue (HashMap key value) -> MapValue (HashMap key value)) -> ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value # adjustWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value # updateMap :: (MapValue (HashMap key value) -> Maybe (MapValue (HashMap key value))) -> ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value # updateWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> Maybe (MapValue (HashMap key value))) -> ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value # updateLookupWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> Maybe (MapValue (HashMap key value))) -> ContainerKey (HashMap key value) -> HashMap key value -> (Maybe (MapValue (HashMap key value)), HashMap key value) # alterMap :: (Maybe (MapValue (HashMap key value)) -> Maybe (MapValue (HashMap key value))) -> ContainerKey (HashMap key value) -> HashMap key value -> HashMap key value # unionWith :: (MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> HashMap key value -> HashMap key value -> HashMap key value # unionWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> HashMap key value -> HashMap key value -> HashMap key value # unionsWith :: (MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> [HashMap key value] -> HashMap key value # mapWithKey :: (ContainerKey (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> HashMap key value -> HashMap key value # omapKeysWith :: (MapValue (HashMap key value) -> MapValue (HashMap key value) -> MapValue (HashMap key value)) -> (ContainerKey (HashMap key value) -> ContainerKey (HashMap key value)) -> HashMap key value -> HashMap key value # filterMap :: (MapValue (HashMap key value) -> Bool) -> HashMap key value -> HashMap key value # | |
(Hashable k, Eq k) => HasKeysSet (HashMap k v) | |
MonoFunctor (HashMap k v) | |
MonoFoldable (HashMap k v) | |
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element (HashMap k v) -> m) -> HashMap k v -> m # ofoldr :: (Element (HashMap k v) -> b -> b) -> b -> HashMap k v -> b # ofoldl' :: (a -> Element (HashMap k v) -> a) -> a -> HashMap k v -> a # otoList :: HashMap k v -> [Element (HashMap k v)] # oall :: (Element (HashMap k v) -> Bool) -> HashMap k v -> Bool # oany :: (Element (HashMap k v) -> Bool) -> HashMap k v -> Bool # onull :: HashMap k v -> Bool # olength :: HashMap k v -> Int # olength64 :: HashMap k v -> Int64 # ocompareLength :: Integral i => HashMap k v -> i -> Ordering # otraverse_ :: Applicative f => (Element (HashMap k v) -> f b) -> HashMap k v -> f () # ofor_ :: Applicative f => HashMap k v -> (Element (HashMap k v) -> f b) -> f () # omapM_ :: Applicative m => (Element (HashMap k v) -> m ()) -> HashMap k v -> m () # oforM_ :: Applicative m => HashMap k v -> (Element (HashMap k v) -> m ()) -> m () # ofoldlM :: Monad m => (a -> Element (HashMap k v) -> m a) -> a -> HashMap k v -> m a # ofoldMap1Ex :: Semigroup m => (Element (HashMap k v) -> m) -> HashMap k v -> m # ofoldr1Ex :: (Element (HashMap k v) -> Element (HashMap k v) -> Element (HashMap k v)) -> HashMap k v -> Element (HashMap k v) # ofoldl1Ex' :: (Element (HashMap k v) -> Element (HashMap k v) -> Element (HashMap k v)) -> HashMap k v -> Element (HashMap k v) # headEx :: HashMap k v -> Element (HashMap k v) # lastEx :: HashMap k v -> Element (HashMap k v) # unsafeHead :: HashMap k v -> Element (HashMap k v) # unsafeLast :: HashMap k v -> Element (HashMap k v) # maximumByEx :: (Element (HashMap k v) -> Element (HashMap k v) -> Ordering) -> HashMap k v -> Element (HashMap k v) # minimumByEx :: (Element (HashMap k v) -> Element (HashMap k v) -> Ordering) -> HashMap k v -> Element (HashMap k v) # | |
MonoTraversable (HashMap k v) | |
(Eq k, Hashable k) => GrowingAppend (HashMap k v) | |
Defined in Data.MonoTraversable | |
ToMustache ω => ToMustache (HashMap String ω) | |
Defined in Text.Mustache.Internal.Types | |
ToMustache ω => ToMustache (HashMap Text ω) | |
Defined in Text.Mustache.Internal.Types | |
ToMustache ω => ToMustache (HashMap Text ω) | |
Defined in Text.Mustache.Internal.Types | |
MonadReader (Context Value, TemplateCache) SubM | |
Defined in Text.Mustache.Internal.Types | |
type BPMKeyConstraint HashMap key | |
Defined in Data.Containers | |
type Item (HashMap k v) | |
Defined in Data.HashMap.Base | |
type ContainerKey (HashMap key value) | |
Defined in Data.Containers | |
type MapValue (HashMap key value) | |
Defined in Data.Containers | |
type KeySet (HashMap k v) | |
Defined in Data.Containers | |
type Element (HashMap k v) | |
Defined in Data.MonoTraversable |
class Monad m => MonadThrow (m :: Type -> Type) where #
A class for monads in which exceptions may be thrown.
Instances should obey the following law:
throwM e >> x = throwM e
In other words, throwing an exception short-circuits the rest of the monadic computation.
Methods
throwM :: Exception e => e -> m a #
Throw an exception. Note that this throws when this action is run in
the monad m
, not when it is applied. It is a generalization of
Control.Exception's throwIO
.
Should satisfy the law:
throwM e >> f = throwM e
Instances
Haskell defines operations to read and write characters from and to files,
represented by values of type Handle
. Each value of this type is a
handle: a record used by the Haskell run-time system to manage I/O
with file system objects. A handle has at least the following properties:
- whether it manages input or output or both;
- whether it is open, closed or semi-closed;
- whether the object is seekable;
- whether buffering is disabled, or enabled on a line or block basis;
- a buffer (whose length may be zero).
Most handles will also have a current I/O position indicating where the next
input or output operation will occur. A handle is readable if it
manages only input or both input and output; likewise, it is writable if
it manages only output or both input and output. A handle is open when
first allocated.
Once it is closed it can no longer be used for either input or output,
though an implementation cannot re-use its storage while references
remain to it. Handles are in the Show
and Eq
classes. The string
produced by showing a handle is system dependent; it should include
enough information to identify the handle for debugging. A handle is
equal according to ==
only to itself; no attempt
is made to compare the internal state of different handles for equality.
A ThreadId
is an abstract type representing a handle to a thread.
ThreadId
is an instance of Eq
, Ord
and Show
, where
the Ord
instance implements an arbitrary total ordering over
ThreadId
s. The Show
instance lets you convert an arbitrary-valued
ThreadId
to string form; showing a ThreadId
value is occasionally
useful when debugging or diagnosing the behaviour of a concurrent
program.
Note: in GHC, if you have a ThreadId
, you essentially have
a pointer to the thread itself. This means the thread itself can't be
garbage collected until you drop the ThreadId
.
This misfeature will hopefully be corrected at a later date.
Instances
Eq ThreadId | Since: base-4.2.0.0 |
Ord ThreadId | Since: base-4.2.0.0 |
Defined in GHC.Conc.Sync | |
Show ThreadId | Since: base-4.2.0.0 |
NFData ThreadId | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Hashable ThreadId | |
Defined in Data.Hashable.Class | |
PrimUnlifted ThreadId | Since: primitive-0.6.4.0 |
Defined in Data.Primitive.UnliftedArray |
waitBothSTM :: Async a -> Async b -> STM (a, b) #
A version of waitBoth
that can be used inside an STM transaction.
Since: async-2.1.0
waitEitherSTM_ :: Async a -> Async b -> STM () #
A version of waitEither_
that can be used inside an STM transaction.
Since: async-2.1.0
waitEitherSTM :: Async a -> Async b -> STM (Either a b) #
A version of waitEither
that can be used inside an STM transaction.
Since: async-2.1.0
waitEitherCatchSTM :: Async a -> Async b -> STM (Either (Either SomeException a) (Either SomeException b)) #
A version of waitEitherCatch
that can be used inside an STM transaction.
Since: async-2.1.0
waitAnySTM :: [Async a] -> STM (Async a, a) #
A version of waitAny
that can be used inside an STM transaction.
Since: async-2.1.0
waitAnyCatchSTM :: [Async a] -> STM (Async a, Either SomeException a) #
A version of waitAnyCatch
that can be used inside an STM transaction.
Since: async-2.1.0
pollSTM :: Async a -> STM (Maybe (Either SomeException a)) #
A version of poll
that can be used inside an STM transaction.
waitCatchSTM :: Async a -> STM (Either SomeException a) #
A version of waitCatch
that can be used inside an STM transaction.
An asynchronous action spawned by async
or withAsync
.
Asynchronous actions are executed in a separate thread, and
operations are provided for waiting for asynchronous actions to
complete and obtaining their results (see e.g. wait
).
Instances
Functor Async | |
Eq (Async a) | |
Ord (Async a) | |
Defined in Control.Concurrent.Async | |
Hashable (Async a) | |
Defined in Control.Concurrent.Async |
Since Void
values logically don't exist, this witnesses the
logical reasoning tool of "ex falso quodlibet".
>>>
let x :: Either Void Int; x = Right 5
>>>
:{
case x of Right r -> r Left l -> absurd l :} 5
Since: base-4.8.0.0
Uninhabited data type
Since: base-4.8.0.0
Instances
Eq Void | Since: base-4.8.0.0 |
Data Void | Since: base-4.8.0.0 |
Defined in Data.Void Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Void -> c Void # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Void # dataTypeOf :: Void -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Void) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Void) # gmapT :: (forall b. Data b => b -> b) -> Void -> Void # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r # gmapQ :: (forall d. Data d => d -> u) -> Void -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Void -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Void -> m Void # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void # | |
Ord Void | Since: base-4.8.0.0 |
Read Void | Reading a Since: base-4.8.0.0 |
Show Void | Since: base-4.8.0.0 |
Ix Void | Since: base-4.8.0.0 |
Generic Void | |
Semigroup Void | Since: base-4.9.0.0 |
NFData Void | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Hashable Void | |
Defined in Data.Hashable.Class | |
ToJSON Void | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON Void | |
Exception Void | Since: base-4.8.0.0 |
Defined in Data.Void Methods toException :: Void -> SomeException # fromException :: SomeException -> Maybe Void # displayException :: Void -> String # | |
ToHttpApiData Void | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Void -> Text # toEncodedUrlPiece :: Void -> Builder # toHeader :: Void -> ByteString # toQueryParam :: Void -> Text # | |
FromHttpApiData Void | Parsing a |
Defined in Web.Internal.HttpApiData | |
type Rep Void | Since: base-4.8.0.0 |
Chan
is an abstract type representing an unbounded FIFO channel.
class Monad m => MonadIO (m :: Type -> Type) where #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Instances
replicateM_ :: Applicative m => Int -> m a -> m () #
Like replicateM
, but discards the result.
foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () #
Like foldM
, but discards the result.
zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m () #
zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c] #
forever :: Applicative f => f a -> f b #
Repeat an action indefinitely.
Examples
A common use of forever
is to process input from network sockets,
Handle
s, and channels
(e.g. MVar
and
Chan
).
For example, here is how we might implement an echo
server, using
forever
both to listen for client connections on a network socket
and to echo client input on client connection handles:
echoServer :: Socket -> IO () echoServer socket =forever
$ do client <- accept socketforkFinally
(echo client) (\_ -> hClose client) where echo :: Handle -> IO () echo client =forever
$ hGetLine client >>= hPutStrLn client
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #
Left-to-right composition of Kleisli arrows.
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) #
first :: Arrow a => a b c -> a (b, d) (c, d) #
Send the first component of the input through the argument arrow, and copy the rest unchanged to the output.
second :: Arrow a => a b c -> a (d, b) (d, c) #
A mirror image of first
.
The default definition may be overridden with a more efficient version if desired.
(***) :: Arrow a => a b c -> a b' c' -> a (b, b') (c, c') infixr 3 #
Split the input between the two argument arrows and combine their output. Note that this is in general not a functor.
The default definition may be overridden with a more efficient version if desired.
(&&&) :: Arrow a => a b c -> a b c' -> a b (c, c') infixr 3 #
Fanout: send the input to both argument arrows and combine their output.
The default definition may be overridden with a more efficient version if desired.
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Constructors
Identity | |
Fields
|
Instances
A monad supporting atomic memory transactions.
Instances
Monad STM | Since: base-4.3.0.0 |
Functor STM | Since: base-4.3.0.0 |
Applicative STM | Since: base-4.8.0.0 |
MonadPlus STM | Since: base-4.3.0.0 |
Alternative STM | Since: base-4.8.0.0 |
MonadThrow STM | |
Defined in Control.Monad.Catch | |
MonadCatch STM | |
MonadBaseControl STM STM | |
type StM STM a | |
Defined in Control.Monad.Trans.Control |
Shared memory locations that support atomic memory transactions.
Instances
Eq (TVar a) | Since: base-4.8.0.0 |
PrimUnlifted (TVar a) | Since: primitive-0.6.4.0 |
Defined in Data.Primitive.UnliftedArray |
data SomeAsyncException where #
Superclass for asynchronous exceptions.
Since: base-4.7.0.0
Constructors
SomeAsyncException :: forall e. Exception e => e -> SomeAsyncException |
Instances
Show SomeAsyncException | Since: base-4.7.0.0 |
Defined in GHC.IO.Exception Methods showsPrec :: Int -> SomeAsyncException -> ShowS # show :: SomeAsyncException -> String # showList :: [SomeAsyncException] -> ShowS # | |
Exception SomeAsyncException | Since: base-4.7.0.0 |
Defined in GHC.IO.Exception Methods toException :: SomeAsyncException -> SomeException # fromException :: SomeException -> Maybe SomeAsyncException # |
Defines the exit codes that a program can return.
Constructors
ExitSuccess | indicates successful termination; |
ExitFailure Int | indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system). |
Instances
Eq ExitCode | |
Ord ExitCode | |
Defined in GHC.IO.Exception | |
Read ExitCode | |
Show ExitCode | |
Generic ExitCode | |
NFData ExitCode | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
Exception ExitCode | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception Methods toException :: ExitCode -> SomeException # fromException :: SomeException -> Maybe ExitCode # displayException :: ExitCode -> String # | |
type Rep ExitCode | |
Defined in GHC.IO.Exception |
data BufferMode #
Three kinds of buffering are supported: line-buffering, block-buffering or no-buffering. These modes have the following effects. For output, items are written out, or flushed, from the internal buffer according to the buffer mode:
- line-buffering: the entire output buffer is flushed
whenever a newline is output, the buffer overflows,
a
hFlush
is issued, or the handle is closed. - block-buffering: the entire buffer is written out whenever it
overflows, a
hFlush
is issued, or the handle is closed. - no-buffering: output is written immediately, and never stored in the buffer.
An implementation is free to flush the buffer more frequently, but not less frequently, than specified above. The output buffer is emptied as soon as it has been written out.
Similarly, input occurs according to the buffer mode for the handle:
- line-buffering: when the buffer for the handle is not empty, the next item is obtained from the buffer; otherwise, when the buffer is empty, characters up to and including the next newline character are read into the buffer. No characters are available until the newline character is available or the buffer is full.
- block-buffering: when the buffer for the handle becomes empty, the next block of data is read into the buffer.
- no-buffering: the next input item is read and returned.
The
hLookAhead
operation implies that even a no-buffered handle may require a one-character buffer.
The default buffering mode when a handle is opened is implementation-dependent and may depend on the file system object which is attached to that handle. For most implementations, physical files will normally be block-buffered and terminals will normally be line-buffered.
Constructors
NoBuffering | buffering is disabled if possible. |
LineBuffering | line-buffering should be enabled if possible. |
BlockBuffering (Maybe Int) | block-buffering should be enabled if possible.
The size of the buffer is |
Instances
Eq BufferMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types | |
Ord BufferMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types Methods compare :: BufferMode -> BufferMode -> Ordering # (<) :: BufferMode -> BufferMode -> Bool # (<=) :: BufferMode -> BufferMode -> Bool # (>) :: BufferMode -> BufferMode -> Bool # (>=) :: BufferMode -> BufferMode -> Bool # max :: BufferMode -> BufferMode -> BufferMode # min :: BufferMode -> BufferMode -> BufferMode # | |
Read BufferMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types Methods readsPrec :: Int -> ReadS BufferMode # readList :: ReadS [BufferMode] # readPrec :: ReadPrec BufferMode # readListPrec :: ReadPrec [BufferMode] # | |
Show BufferMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types Methods showsPrec :: Int -> BufferMode -> ShowS # show :: BufferMode -> String # showList :: [BufferMode] -> ShowS # |
A mode that determines the effect of hSeek
hdl mode i
.
Instances
Enum SeekMode | Since: base-4.2.0.0 |
Eq SeekMode | Since: base-4.2.0.0 |
Ord SeekMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Device | |
Read SeekMode | Since: base-4.2.0.0 |
Show SeekMode | Since: base-4.2.0.0 |
Ix SeekMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Device |
A mutable variable in the IO
monad
Instances
NFData1 IORef | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Eq (IORef a) | ^ Pointer equality. Since: base-4.1.0.0 |
NFData (IORef a) | NOTE: Only strict in the reference and not the referenced value. Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
MonadReader (IORef State) Sh | |
data IOException #
Exceptions that occur in the IO
monad.
An IOException
records a more specific error type, a descriptive
string and maybe the handle that was used when the error was
flagged.
Instances
Eq IOException | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception | |
Show IOException | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception Methods showsPrec :: Int -> IOException -> ShowS # show :: IOException -> String # showList :: [IOException] -> ShowS # | |
Exception IOException | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception Methods toException :: IOException -> SomeException # fromException :: SomeException -> Maybe IOException # displayException :: IOException -> String # | |
Error IOException | |
Defined in Control.Monad.Trans.Error | |
Display IOException | Since: rio-0.1.0.0 |
Defined in RIO.Prelude.Display Methods display :: IOException -> Utf8Builder # |
class (Typeable e, Show e) => Exception e where #
Any type that you wish to throw or catch as an exception must be an
instance of the Exception
class. The simplest case is a new exception
type directly below the root:
data MyException = ThisException | ThatException deriving Show instance Exception MyException
The default method definitions in the Exception
class do what we need
in this case. You can now throw and catch ThisException
and
ThatException
as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) Caught ThisException
In more complicated examples, you may wish to define a whole hierarchy of exceptions:
--------------------------------------------------------------------- -- Make the root exception type for all the exceptions in a compiler data SomeCompilerException = forall e . Exception e => SomeCompilerException e instance Show SomeCompilerException where show (SomeCompilerException e) = show e instance Exception SomeCompilerException compilerExceptionToException :: Exception e => e -> SomeException compilerExceptionToException = toException . SomeCompilerException compilerExceptionFromException :: Exception e => SomeException -> Maybe e compilerExceptionFromException x = do SomeCompilerException a <- fromException x cast a --------------------------------------------------------------------- -- Make a subhierarchy for exceptions in the frontend of the compiler data SomeFrontendException = forall e . Exception e => SomeFrontendException e instance Show SomeFrontendException where show (SomeFrontendException e) = show e instance Exception SomeFrontendException where toException = compilerExceptionToException fromException = compilerExceptionFromException frontendExceptionToException :: Exception e => e -> SomeException frontendExceptionToException = toException . SomeFrontendException frontendExceptionFromException :: Exception e => SomeException -> Maybe e frontendExceptionFromException x = do SomeFrontendException a <- fromException x cast a --------------------------------------------------------------------- -- Make an exception type for a particular frontend compiler exception data MismatchedParentheses = MismatchedParentheses deriving Show instance Exception MismatchedParentheses where toException = frontendExceptionToException fromException = frontendExceptionFromException
We can now catch a MismatchedParentheses
exception as
MismatchedParentheses
, SomeFrontendException
or
SomeCompilerException
, but not other types, e.g. IOException
:
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
Minimal complete definition
Nothing
Methods
toException :: e -> SomeException #
fromException :: SomeException -> Maybe e #
displayException :: e -> String #
Render this exception value in a human-friendly manner.
Default implementation:
.show
Since: base-4.8.0.0
Instances
newtype Const a (b :: k) :: forall k. Type -> k -> Type #
The Const
functor.
Instances
Generic1 (Const a :: k -> Type) | |
ToJSON2 (Const :: Type -> Type -> Type) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Const a b -> Value # liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Const a b] -> Value # liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Const a b -> Encoding # liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Const a b] -> Encoding # | |
FromJSON2 (Const :: Type -> Type -> Type) | |
Defined in Data.Aeson.Types.FromJSON | |
Eq2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Ord2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] # | |
Show2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
NFData2 (Const :: Type -> Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable2 (Const :: Type -> Type -> Type) | |
Defined in Data.Hashable.Class | |
Functor (Const m :: Type -> Type) | Since: base-2.1 |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Foldable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const 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 # | |
Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
ToJSON a => ToJSON1 (Const a :: Type -> Type) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a0 -> Value) -> ([a0] -> Value) -> Const a a0 -> Value # liftToJSONList :: (a0 -> Value) -> ([a0] -> Value) -> [Const a a0] -> Value # liftToEncoding :: (a0 -> Encoding) -> ([a0] -> Encoding) -> Const a a0 -> Encoding # liftToEncodingList :: (a0 -> Encoding) -> ([a0] -> Encoding) -> [Const a a0] -> Encoding # | |
FromJSON a => FromJSON1 (Const a :: Type -> Type) | |
Eq a => Eq1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Ord a => Ord1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read a => Read1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Const a a0) # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Const a a0] # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Const a a0) # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Const a a0] # | |
Show a => Show1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
NFData a => NFData1 (Const a :: Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable a => Hashable1 (Const a :: Type -> Type) | |
Defined in Data.Hashable.Class | |
Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
Enum a => Enum (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods succ :: Const a b -> Const a b # pred :: Const a b -> Const a b # fromEnum :: Const a b -> Int # enumFrom :: Const a b -> [Const a b] # enumFromThen :: Const a b -> Const a b -> [Const a b] # enumFromTo :: Const a b -> Const a b -> [Const a b] # enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] # | |
Eq a => Eq (Const a b) | Since: base-4.9.0.0 |
Floating a => Floating (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const 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 # | |
Fractional a => Fractional (Const a b) | Since: base-4.9.0.0 |
Integral a => Integral (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods quot :: Const a b -> Const a b -> Const a b # rem :: Const a b -> Const a b -> Const a b # div :: Const a b -> Const a b -> Const a b # mod :: Const a b -> Const a b -> Const a b # quotRem :: Const a b -> Const a b -> (Const a b, Const a b) # divMod :: Const a b -> Const a b -> (Const a b, Const a b) # | |
(Typeable k, Data a, Typeable b) => Data (Const a b) | Since: base-4.10.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Const a b -> c (Const a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const a b) # toConstr :: Const a b -> Constr # dataTypeOf :: Const a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Const a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Const a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Const a b -> Const a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Const a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Const a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) # | |
Num a => Num (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Ord a => Ord (Const a b) | Since: base-4.9.0.0 |
Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Real a => Real (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods toRational :: Const a b -> Rational # | |
RealFloat a => RealFloat (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods floatRadix :: Const a b -> Integer # floatDigits :: Const a b -> Int # floatRange :: Const a b -> (Int, Int) # decodeFloat :: Const a b -> (Integer, Int) # encodeFloat :: Integer -> Int -> Const a b # exponent :: Const a b -> Int # significand :: Const a b -> Const a b # scaleFloat :: Int -> Const a b -> Const a b # isInfinite :: Const a b -> Bool # isDenormalized :: Const a b -> Bool # isNegativeZero :: Const a b -> Bool # | |
RealFrac a => RealFrac (Const a b) | Since: base-4.9.0.0 |
Show a => Show (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Ix a => Ix (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods range :: (Const a b, Const a b) -> [Const a b] # index :: (Const a b, Const a b) -> Const a b -> Int # unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int inRange :: (Const a b, Const a b) -> Const a b -> Bool # rangeSize :: (Const a b, Const a b) -> Int # unsafeRangeSize :: (Const a b, Const a b) -> Int | |
IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String Methods fromString :: String -> Const a b # | |
Generic (Const a b) | |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
NFData a => NFData (Const a b) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Hashable a => Hashable (Const a b) | |
Defined in Data.Hashable.Class | |
ToJSON a => ToJSON (Const a b) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (Const a b) | |
Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Bits a => Bits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods (.&.) :: Const a b -> Const a b -> Const a b # (.|.) :: Const a b -> Const a b -> Const a b # xor :: Const a b -> Const a b -> Const a b # complement :: Const a b -> Const a b # shift :: Const a b -> Int -> Const a b # rotate :: Const a b -> Int -> Const a b # setBit :: Const a b -> Int -> Const a b # clearBit :: Const a b -> Int -> Const a b # complementBit :: Const a b -> Int -> Const a b # testBit :: Const a b -> Int -> Bool # bitSizeMaybe :: Const a b -> Maybe Int # isSigned :: Const a b -> Bool # shiftL :: Const a b -> Int -> Const a b # unsafeShiftL :: Const a b -> Int -> Const a b # shiftR :: Const a b -> Int -> Const a b # unsafeShiftR :: Const a b -> Int -> Const a b # rotateL :: Const a b -> Int -> Const a b # | |
FiniteBits a => FiniteBits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods finiteBitSize :: Const a b -> Int # countLeadingZeros :: Const a b -> Int # countTrailingZeros :: Const a b -> Int # | |
GMonoid a => GMonoid (Const a b) | |
MonoFunctor (Const m a) | |
MonoFoldable (Const m a) | |
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m0 => (Element (Const m a) -> m0) -> Const m a -> m0 # ofoldr :: (Element (Const m a) -> b -> b) -> b -> Const m a -> b # ofoldl' :: (a0 -> Element (Const m a) -> a0) -> a0 -> Const m a -> a0 # otoList :: Const m a -> [Element (Const m a)] # oall :: (Element (Const m a) -> Bool) -> Const m a -> Bool # oany :: (Element (Const m a) -> Bool) -> Const m a -> Bool # olength64 :: Const m a -> Int64 # ocompareLength :: Integral i => Const m a -> i -> Ordering # otraverse_ :: Applicative f => (Element (Const m a) -> f b) -> Const m a -> f () # ofor_ :: Applicative f => Const m a -> (Element (Const m a) -> f b) -> f () # omapM_ :: Applicative m0 => (Element (Const m a) -> m0 ()) -> Const m a -> m0 () # oforM_ :: Applicative m0 => Const m a -> (Element (Const m a) -> m0 ()) -> m0 () # ofoldlM :: Monad m0 => (a0 -> Element (Const m a) -> m0 a0) -> a0 -> Const m a -> m0 a0 # ofoldMap1Ex :: Semigroup m0 => (Element (Const m a) -> m0) -> Const m a -> m0 # ofoldr1Ex :: (Element (Const m a) -> Element (Const m a) -> Element (Const m a)) -> Const m a -> Element (Const m a) # ofoldl1Ex' :: (Element (Const m a) -> Element (Const m a) -> Element (Const m a)) -> Const m a -> Element (Const m a) # headEx :: Const m a -> Element (Const m a) # lastEx :: Const m a -> Element (Const m a) # unsafeHead :: Const m a -> Element (Const m a) # unsafeLast :: Const m a -> Element (Const m a) # maximumByEx :: (Element (Const m a) -> Element (Const m a) -> Ordering) -> Const m a -> Element (Const m a) # minimumByEx :: (Element (Const m a) -> Element (Const m a) -> Ordering) -> Const m a -> Element (Const m a) # | |
MonoTraversable (Const m a) | |
Monoid m => MonoPointed (Const m a) | |
type Rep1 (Const a :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
type Rep (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
type Element (Const m a) | |
Defined in Data.MonoTraversable |
asum :: (Foldable t, Alternative f) => t (f a) -> f a #
sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () #
Evaluate each action in the structure from left to right, and
ignore the results. For a version that doesn't ignore the results
see sequenceA
.
Maybe monoid returning the leftmost non-Nothing value.
is isomorphic to First
a
, but precedes it
historically.Alt
Maybe
a
>>>
getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))
Just "hello"
Use of this type is discouraged. Note the following equivalence:
Data.Monoid.First x === Maybe (Data.Semigroup.First x)
In addition to being equivalent in the structural sense, the two
also have Monoid
instances that behave the same. This type will
be marked deprecated in GHC 8.8, and removed in GHC 8.10.
Users are advised to use the variant from Data.Semigroup and wrap
it in Maybe
.
Instances
Monad First | Since: base-4.8.0.0 |
Functor First | Since: base-4.8.0.0 |
MonadFix First | Since: base-4.8.0.0 |
Defined in Control.Monad.Fix | |
Applicative First | Since: base-4.8.0.0 |
Foldable First | Since: base-4.8.0.0 |
Defined in Data.Foldable 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 # | |
Traversable First | Since: base-4.8.0.0 |
ToJSON1 First | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> First a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [First a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> First a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [First a] -> Encoding # | |
FromJSON1 First | |
NFData1 First | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (First a) | Since: base-2.1 |
Data a => Data (First a) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> First a -> c (First a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (First a) # toConstr :: First a -> Constr # dataTypeOf :: First a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (First a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (First a)) # gmapT :: (forall b. Data b => b -> b) -> First a -> First a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQ :: (forall d. Data d => d -> u) -> First a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> First a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # | |
Ord a => Ord (First a) | Since: base-2.1 |
Read a => Read (First a) | Since: base-2.1 |
Show a => Show (First a) | Since: base-2.1 |
Generic (First a) | |
Semigroup (First a) | Since: base-4.9.0.0 |
Monoid (First a) | Since: base-2.1 |
NFData a => NFData (First a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
ToJSON a => ToJSON (First a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (First a) | |
GMonoid (First a) | |
ToHttpApiData a => ToHttpApiData (First a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: First a -> Text # toEncodedUrlPiece :: First a -> Builder # toHeader :: First a -> ByteString # toQueryParam :: First a -> Text # | |
FromHttpApiData a => FromHttpApiData (First a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (First a) # parseHeader :: ByteString -> Either Text (First a) # | |
Generic1 First | |
type Rep (First a) | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
type Rep1 First | Since: base-4.7.0.0 |
Defined in Data.Monoid |
The monoid of endomorphisms under composition.
>>>
let computation = Endo ("Hello, " ++) <> Endo (++ "!")
>>>
appEndo computation "Haskell"
"Hello, Haskell!"
Monoid under addition.
>>>
getSum (Sum 1 <> Sum 2 <> mempty)
3
Instances
Monad Sum | Since: base-4.8.0.0 |
Functor Sum | Since: base-4.8.0.0 |
MonadFix Sum | Since: base-4.8.0.0 |
Defined in Control.Monad.Fix | |
Applicative Sum | Since: base-4.8.0.0 |
Foldable Sum | Since: base-4.8.0.0 |
Defined in Data.Foldable 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 # | |
Traversable Sum | Since: base-4.8.0.0 |
NFData1 Sum | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Bounded a => Bounded (Sum a) | Since: base-2.1 |
Eq a => Eq (Sum a) | Since: base-2.1 |
Data a => Data (Sum a) | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum a -> c (Sum a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum a) # dataTypeOf :: Sum a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum a)) # gmapT :: (forall b. Data b => b -> b) -> Sum a -> Sum a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r # gmapQ :: (forall d. Data d => d -> u) -> Sum a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) # | |
Num a => Num (Sum a) | Since: base-4.7.0.0 |
Ord a => Ord (Sum a) | Since: base-2.1 |
Read a => Read (Sum a) | Since: base-2.1 |
Show a => Show (Sum a) | Since: base-2.1 |
Generic (Sum a) | |
Num a => Semigroup (Sum a) | Since: base-4.9.0.0 |
Num a => Monoid (Sum a) | Since: base-2.1 |
NFData a => NFData (Sum a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Num a => GMonoid (Sum a) | |
ToHttpApiData a => ToHttpApiData (Sum a) | |
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: Sum a -> Text # toEncodedUrlPiece :: Sum a -> Builder # toHeader :: Sum a -> ByteString # toQueryParam :: Sum a -> Text # | |
FromHttpApiData a => FromHttpApiData (Sum a) | |
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text (Sum a) # parseHeader :: ByteString -> Either Text (Sum a) # | |
Generic1 Sum | |
type Rep (Sum a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
type Rep1 Sum | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
readMaybe :: Read a => String -> Maybe a #
Parse a string using the Read
instance.
Succeeds if there is exactly one valid result.
>>>
readMaybe "123" :: Maybe Int
Just 123
>>>
readMaybe "hello" :: Maybe Int
Nothing
Since: base-4.6.0.0
isRight :: Either a b -> Bool #
Return True
if the given value is a Right
-value, False
otherwise.
Examples
Basic usage:
>>>
isRight (Left "foo")
False>>>
isRight (Right 3)
True
Assuming a Left
value signifies some sort of error, we can use
isRight
to write a very simple reporting function that only
outputs "SUCCESS" when a computation has succeeded.
This example shows how isRight
might be used to avoid pattern
matching when one does not care about the value contained in the
constructor:
>>>
import Control.Monad ( when )
>>>
let report e = when (isRight e) $ putStrLn "SUCCESS"
>>>
report (Left "parse error")
>>>
report (Right 1)
SUCCESS
Since: base-4.7.0.0
isLeft :: Either a b -> Bool #
Return True
if the given value is a Left
-value, False
otherwise.
Examples
Basic usage:
>>>
isLeft (Left "foo")
True>>>
isLeft (Right 3)
False
Assuming a Left
value signifies some sort of error, we can use
isLeft
to write a very simple error-reporting function that does
absolutely nothing in the case of success, and outputs "ERROR" if
any error occurred.
This example shows how isLeft
might be used to avoid pattern
matching when one does not care about the value contained in the
constructor:
>>>
import Control.Monad ( when )
>>>
let report e = when (isLeft e) $ putStrLn "ERROR"
>>>
report (Right 1)
>>>
report (Left "parse error")
ERROR
Since: base-4.7.0.0
partitionEithers :: [Either a b] -> ([a], [b]) #
Partitions a list of Either
into two lists.
All the Left
elements are extracted, in order, to the first
component of the output. Similarly the Right
elements are extracted
to the second component of the output.
Examples
Basic usage:
>>>
let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>>
partitionEithers list
(["foo","bar","baz"],[3,7])
The pair returned by
should be the same
pair as partitionEithers
x(
:lefts
x, rights
x)
>>>
let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>>
partitionEithers list == (lefts list, rights list)
True
data Proxy (t :: k) :: forall k. k -> Type #
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a'undefined :: a'
idiom.
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Constructors
Proxy |
Instances
Generic1 (Proxy :: k -> Type) | |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable 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 # | |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
ToJSON1 (Proxy :: Type -> Type) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Proxy a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Proxy a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Proxy a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Proxy a] -> Encoding # | |
FromJSON1 (Proxy :: Type -> Type) | |
Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
NFData1 (Proxy :: Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable1 (Proxy :: Type -> Type) | |
Defined in Data.Hashable.Class | |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Data t => Data (Proxy t) | Since: base-4.7.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) # toConstr :: Proxy t -> Constr # dataTypeOf :: Proxy t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) # gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r # gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # | |
Ord (Proxy s) | Since: base-4.7.0.0 |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
Generic (Proxy t) | |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Monoid (Proxy s) | Since: base-4.7.0.0 |
NFData (Proxy a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Hashable (Proxy a) | |
Defined in Data.Hashable.Class | |
ToJSON (Proxy a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON (Proxy a) | |
GMonoid (Proxy s) | |
type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
type Rep (Proxy t) | Since: base-4.6.0.0 |
See openFile
Constructors
ReadMode | |
WriteMode | |
AppendMode | |
ReadWriteMode |
The member functions of this class facilitate writing values of primitive types to raw memory (which may have been allocated with the above mentioned routines) and reading values from blocks of raw memory. The class, furthermore, includes support for computing the storage requirements and alignment restrictions of storable types.
Memory addresses are represented as values of type
, for some
Ptr
aa
which is an instance of class Storable
. The type argument to
Ptr
helps provide some valuable type safety in FFI code (you can't
mix pointers of different types without an explicit cast), while
helping the Haskell type system figure out which marshalling method is
needed for a given pointer.
All marshalling between Haskell and a foreign language ultimately
boils down to translating Haskell data structures into the binary
representation of a corresponding data structure of the foreign
language and vice versa. To code this marshalling in Haskell, it is
necessary to manipulate primitive data types stored in unstructured
memory blocks. The class Storable
facilitates this manipulation on
all types for which it is instantiated, which are the standard basic
types of Haskell, the fixed size Int
types (Int8
, Int16
,
Int32
, Int64
), the fixed size Word
types (Word8
, Word16
,
Word32
, Word64
), StablePtr
, all types from Foreign.C.Types,
as well as Ptr
.
Minimal complete definition
sizeOf, alignment, (peek | peekElemOff | peekByteOff), (poke | pokeElemOff | pokeByteOff)
Instances
Case analysis for the Bool
type.
evaluates to bool
x y px
when p
is False
, and evaluates to y
when p
is True
.
This is equivalent to if p then y else x
; that is, one can
think of it as an if-then-else construct with its arguments
reordered.
Examples
Basic usage:
>>>
bool "foo" "bar" True
"bar">>>
bool "foo" "bar" False
"foo"
Confirm that
and bool
x y pif p then y else x
are
equivalent:
>>>
let p = True; x = "bar"; y = "foo"
>>>
bool x y p == if p then y else x
True>>>
let p = False
>>>
bool x y p == if p then y else x
True
Since: base-4.7.0.0
is the least fixed point of the function fix
ff
,
i.e. the least defined x
such that f x = x
.
For example, we can write the factorial function using direct recursion as
>>>
let fac n = if n <= 1 then 1 else n * fac (n-1) in fac 5
120
This uses the fact that Haskell’s let
introduces recursive bindings. We can
rewrite this definition using fix
,
>>>
fix (\rec n -> if n <= 1 then 1 else n * rec (n-1)) 5
120
Instead of making a recursive call, we introduce a dummy parameter rec
;
when used within fix
, this parameter then refers to fix'
argument, hence
the recursion is reintroduced.
($>) :: Functor f => f a -> b -> f b infixl 4 #
Flipped version of <$
.
Examples
Replace the contents of a
with a constant Maybe
Int
String
:
>>>
Nothing $> "foo"
Nothing>>>
Just 90210 $> "foo"
Just "foo"
Replace the contents of an
with a constant
Either
Int
Int
String
, resulting in an
:Either
Int
String
>>>
Left 8675309 $> "foo"
Left 8675309>>>
Right 8675309 $> "foo"
Right "foo"
Replace each element of a list with a constant String
:
>>>
[1,2,3] $> "foo"
["foo","foo","foo"]
Replace the second element of a pair with a constant String
:
>>>
(1,2) $> "foo"
(1,"foo")
Since: base-4.7.0.0
An MVar
(pronounced "em-var") is a synchronising variable, used
for communication between concurrent threads. It can be thought of
as a box, which may be empty or full.
Instances
NFData1 MVar | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Eq (MVar a) | Since: base-4.1.0.0 |
NFData (MVar a) | NOTE: Only strict in the reference and not the referenced value. Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
PrimUnlifted (MVar a) | Since: primitive-0.6.4.0 |
Defined in Data.Primitive.UnliftedArray |
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d #
Lift a ternary function to actions.
liftA :: Applicative f => (a -> b) -> f a -> f b #
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack
is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.9.0.0
data SomeException where #
The SomeException
type is the root of the exception type hierarchy.
When an exception of type e
is thrown, behind the scenes it is
encapsulated in a SomeException
.
Constructors
SomeException :: forall e. Exception e => e -> SomeException |
Instances
Show SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type Methods showsPrec :: Int -> SomeException -> ShowS # show :: SomeException -> String # showList :: [SomeException] -> ShowS # | |
Exception SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type Methods toException :: SomeException -> SomeException # fromException :: SomeException -> Maybe SomeException # displayException :: SomeException -> String # | |
Display SomeException | Since: rio-0.1.0.0 |
Defined in RIO.Prelude.Display Methods display :: SomeException -> Utf8Builder # |
fromShort :: ShortByteString -> ByteString #
O(n). Convert a ShortByteString
into a ByteString
.
toShort :: ByteString -> ShortByteString #
O(n). Convert a ByteString
into a ShortByteString
.
This makes a copy, so does not retain the input string.
newtype ReaderT r (m :: k -> Type) (a :: k) :: forall k. Type -> (k -> Type) -> k -> Type #
The reader monad transformer, which adds a read-only environment to the given monad.
The return
function ignores the environment, while >>=
passes
the inherited environment to both subcomputations.
Constructors
ReaderT | |
Fields
|
Instances
runConduit :: Monad m => ConduitT () Void m r -> m r #
Run a pipeline until processing completes.
Since 1.2.1
Combine two Conduit
s together into a new Conduit
(aka fuse
).
Output from the upstream (left) conduit will be fed into the
downstream (right) conduit. Processing will terminate when
downstream (right) returns.
Leftover data returned from the right Conduit
will be discarded.
Equivalent to fuse
and =$=
, however the latter is deprecated and will
be removed in a future version.
Note that, while this operator looks like categorical composition (from Control.Category), there are a few reasons it's different:
- The position of the type parameters to
ConduitT
do not match. We would need to changeConduitT i o m r
toConduitT r m i o
, which would preclude aMonad
orMonadTrans
instance. - The result value from upstream and downstream are allowed to
differ between upstream and downstream. In other words, we would
need the type signature here to look like
ConduitT a b m r -> ConduitT b c m r -> ConduitT a c m r
. - Due to leftovers, we do not have a left identity in Conduit. This
can be achieved with the underlying
Pipe
datatype, but this is not generally recommended. See https://stackoverflow.com/a/15263700.
Since: conduit-1.2.8
class MonadIO m => MonadUnliftIO (m :: Type -> Type) where #
Monads which allow their actions to be run in IO
.
While MonadIO
allows an IO
action to be lifted into another
monad, this class captures the opposite concept: allowing you to
capture the monadic context. Note that, in order to meet the laws
given below, the intuition is that a monad must have no monadic
state, but may have monadic context. This essentially limits
MonadUnliftIO
to ReaderT
and IdentityT
transformers on top of
IO
.
Laws. For any value u
returned by askUnliftIO
, it must meet the
monad transformer laws as reformulated for MonadUnliftIO
:
unliftIO u . return = return
unliftIO u (m >>= f) = unliftIO u m >>= unliftIO u . f
The third is a currently nameless law which ensures that the current context is preserved.
askUnliftIO >>= (u -> liftIO (unliftIO u m)) = m
If you have a name for this, please submit it in a pull request for great glory.
Since: unliftio-core-0.1.0.0
Minimal complete definition
Methods
askUnliftIO :: m (UnliftIO m) #
Capture the current monadic context, providing the ability to
run monadic actions in IO
.
See UnliftIO
for an explanation of why we need a helper
datatype here.
Since: unliftio-core-0.1.0.0
withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b #
Convenience function for capturing the monadic context and running an IO
action with a runner function. The runner function is used to run a monadic
action m
in IO
.
Since: unliftio-core-0.1.0.0
Instances
MonadUnliftIO IO | |
Defined in Control.Monad.IO.Unlift | |
MonadUnliftIO m => MonadUnliftIO (ResourceT m) | Since: resourcet-1.1.10 |
Defined in Control.Monad.Trans.Resource.Internal | |
MonadUnliftIO m => MonadUnliftIO (NoLoggingT m) | Since: monad-logger-0.3.26 |
Defined in Control.Monad.Logger Methods askUnliftIO :: NoLoggingT m (UnliftIO (NoLoggingT m)) # withRunInIO :: ((forall a. NoLoggingT m a -> IO a) -> IO b) -> NoLoggingT m b # | |
MonadUnliftIO m => MonadUnliftIO (LoggingT m) | Since: monad-logger-0.3.26 |
Defined in Control.Monad.Logger | |
MonadUnliftIO (RIO env) | |
Defined in RIO.Prelude.RIO | |
MonadUnliftIO m => MonadUnliftIO (IdentityT m) | |
Defined in Control.Monad.IO.Unlift | |
MonadUnliftIO m => MonadUnliftIO (ReaderT r m) | |
Defined in Control.Monad.IO.Unlift |
class Monad m => PrimMonad (m :: Type -> Type) where #
Class of monads which can perform primitive state-transformer actions
Methods
primitive :: (State# (PrimState m) -> (#State# (PrimState m), a#)) -> m a #
Execute a primitive operation
Instances
PrimMonad IO | |
PrimMonad Peek | |
PrimMonad (ST s) | |
PrimMonad m => PrimMonad (MaybeT m) | |
PrimMonad m => PrimMonad (ResourceT m) | |
PrimMonad m => PrimMonad (ListT m) | |
PrimMonad (RIO env) | |
PrimMonad m => PrimMonad (IdentityT m) | |
(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) | |
(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) | |
PrimMonad m => PrimMonad (StateT s m) | |
PrimMonad m => PrimMonad (StateT s m) | |
PrimMonad m => PrimMonad (ExceptT e m) | |
(Error e, PrimMonad m) => PrimMonad (ErrorT e m) | |
(Monoid w, PrimMonad m) => PrimMonad (AccumT w m) | Since: primitive-0.6.3.0 |
PrimMonad m => PrimMonad (SelectT r m) | |
PrimMonad m => PrimMonad (ReaderT r m) | |
PrimMonad m => PrimMonad (ConduitT i o m) | |
PrimMonad m => PrimMonad (ContT r m) | Since: primitive-0.6.3.0 |
(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) | |
(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) | |
PrimMonad m => PrimMonad (Pipe l i o u m) | |
class MonadTrans (t :: (Type -> Type) -> Type -> Type) where #
The class of monad transformers. Instances should satisfy the
following laws, which state that lift
is a monad transformation:
Methods
lift :: Monad m => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
Instances
A map of integers to values a
.
Instances
A set of integers.
Instances
A set of values a
.
Instances
Foldable Set | |
Defined in Data.Set.Internal 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 # | |
ToJSON1 Set | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Set a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Set a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Set a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Set a] -> Encoding # | |
Eq1 Set | Since: containers-0.5.9 |
Ord1 Set | Since: containers-0.5.9 |
Defined in Data.Set.Internal | |
Show1 Set | Since: containers-0.5.9 |
Ord a => IsList (Set a) | Since: containers-0.5.6.2 |
Eq a => Eq (Set a) | |
(Data a, Ord a) => Data (Set a) | |
Defined in Data.Set.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) # dataTypeOf :: Set a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) # gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # | |
Ord a => Ord (Set a) | |
(Read a, Ord a) => Read (Set a) | |
Show a => Show (Set a) | |
Ord a => Semigroup (Set a) | Since: containers-0.5.7 |
Ord a => Monoid (Set a) | |
NFData a => NFData (Set a) | |
Defined in Data.Set.Internal | |
ToJSON a => ToJSON (Set a) | |
Defined in Data.Aeson.Types.ToJSON | |
(Ord a, FromJSON a) => FromJSON (Set a) | |
Ord element => SetContainer (Set element) | |
Defined in Data.Containers Associated Types type ContainerKey (Set element) :: Type # Methods member :: ContainerKey (Set element) -> Set element -> Bool # notMember :: ContainerKey (Set element) -> Set element -> Bool # union :: Set element -> Set element -> Set element # unions :: (MonoFoldable mono, Element mono ~ Set element) => mono -> Set element # difference :: Set element -> Set element -> Set element # intersection :: Set element -> Set element -> Set element # keys :: Set element -> [ContainerKey (Set element)] # | |
Ord element => IsSet (Set element) | |
Ord e => MonoFoldable (Set e) | |
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element (Set e) -> m) -> Set e -> m # ofoldr :: (Element (Set e) -> b -> b) -> b -> Set e -> b # ofoldl' :: (a -> Element (Set e) -> a) -> a -> Set e -> a # otoList :: Set e -> [Element (Set e)] # oall :: (Element (Set e) -> Bool) -> Set e -> Bool # oany :: (Element (Set e) -> Bool) -> Set e -> Bool # ocompareLength :: Integral i => Set e -> i -> Ordering # otraverse_ :: Applicative f => (Element (Set e) -> f b) -> Set e -> f () # ofor_ :: Applicative f => Set e -> (Element (Set e) -> f b) -> f () # omapM_ :: Applicative m => (Element (Set e) -> m ()) -> Set e -> m () # oforM_ :: Applicative m => Set e -> (Element (Set e) -> m ()) -> m () # ofoldlM :: Monad m => (a -> Element (Set e) -> m a) -> a -> Set e -> m a # ofoldMap1Ex :: Semigroup m => (Element (Set e) -> m) -> Set e -> m # ofoldr1Ex :: (Element (Set e) -> Element (Set e) -> Element (Set e)) -> Set e -> Element (Set e) # ofoldl1Ex' :: (Element (Set e) -> Element (Set e) -> Element (Set e)) -> Set e -> Element (Set e) # headEx :: Set e -> Element (Set e) # lastEx :: Set e -> Element (Set e) # unsafeHead :: Set e -> Element (Set e) # unsafeLast :: Set e -> Element (Set e) # maximumByEx :: (Element (Set e) -> Element (Set e) -> Ordering) -> Set e -> Element (Set e) # minimumByEx :: (Element (Set e) -> Element (Set e) -> Ordering) -> Set e -> Element (Set e) # | |
MonoPointed (Set a) | |
Ord v => GrowingAppend (Set v) | |
Defined in Data.MonoTraversable | |
ToMustache ω => ToMustache (Set ω) | |
Defined in Text.Mustache.Internal.Types | |
(Ord a, PersistFieldSql a) => PersistFieldSql (Set a) | |
(Ord a, PersistField a) => PersistField (Set a) | |
Defined in Database.Persist.Class.PersistField Methods toPersistValue :: Set a -> PersistValue # fromPersistValue :: PersistValue -> Either Text (Set a) # | |
type Item (Set a) | |
Defined in Data.Set.Internal | |
type ContainerKey (Set element) | |
Defined in Data.Containers | |
type Element (Set e) | |
Defined in Data.MonoTraversable |
a variant of deepseq
that is useful in some circumstances:
force x = x `deepseq` x
force x
fully evaluates x
, and then returns it. Note that
force x
only performs evaluation when the value of force x
itself is demanded, so essentially it turns shallow evaluation into
deep evaluation.
force
can be conveniently used in combination with ViewPatterns
:
{-# LANGUAGE BangPatterns, ViewPatterns #-} import Control.DeepSeq someFun :: ComplexData -> SomeResult someFun (force -> !arg) = {- 'arg' will be fully evaluated -}
Another useful application is to combine force
with
evaluate
in order to force deep evaluation
relative to other IO
operations:
import Control.Exception (evaluate) import Control.DeepSeq main = do result <- evaluate $ force $ pureComputation {- 'result' will be fully evaluated at this point -} return ()
Finally, here's an exception safe variant of the readFile'
example:
readFile' :: FilePath -> IO String readFile' fn = bracket (openFile fn ReadMode) hClose $ \h -> evaluate . force =<< hGetContents h
Since: deepseq-1.2.0.0
($!!) :: NFData a => (a -> b) -> a -> b infixr 0 #
the deep analogue of $!
. In the expression f $!! x
, x
is
fully evaluated before the function f
is applied to it.
Since: deepseq-1.2.0.0
lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b #
lens
creates a Lens
from a getter and a setter. The resulting lens isn't the most effective one (because of having to traverse the structure twice when modifying), but it shouldn't matter much.
A (partial) lens for list indexing:
ix :: Int ->Lens'
[a] a ix i =lens
(!!
i) -- getter (\s b -> take i s ++ b : drop (i+1) s) -- setter
Usage:
>>> [1..9]^.
ix 3 4 >>> [1..9] & ix 3%~
negate [1,2,3,-4,5,6,7,8,9]
When getting, the setter is completely unused; when setting, the getter is unused. Both are used only when the value is being modified. For instance, here we define a lens for the 1st element of a list, but instead of a legitimate getter we use undefined
. Then we use the resulting lens for setting and it works, which proves that the getter wasn't used:
>>>
[1,2,3] & lens undefined (\s b -> b : tail s) .~ 10
[10,2,3]
to :: (s -> a) -> SimpleGetter s a #
to
creates a getter from any function:
a^.
to
f = f a
It's most useful in chains, because it lets you mix lenses and ordinary functions. Suppose you have a record which comes from some third-party library and doesn't have any lens accessors. You want to do something like this:
value ^. _1 . field . at 2
However, field
isn't a getter, and you have to do this instead:
field (value ^. _1) ^. at 2
but now value
is in the middle and it's hard to read the resulting code. A variant with to
is prettier and more readable:
value ^. _1 . to field . at 2
(^.) :: s -> Getting a s a -> a infixl 8 #
(^.
) applies a getter to a value; in other words, it gets a value out of a structure using a getter (which can be a lens, traversal, fold, etc.).
Getting 1st field of a tuple:
(^.
_1
) :: (a, b) -> a (^.
_1
) =fst
When (^.
) is used with a traversal, it combines all results using the Monoid
instance for the resulting type. For instance, for lists it would be simple concatenation:
>>>
("str","ing") ^. each
"string"
The reason for this is that traversals use Applicative
, and the Applicative
instance for Const
uses monoid concatenation to combine “effects” of Const
.
A non-operator version of (^.
) is called view
, and it's a bit more general than (^.
) (it works in MonadReader
). If you need the general version, you can get it from microlens-mtl; otherwise there's view
available in Lens.Micro.Extras.
over :: ASetter s t a b -> (a -> b) -> s -> t #
Getting fmap
in a roundabout way:
over
mapped
::Functor
f => (a -> b) -> f a -> f bover
mapped
=fmap
Applying a function to both components of a pair:
over
both
:: (a -> b) -> (a, a) -> (b, b)over
both
= \f t -> (f (fst t), f (snd t))
Using
as a replacement for over
_2
second
:
>>>
over _2 show (10,20)
(10,"20")
type ASetter s t a b = (a -> Identity b) -> s -> Identity t #
ASetter s t a b
is something that turns a function modifying a value into a function modifying a structure. If you ignore Identity
(as Identity a
is the same thing as a
), the type is:
type ASetter s t a b = (a -> b) -> s -> t
The reason Identity
is used here is for ASetter
to be composable with other types, such as Lens
.
Technically, if you're writing a library, you shouldn't use this type for setters you are exporting from your library; the right type to use is Setter
, but it is not provided by this package (because then it'd have to depend on distributive). It's completely alright, however, to export functions which take an ASetter
as an argument.
type SimpleGetter s a = forall r. Getting r s a #
A SimpleGetter s a
extracts a
from s
; so, it's the same thing as (s -> a)
, but you can use it in lens chains because its type looks like this:
type SimpleGetter s a = forall r. (a -> Const r a) -> s -> Const r s
Since Const r
is a functor, SimpleGetter
has the same shape as other lens types and can be composed with them. To get (s -> a)
out of a SimpleGetter
, choose r ~ a
and feed Const :: a -> Const a a
to the getter:
-- the actual signature is more permissive: --view
::Getting
a s a -> s -> aview
::SimpleGetter
s a -> s -> aview
getter =getConst
. getterConst
The actual Getter
from lens is more general:
type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s
I'm not currently aware of any functions that take lens's Getter
but won't accept SimpleGetter
, but you should try to avoid exporting SimpleGetter
s anyway to minimise confusion. Alternatively, look at microlens-contra, which provides a fully lens-compatible Getter
.
Lens users: you can convert a SimpleGetter
to Getter
by applying to . view
to it.
type Getting r s a = (a -> Const r a) -> s -> Const r s #
Functions that operate on getters and folds – such as (^.
), (^..
), (^?
) – use Getter r s a
(with different values of r
) to describe what kind of result they need. For instance, (^.
) needs the getter to be able to return a single value, and so it accepts a getter of type Getting a s a
. (^..
) wants the getter to gather values together, so it uses Getting (Endo [a]) s a
(it could've used Getting [a] s a
instead, but it's faster with Endo
). The choice of r
depends on what you want to do with elements you're extracting from s
.
type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t #
Lens s t a b
is the lowest common denominator of a setter and a getter, something that has the power of both; it has a Functor
constraint, and since both Const
and Identity
are functors, it can be used whenever a getter or a setter is needed.
a
is the type of the value inside of structureb
is the type of the replaced values
is the type of the whole structuret
is the type of the structure after replacinga
in it withb
type Lens' s a = Lens s s a a #
This is a type alias for monomorphic lenses which don't change the type of the container (or of the value inside).
Arguments
:: MonadReader r m | |
=> (r -> a) | The selector function to apply to the environment. |
-> m a |
Retrieves a function of the current environment.
class Monad m => MonadReader r (m :: Type -> Type) | m -> r where #
See examples in Control.Monad.Reader.
Note, the partially applied function type (->) r
is a simple reader monad.
See the instance
declaration below.
Methods
Retrieves the monad environment.
Arguments
:: (r -> r) | The function to modify the environment. |
-> m a |
|
-> m a |
Executes a computation in a modified environment.
Instances
type Reader r = ReaderT r Identity #
The parameterizable reader monad.
Computations are functions of a shared environment.
The return
function ignores the environment, while >>=
passes
the inherited environment to both subcomputations.
Arguments
:: Reader r a | A |
-> r | An initial environment. |
-> a |
Runs a Reader
and extracts the final value from it.
(The inverse of reader
.)
An absolute path.
A relative path; one without a root. Note that a ..
path component to
represent the parent directory is not allowed by this library.
A file path.
Instances
FromJSON (Path Abs File) | |
FromJSON (Path Rel File) | |
AnyPath (Path b File) | |
Defined in Path.IO Methods canonicalizePath :: MonadIO m => Path b File -> m (AbsPath (Path b File)) # makeAbsolute :: MonadIO m => Path b File -> m (AbsPath (Path b File)) # makeRelative :: MonadThrow m => Path Abs Dir -> Path b File -> m (RelPath (Path b File)) # makeRelativeToCurrentDir :: MonadIO m => Path b File -> m (RelPath (Path b File)) # | |
Display (Path b File) Source # | |
type RelPath (Path b File) | |
type AbsPath (Path b File) | |
type Ann (Path b File) Source # | |
Defined in Stack.PrettyPrint |
A directory path.
Instances
FromJSON (Path Abs Dir) | |
FromJSON (Path Rel Dir) | |
AnyPath (Path b Dir) | |
Defined in Path.IO Methods canonicalizePath :: MonadIO m => Path b Dir -> m (AbsPath (Path b Dir)) # makeAbsolute :: MonadIO m => Path b Dir -> m (AbsPath (Path b Dir)) # makeRelative :: MonadThrow m => Path Abs Dir -> Path b Dir -> m (RelPath (Path b Dir)) # makeRelativeToCurrentDir :: MonadIO m => Path b Dir -> m (RelPath (Path b Dir)) # | |
Display (Path b Dir) Source # | |
type RelPath (Path b Dir) | |
type AbsPath (Path b Dir) | |
type Ann (Path b Dir) Source # | |
Defined in Stack.PrettyPrint |
toFilePath :: Path b t -> FilePath #
Convert to a FilePath
type.
All directories have a trailing slash, so if you want no trailing
slash, you can use dropTrailingPathSeparator
from
the filepath package.
Path of some base and type.
The type variables are:
b
— base, the base location of the path; absolute or relative.t
— type, whether file or directory.
Internally is a string. The string can be of two formats only:
- File format:
file.txt
,foo/bar.txt
,/foo/bar.txt
- Directory format:
foo/
,/foo/bar/
All directories end in a trailing separator. There are no duplicate
path separators //
, no ..
, no ./
, no ~/
, etc.
Instances
getChanContents :: MonadIO m => Chan a -> m [a] #
Lifted getChanContents
.
Since: unliftio-0.1.0.0
writeList2Chan :: MonadIO m => Chan a -> [a] -> m () #
Lifted writeList2Chan
.
Since: unliftio-0.1.0.0
data StringException #
Exception type thrown by throwString
.
Note that the second field of the data constructor depends on GHC/base version. For base 4.9 and GHC 8.0 and later, the second field is a call stack. Previous versions of GHC and base do not support call stacks, and the field is simply unit (provided to make pattern matching across GHC versions easier).
Since: unliftio-0.1.0.0
Constructors
StringException String CallStack |
Instances
Show StringException | Since: unliftio-0.1.0.0 |
Defined in UnliftIO.Exception Methods showsPrec :: Int -> StringException -> ShowS # show :: StringException -> String # showList :: [StringException] -> ShowS # | |
Exception StringException | Since: unliftio-0.1.0.0 |
Defined in UnliftIO.Exception Methods toException :: StringException -> SomeException # |
data AsyncExceptionWrapper where #
Wrap up a synchronous exception to be treated as an asynchronous exception.
This is intended to be created via toAsyncException
.
Since: unliftio-0.1.0.0
Constructors
AsyncExceptionWrapper :: forall e. Exception e => e -> AsyncExceptionWrapper |
Instances
Show AsyncExceptionWrapper | Since: unliftio-0.1.0.0 |
Defined in UnliftIO.Exception Methods showsPrec :: Int -> AsyncExceptionWrapper -> ShowS # show :: AsyncExceptionWrapper -> String # showList :: [AsyncExceptionWrapper] -> ShowS # | |
Exception AsyncExceptionWrapper | Since: unliftio-0.1.0.0 |
Defined in UnliftIO.Exception |
data SyncExceptionWrapper where #
Wrap up an asynchronous exception to be treated as a synchronous exception.
This is intended to be created via toSyncException
.
Since: unliftio-0.1.0.0
Constructors
SyncExceptionWrapper :: forall e. Exception e => e -> SyncExceptionWrapper |
Instances
Show SyncExceptionWrapper | Since: unliftio-0.1.0.0 |
Defined in UnliftIO.Exception Methods showsPrec :: Int -> SyncExceptionWrapper -> ShowS # show :: SyncExceptionWrapper -> String # showList :: [SyncExceptionWrapper] -> ShowS # | |
Exception SyncExceptionWrapper | Since: unliftio-0.1.0.0 |
Defined in UnliftIO.Exception Methods toException :: SyncExceptionWrapper -> SomeException # fromException :: SomeException -> Maybe SyncExceptionWrapper # |
catch :: (MonadUnliftIO m, Exception e) => m a -> (e -> m a) -> m a #
Unlifted catch
, but will not catch asynchronous exceptions.
Since: unliftio-0.1.0.0
catchIO :: MonadUnliftIO m => m a -> (IOException -> m a) -> m a #
catch
specialized to only catching IOException
s.
Since: unliftio-0.1.0.0
catchAny :: MonadUnliftIO m => m a -> (SomeException -> m a) -> m a #
catch
specialized to catch all synchronous exception.
Since: unliftio-0.1.0.0
catchDeep :: (MonadUnliftIO m, Exception e, NFData a) => m a -> (e -> m a) -> m a #
Same as catch
, but fully force evaluation of the result value
to find all impure exceptions.
Since: unliftio-0.1.0.0
catchAnyDeep :: (NFData a, MonadUnliftIO m) => m a -> (SomeException -> m a) -> m a #
catchDeep
specialized to catch all synchronous exception.
Since: unliftio-0.1.0.0
catchJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a #
handle :: (MonadUnliftIO m, Exception e) => (e -> m a) -> m a -> m a #
Flipped version of catch
.
Since: unliftio-0.1.0.0
handleIO :: MonadUnliftIO m => (IOException -> m a) -> m a -> m a #
handle
specialized to only catching IOException
s.
Since: unliftio-0.1.0.0
handleAny :: MonadUnliftIO m => (SomeException -> m a) -> m a -> m a #
Flipped version of catchAny
.
Since: unliftio-0.1.0.0
handleDeep :: (MonadUnliftIO m, Exception e, NFData a) => (e -> m a) -> m a -> m a #
Flipped version of catchDeep
.
Since: unliftio-0.1.0.0
handleAnyDeep :: (MonadUnliftIO m, NFData a) => (SomeException -> m a) -> m a -> m a #
Flipped version of catchAnyDeep
.
Since: unliftio-0.1.0.0
handleJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m a #
Flipped catchJust
.
Since: unliftio-0.1.0.0
try :: (MonadUnliftIO m, Exception e) => m a -> m (Either e a) #
Unlifted try
, but will not catch asynchronous exceptions.
Since: unliftio-0.1.0.0
tryIO :: MonadUnliftIO m => m a -> m (Either IOException a) #
try
specialized to only catching IOException
s.
Since: unliftio-0.1.0.0
tryAny :: MonadUnliftIO m => m a -> m (Either SomeException a) #
try
specialized to catch all synchronous exceptions.
Since: unliftio-0.1.0.0
tryDeep :: (MonadUnliftIO m, Exception e, NFData a) => m a -> m (Either e a) #
Same as try
, but fully force evaluation of the result value
to find all impure exceptions.
Since: unliftio-0.1.0.0
tryAnyDeep :: (MonadUnliftIO m, NFData a) => m a -> m (Either SomeException a) #
tryDeep
specialized to catch all synchronous exceptions.
Since: unliftio-0.1.0.0
tryJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> m a -> m (Either b a) #
A variant of try
that takes an exception predicate to select
which exceptions are caught.
Since: unliftio-0.1.0.0
pureTry :: a -> Either SomeException a #
Evaluate the value to WHNF and catch any synchronous exceptions.
The expression may still have bottom values within it; you may
instead want to use pureTryDeep
.
Since: unliftio-0.2.2.0
pureTryDeep :: NFData a => a -> Either SomeException a #
Evaluate the value to NF and catch any synchronous exceptions.
Since: unliftio-0.2.2.0
catches :: MonadUnliftIO m => m a -> [Handler m a] -> m a #
Same as upstream catches
, but will not catch
asynchronous exceptions.
Since: unliftio-0.1.0.0
catchesDeep :: (MonadUnliftIO m, NFData a) => m a -> [Handler m a] -> m a #
Same as catches
, but fully force evaluation of the result value
to find all impure exceptions.
Since: unliftio-0.1.0.0
evaluateDeep :: (MonadIO m, NFData a) => a -> m a #
bracket :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> m c) -> m c #
Async safe version of bracket
.
Since: unliftio-0.1.0.0
bracket_ :: MonadUnliftIO m => m a -> m b -> m c -> m c #
Async safe version of bracket_
.
Since: unliftio-0.1.0.0
bracketOnError :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> m c) -> m c #
Async safe version of bracketOnError
.
Since: unliftio-0.1.0.0
bracketOnError_ :: MonadUnliftIO m => m a -> m b -> m c -> m c #
A variant of bracketOnError
where the return value from the first
computation is not required.
Since: unliftio-0.1.0.0
finally :: MonadUnliftIO m => m a -> m b -> m a #
Async safe version of finally
.
Since: unliftio-0.1.0.0
withException :: (MonadUnliftIO m, Exception e) => m a -> (e -> m b) -> m a #
Like onException
, but provides the handler the thrown
exception.
Since: unliftio-0.1.0.0
onException :: MonadUnliftIO m => m a -> m b -> m a #
Async safe version of onException
.
Since: unliftio-0.1.0.0
throwIO :: (MonadIO m, Exception e) => e -> m a #
Synchronously throw the given exception.
Since: unliftio-0.1.0.0
toSyncException :: Exception e => e -> SomeException #
Convert an exception into a synchronous exception.
For synchronous exceptions, this is the same as toException
.
For asynchronous exceptions, this will wrap up the exception with
SyncExceptionWrapper
.
Since: unliftio-0.1.0.0
toAsyncException :: Exception e => e -> SomeException #
Convert an exception into an asynchronous exception.
For asynchronous exceptions, this is the same as toException
.
For synchronous exceptions, this will wrap up the exception with
AsyncExceptionWrapper
.
Since: unliftio-0.1.0.0
isSyncException :: Exception e => e -> Bool #
Check if the given exception is synchronous.
Since: unliftio-0.1.0.0
isAsyncException :: Exception e => e -> Bool #
Check if the given exception is asynchronous.
Since: unliftio-0.1.0.0
mask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b #
Unlifted version of mask
.
Since: unliftio-0.1.0.0
uninterruptibleMask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b #
Unlifted version of uninterruptibleMask
.
Since: unliftio-0.1.0.0
mask_ :: MonadUnliftIO m => m a -> m a #
Unlifted version of mask_
.
Since: unliftio-0.1.0.0
uninterruptibleMask_ :: MonadUnliftIO m => m a -> m a #
Unlifted version of uninterruptibleMask_
.
Since: unliftio-0.1.0.0
throwString :: (MonadIO m, HasCallStack) => String -> m a #
A convenience function for throwing a user error. This is useful for cases where it would be too high a burden to define your own exception type.
This throws an exception of type StringException
. When GHC
supports it (base 4.9 and GHC 8.0 and onward), it includes a call
stack.
Since: unliftio-0.1.0.0
stringException :: HasCallStack -> String -> StringException #
Smart constructor for a StringException
that deals with the
call stack.
Since: unliftio-0.1.0.0
throwTo :: (Exception e, MonadIO m) => ThreadId -> e -> m () #
Throw an asynchronous exception to another thread.
Synchronously typed exceptions will be wrapped into an
AsyncExceptionWrapper
, see
https://github.com/fpco/safe-exceptions#determining-sync-vs-async.
It's usually a better idea to use the UnliftIO.Async module, see https://github.com/fpco/safe-exceptions#quickstart.
Since: unliftio-0.1.0.0
impureThrow :: Exception e => e -> a #
Generate a pure value which, when forced, will synchronously throw the given exception.
Generally it's better to avoid using this function and instead use throwIO
,
see https://github.com/fpco/safe-exceptions#quickstart.
Since: unliftio-0.1.0.0
fromEither :: (Exception e, MonadIO m) => Either e a -> m a #
fromEitherIO :: (Exception e, MonadIO m) => IO (Either e a) -> m a #
Same as fromEither
, but works on an IO
-wrapped Either
.
Since: unliftio-0.1.0.0
fromEitherM :: (Exception e, MonadIO m) => m (Either e a) -> m a #
Same as fromEither
, but works on an m
-wrapped Either
.
Since: unliftio-0.1.0.0
newtype Concurrently (m :: Type -> Type) a #
Unlifted Concurrently
.
Since: unliftio-0.1.0.0
Constructors
Concurrently | |
Fields
|
Instances
async :: MonadUnliftIO m => m a -> m (Async a) #
Unlifted async
.
Since: unliftio-0.1.0.0
asyncBound :: MonadUnliftIO m => m a -> m (Async a) #
Unlifted asyncBound
.
Since: unliftio-0.1.0.0
asyncWithUnmask :: MonadUnliftIO m => ((forall b. m b -> m b) -> m a) -> m (Async a) #
Unlifted asyncWithUnmask
.
Since: unliftio-0.1.0.0
asyncOnWithUnmask :: MonadUnliftIO m => Int -> ((forall b. m b -> m b) -> m a) -> m (Async a) #
Unlifted asyncOnWithUnmask
.
Since: unliftio-0.1.0.0
withAsync :: MonadUnliftIO m => m a -> (Async a -> m b) -> m b #
Unlifted withAsync
.
Since: unliftio-0.1.0.0
withAsyncBound :: MonadUnliftIO m => m a -> (Async a -> m b) -> m b #
Unlifted withAsyncBound
.
Since: unliftio-0.1.0.0
withAsyncOn :: MonadUnliftIO m => Int -> m a -> (Async a -> m b) -> m b #
Unlifted withAsyncOn
.
Since: unliftio-0.1.0.0
withAsyncWithUnmask :: MonadUnliftIO m => ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b #
Unlifted withAsyncWithUnmask
.
Since: unliftio-0.1.0.0
withAsyncOnWithUnmask :: MonadUnliftIO m => Int -> ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b #
Unlifted withAsyncOnWithMask
.
Since: unliftio-0.1.0.0
poll :: MonadIO m => Async a -> m (Maybe (Either SomeException a)) #
Lifted poll
.
Since: unliftio-0.1.0.0
waitCatch :: MonadIO m => Async a -> m (Either SomeException a) #
Lifted waitCatch
.
Since: unliftio-0.1.0.0
uninterruptibleCancel :: MonadIO m => Async a -> m () #
Lifted uninterruptibleCancel
.
Since: unliftio-0.1.0.0
cancelWith :: (Exception e, MonadIO m) => Async a -> e -> m () #
Lifted cancelWith
. Additionally uses toAsyncException
to
ensure async exception safety.
Since: unliftio-0.1.0.0
waitAnyCatch :: MonadIO m => [Async a] -> m (Async a, Either SomeException a) #
Lifted waitAnyCatch
.
Since: unliftio-0.1.0.0
waitAnyCancel :: MonadIO m => [Async a] -> m (Async a, a) #
Lifted waitAnyCancel
.
Since: unliftio-0.1.0.0
waitAnyCatchCancel :: MonadIO m => [Async a] -> m (Async a, Either SomeException a) #
Lifted waitAnyCatchCancel
.
Since: unliftio-0.1.0.0
waitEither :: MonadIO m => Async a -> Async b -> m (Either a b) #
Lifted waitEither
.
Since: unliftio-0.1.0.0
waitEitherCatch :: MonadIO m => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b)) #
Lifted waitEitherCatch
.
Since: unliftio-0.1.0.0
waitEitherCancel :: MonadIO m => Async a -> Async b -> m (Either a b) #
Lifted waitEitherCancel
.
Since: unliftio-0.1.0.0
waitEitherCatchCancel :: MonadIO m => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b)) #
Lifted waitEitherCatchCancel
.
Since: unliftio-0.1.0.0
waitEither_ :: MonadIO m => Async a -> Async b -> m () #
Lifted waitEither_
.
Since: unliftio-0.1.0.0
race :: MonadUnliftIO m => m a -> m b -> m (Either a b) #
Unlifted race
.
Since: unliftio-0.1.0.0
race_ :: MonadUnliftIO m => m a -> m b -> m () #
Unlifted race_
.
Since: unliftio-0.1.0.0
concurrently :: MonadUnliftIO m => m a -> m b -> m (a, b) #
Unlifted concurrently
.
Since: unliftio-0.1.0.0
concurrently_ :: MonadUnliftIO m => m a -> m b -> m () #
Unlifted concurrently_
.
Since: unliftio-0.1.0.0
mapConcurrently :: (MonadUnliftIO m, Traversable t) => (a -> m b) -> t a -> m (t b) #
Unlifted mapConcurrently
.
Since: unliftio-0.1.0.0
forConcurrently :: (MonadUnliftIO m, Traversable t) => t a -> (a -> m b) -> m (t b) #
Unlifted forConcurrently
.
Since: unliftio-0.1.0.0
mapConcurrently_ :: (MonadUnliftIO m, Foldable f) => (a -> m b) -> f a -> m () #
Unlifted mapConcurrently_
.
Since: unliftio-0.1.0.0
forConcurrently_ :: (MonadUnliftIO m, Foldable f) => f a -> (a -> m b) -> m () #
Unlifted forConcurrently_
.
Since: unliftio-0.1.0.0
replicateConcurrently :: MonadUnliftIO m => Int -> m a -> m [a] #
Unlifted replicateConcurrently
.
Since: unliftio-0.1.0.0
replicateConcurrently_ :: MonadUnliftIO m => Int -> m a -> m () #
Unlifted replicateConcurrently_
.
Since: unliftio-0.1.0.0
withFile :: MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m a) -> m a #
Unlifted version of withFile
.
Since: unliftio-0.1.0.0
withBinaryFile :: MonadUnliftIO m => FilePath -> IOMode -> (Handle -> m a) -> m a #
Unlifted version of withBinaryFile
.
Since: unliftio-0.1.0.0
hSetFileSize :: MonadIO m => Handle -> Integer -> m () #
Lifted version of hSetFileSize
Since: unliftio-0.2.1.0
hSetBuffering :: MonadIO m => Handle -> BufferMode -> m () #
Lifted version of hSetBuffering
Since: unliftio-0.2.1.0
hGetBuffering :: MonadIO m => Handle -> m BufferMode #
Lifted version of hGetBuffering
Since: unliftio-0.2.1.0
hSeek :: MonadIO m => Handle -> SeekMode -> Integer -> m () #
Lifted version of hSeek
Since: unliftio-0.2.1.0
hIsReadable :: MonadIO m => Handle -> m Bool #
Lifted version of hIsReadable
Since: unliftio-0.2.1.0
hIsWritable :: MonadIO m => Handle -> m Bool #
Lifted version of hIsWritable
Since: unliftio-0.2.1.0
hIsSeekable :: MonadIO m => Handle -> m Bool #
Lifted version of hIsSeekable
Since: unliftio-0.2.1.0
hIsTerminalDevice :: MonadIO m => Handle -> m Bool #
Lifted version of hIsTerminalDevice
Since: unliftio-0.2.1.0
hWaitForInput :: MonadIO m => Handle -> Int -> m Bool #
Lifted version of hWaitForInput
Since: unliftio-0.2.1.0
getMonotonicTime :: MonadIO m => m Double #
Get the number of seconds which have passed since an arbitrary starting time, useful for calculating runtime in a program.
Since: unliftio-0.2.3.0
writeIORef :: MonadIO m => IORef a -> a -> m () #
Lifted writeIORef
.
Since: unliftio-0.1.0.0
modifyIORef :: MonadIO m => IORef a -> (a -> a) -> m () #
Lifted modifyIORef
.
Since: unliftio-0.1.0.0
modifyIORef' :: MonadIO m => IORef a -> (a -> a) -> m () #
Lifted modifyIORef'
.
Since: unliftio-0.1.0.0
atomicModifyIORef :: MonadIO m => IORef a -> (a -> (a, b)) -> m b #
Lifted atomicModifyIORef
.
Since: unliftio-0.1.0.0
atomicModifyIORef' :: MonadIO m => IORef a -> (a -> (a, b)) -> m b #
Lifted atomicModifyIORef'
.
Since: unliftio-0.1.0.0
atomicWriteIORef :: MonadIO m => IORef a -> a -> m () #
Lifted atomicWriteIORef
.
Since: unliftio-0.1.0.0
mkWeakIORef :: MonadUnliftIO m => IORef a -> m () -> m (Weak (IORef a)) #
Unlifted mkWeakIORef
.
Since: unliftio-0.1.0.0
newEmptyMVar :: MonadIO m => m (MVar a) #
Lifted newEmptyMVar
.
Since: unliftio-0.1.0.0
tryTakeMVar :: MonadIO m => MVar a -> m (Maybe a) #
Lifted tryTakeMVar
.
Since: unliftio-0.1.0.0
tryPutMVar :: MonadIO m => MVar a -> a -> m Bool #
Lifted tryPutMVar
.
Since: unliftio-0.1.0.0
isEmptyMVar :: MonadIO m => MVar a -> m Bool #
Lifted isEmptyMVar
.
Since: unliftio-0.1.0.0
tryReadMVar :: MonadIO m => MVar a -> m (Maybe a) #
Lifted tryReadMVar
.
Since: unliftio-0.1.0.0
withMVar :: MonadUnliftIO m => MVar a -> (a -> m b) -> m b #
Unlifted withMVar
.
Since: unliftio-0.1.0.0
withMVarMasked :: MonadUnliftIO m => MVar a -> (a -> m b) -> m b #
Unlifted withMVarMasked
.
Since: unliftio-0.1.0.0
modifyMVar_ :: MonadUnliftIO m => MVar a -> (a -> m a) -> m () #
Unlifted modifyMVar_
.
Since: unliftio-0.1.0.0
modifyMVar :: MonadUnliftIO m => MVar a -> (a -> m (a, b)) -> m b #
Unlifted modifyMVar
.
Since: unliftio-0.1.0.0
modifyMVarMasked_ :: MonadUnliftIO m => MVar a -> (a -> m a) -> m () #
Unlifted modifyMVarMasked_
.
Since: unliftio-0.1.0.0
modifyMVarMasked :: MonadUnliftIO m => MVar a -> (a -> m (a, b)) -> m b #
Unlifted modifyMVarMasked
.
Since: unliftio-0.1.0.0
mkWeakMVar :: MonadUnliftIO m => MVar a -> m () -> m (Weak (MVar a)) #
Unlifted mkWeakMVar
.
Since: unliftio-0.1.0.0
A "run once" value, with results saved. Extract the value with
runMemoized
. For single-threaded usage, you can use memoizeRef
to
create a value. If you need guarantees that only one thread will run the
action at a time, use memoizeMVar
.
Note that this type provides a Show
instance for convenience, but not
useful information can be provided.
Since: unliftio-0.2.8.0
runMemoized :: MonadIO m => Memoized a -> m a #
Extract a value from a Memoized
, running an action if no cached value is
available.
Since: unliftio-0.2.8.0
memoizeRef :: MonadUnliftIO m => m a -> m (Memoized a) #
Create a new Memoized
value using an IORef
under the surface. Note that
the action may be run in multiple threads simultaneously, so this may not be
thread safe (depending on the underlying action). Consider using
memoizeMVar
.
Since: unliftio-0.2.8.0
memoizeMVar :: MonadUnliftIO m => m a -> m (Memoized a) #
Same as memoizeRef
, but uses an MVar
to ensure that an action is
only run once, even in a multithreaded application.
Since: unliftio-0.2.8.0
atomically :: MonadIO m => STM a -> m a #
Lifted version of atomically
Since: unliftio-0.2.1.0
readTVarIO :: MonadIO m => TVar a -> m a #
Lifted version of readTVarIO
Since: unliftio-0.2.1.0
registerDelay :: MonadIO m => Int -> m (TVar Bool) #
Lifted version of registerDelay
Since: unliftio-0.2.1.0
mkWeakTVar :: MonadUnliftIO m => TVar a -> m () -> m (Weak (TVar a)) #
Lifted version of mkWeakTVar
Since: unliftio-0.2.1.0
newTMVarIO :: MonadIO m => a -> m (TMVar a) #
Lifted version of newTMVarIO
Since: unliftio-0.2.1.0
newEmptyTMVarIO :: MonadIO m => m (TMVar a) #
Lifted version of newEmptyTMVarIO
Since: unliftio-0.2.1.0
mkWeakTMVar :: MonadUnliftIO m => TMVar a -> m () -> m (Weak (TMVar a)) #
Lifted version of mkWeakTMVar
Since: unliftio-0.2.1.0
newTChanIO :: MonadIO m => m (TChan a) #
Lifted version of newTChanIO
Since: unliftio-0.2.1.0
newBroadcastTChanIO :: MonadIO m => m (TChan a) #
Lifted version of newBroadcastTChanIO
Since: unliftio-0.2.1.0
newTQueueIO :: MonadIO m => m (TQueue a) #
Lifted version of newTQueueIO
Since: unliftio-0.2.1.0
newTBQueueIO :: MonadIO m => Natural -> m (TBQueue a) #
Lifted version of newTBQueueIO
Since: unliftio-0.2.1.0
Arguments
:: MonadUnliftIO m | |
=> String | File name template. See |
-> (FilePath -> Handle -> m a) | Callback that can use the file |
-> m a |
Create and use a temporary file in the system standard temporary directory.
Behaves exactly the same as withTempFile
, except that the parent temporary directory
will be that returned by getCanonicalTemporaryDirectory
.
Since: unliftio-0.1.0.0
Arguments
:: MonadUnliftIO m | |
=> String | Directory name template. See |
-> (FilePath -> m a) | Callback that can use the directory. |
-> m a |
Create and use a temporary directory in the system standard temporary directory.
Behaves exactly the same as withTempDirectory
, except that the parent temporary directory
will be that returned by getCanonicalTemporaryDirectory
.
Since: unliftio-0.1.0.0
Arguments
:: MonadUnliftIO m | |
=> FilePath | Temp dir to create the file in. |
-> String | File name template. See |
-> (FilePath -> Handle -> m a) | Callback that can use the file. |
-> m a |
Use a temporary filename that doesn't already exist.
Creates a new temporary file inside the given directory, making use of the template. The temp file is deleted after use. For example:
withTempFile "src" "sdist." $ \tmpFile hFile -> do ...
The tmpFile
will be file in the given directory, e.g.
src/sdist.342
.
Since: unliftio-0.1.0.0
Arguments
:: MonadUnliftIO m | |
=> FilePath | Temp directory to create the directory in. |
-> String | Directory name template. See |
-> (FilePath -> m a) | Callback that can use the directory. |
-> m a |
Create and use a temporary directory.
Creates a new temporary directory inside the given directory, making use of the template. The temp directory is deleted after use. For example:
withTempDirectory "src" "sdist." $ \tmpDir -> do ...
The tmpDir
will be a new subdirectory of the given directory, e.g.
src/sdist.342
.
Since: unliftio-0.1.0.0
Arguments
:: MonadUnliftIO n | |
=> (n b -> m b) | The wrapper, for instance |
-> (forall a. m a -> n a) | The inverse, for instance |
-> ((forall a. m a -> IO a) -> IO b) | The actual function to invoke |
-> m b |
A helper function for implementing MonadUnliftIO
instances.
Useful for the common case where you want to simply delegate to the
underlying transformer.
Example
newtype AppT m a = AppT { unAppT :: ReaderT Int (ResourceT m) a } deriving (Functor, Applicative, Monad, MonadIO) -- Unfortunately, deriving MonadUnliftIO does not work. instance MonadUnliftIO m => MonadUnliftIO (AppT m) where withRunInIO = wrappedWithRunInIO AppT unAppT
Since: unliftio-core-0.1.2.0
toIO :: MonadUnliftIO m => m a -> m (IO a) #
Convert an action in m
to an action in IO
.
Since: unliftio-core-0.1.0.0
withUnliftIO :: MonadUnliftIO m => (UnliftIO m -> IO a) -> m a #
Convenience function for capturing the monadic context and running
an IO
action. The UnliftIO
newtype wrapper is rarely needed, so
prefer withRunInIO
to this function.
Since: unliftio-core-0.1.0.0
askRunInIO :: MonadUnliftIO m => m (m a -> IO a) #
Same as askUnliftIO
, but returns a monomorphic function
instead of a polymorphic newtype wrapper. If you only need to apply
the transformation on one concrete type, this function can be more
convenient.
Since: unliftio-core-0.1.0.0
newtype UnliftIO (m :: Type -> Type) #
The ability to run any monadic action m a
as IO a
.
This is more precisely a natural transformation. We need to new
datatype (instead of simply using a forall
) due to lack of
support in GHC for impredicative types.
Since: unliftio-core-0.1.0.0
TBQueue
is an abstract type representing a bounded FIFO channel.
Since: stm-2.4
Builds and returns a new instance of TBQueue
.
writeTBQueue :: TBQueue a -> a -> STM () #
Write a value to a TBQueue
; blocks if the queue is full.
readTBQueue :: TBQueue a -> STM a #
Read the next value from the TBQueue
.
tryReadTBQueue :: TBQueue a -> STM (Maybe a) #
A version of readTBQueue
which does not retry. Instead it
returns Nothing
if no value is available.
peekTBQueue :: TBQueue a -> STM a #
Get the next value from the TBQueue
without removing it,
retrying if the channel is empty.
tryPeekTBQueue :: TBQueue a -> STM (Maybe a) #
A version of peekTBQueue
which does not retry. Instead it
returns Nothing
if no value is available.
unGetTBQueue :: TBQueue a -> a -> STM () #
Put a data item back onto a channel, where it will be the next item read. Blocks if the queue is full.
isFullTBQueue :: TBQueue a -> STM Bool #
TChan
is an abstract type representing an unbounded FIFO channel.
newBroadcastTChan :: STM (TChan a) #
Create a write-only TChan
. More precisely, readTChan
will retry
even after items have been written to the channel. The only way to read
a broadcast channel is to duplicate it with dupTChan
.
Consider a server that broadcasts messages to clients:
serve :: TChan Message -> Client -> IO loop serve broadcastChan client = do myChan <- dupTChan broadcastChan forever $ do message <- readTChan myChan send client message
The problem with using newTChan
to create the broadcast channel is that if
it is only written to and never read, items will pile up in memory. By
using newBroadcastTChan
to create the broadcast channel, items can be
garbage collected after clients have seen them.
Since: stm-2.4
writeTChan :: TChan a -> a -> STM () #
Write a value to a TChan
.
tryReadTChan :: TChan a -> STM (Maybe a) #
A version of readTChan
which does not retry. Instead it
returns Nothing
if no value is available.
Since: stm-2.3
peekTChan :: TChan a -> STM a #
Get the next value from the TChan
without removing it,
retrying if the channel is empty.
Since: stm-2.3
tryPeekTChan :: TChan a -> STM (Maybe a) #
A version of peekTChan
which does not retry. Instead it
returns Nothing
if no value is available.
Since: stm-2.3
dupTChan :: TChan a -> STM (TChan a) #
Duplicate a TChan
: the duplicate channel begins empty, but data written to
either channel from then on will be available from both. Hence this creates
a kind of broadcast channel, where data written by anyone is seen by
everyone else.
unGetTChan :: TChan a -> a -> STM () #
Put a data item back onto a channel, where it will be the next item read.
cloneTChan :: TChan a -> STM (TChan a) #
Clone a TChan
: similar to dupTChan, but the cloned channel starts with the
same content available as the original channel.
Since: stm-2.4
A TMVar
is a synchronising variable, used
for communication between concurrent threads. It can be thought of
as a box, which may be empty or full.
newEmptyTMVar :: STM (TMVar a) #
Create a TMVar
which is initially empty.
tryTakeTMVar :: TMVar a -> STM (Maybe a) #
A version of takeTMVar
that does not retry
. The tryTakeTMVar
function returns Nothing
if the TMVar
was empty, or
if
the Just
aTMVar
was full with contents a
. After tryTakeTMVar
, the
TMVar
is left empty.
tryPutTMVar :: TMVar a -> a -> STM Bool #
tryReadTMVar :: TMVar a -> STM (Maybe a) #
A version of readTMVar
which does not retry. Instead it
returns Nothing
if no value is available.
Since: stm-2.3
TQueue
is an abstract type representing an unbounded FIFO channel.
Since: stm-2.4
writeTQueue :: TQueue a -> a -> STM () #
Write a value to a TQueue
.
readTQueue :: TQueue a -> STM a #
Read the next value from the TQueue
.
tryReadTQueue :: TQueue a -> STM (Maybe a) #
A version of readTQueue
which does not retry. Instead it
returns Nothing
if no value is available.
peekTQueue :: TQueue a -> STM a #
Get the next value from the TQueue
without removing it,
retrying if the channel is empty.
tryPeekTQueue :: TQueue a -> STM (Maybe a) #
A version of peekTQueue
which does not retry. Instead it
returns Nothing
if no value is available.
unGetTQueue :: TQueue a -> a -> STM () #
Put a data item back onto a channel, where it will be the next item read.
modifyTVar :: TVar a -> (a -> a) -> STM () #
Mutate the contents of a TVar
. N.B., this version is
non-strict.
Since: stm-2.3
modifyTVar' :: TVar a -> (a -> a) -> STM () #
Strict version of modifyTVar
.
Since: stm-2.3
traceDisplayStack :: Display a => a -> b -> b #
Since: rio-0.1.0.0
traceDisplayMarkerIO :: (Display a, MonadIO m) => a -> m () #
Since: rio-0.1.0.0
traceDisplayMarker :: Display a => a -> b -> b #
Since: rio-0.1.0.0
traceDisplayEventIO :: (Display a, MonadIO m) => a -> m () #
Since: rio-0.1.0.0
traceDisplayEvent :: Display a => a -> b -> b #
Since: rio-0.1.0.0
traceDisplayM :: (Display a, Applicative f) => a -> f () #
Since: rio-0.1.0.0
traceDisplayIO :: (Display a, MonadIO m) => a -> m () #
Since: rio-0.1.0.0
traceDisplayId :: Display a => a -> a #
Since: rio-0.1.0.0
traceDisplay :: Display a => a -> b -> b #
Since: rio-0.1.0.0
traceShowStack :: Show a => a -> b -> b #
Since: rio-0.1.0.0
traceShowMarkerIO :: (Show a, MonadIO m) => a -> m () #
Since: rio-0.1.0.0
traceShowMarker :: Show a => a -> b -> b #
Since: rio-0.1.0.0
traceShowEventIO :: (Show a, MonadIO m) => a -> m () #
Since: rio-0.1.0.0
traceShowEvent :: Show a => a -> b -> b #
Since: rio-0.1.0.0
traceShowM :: (Show a, Applicative f) => a -> f () #
Since: rio-0.1.0.0
traceShowIO :: (Show a, MonadIO m) => a -> m () #
Since: rio-0.1.0.0
traceShowId :: Show a => a -> a #
Since: rio-0.1.0.0
traceStack :: Text -> a -> a #
Since: rio-0.1.0.0
traceMarkerIO :: MonadIO m => Text -> m () #
Since: rio-0.1.0.0
traceMarker :: Text -> a -> a #
Since: rio-0.1.0.0
traceEventIO :: MonadIO m => Text -> m () #
Since: rio-0.1.0.0
traceEvent :: Text -> a -> a #
Since: rio-0.1.0.0
traceM :: Applicative f => Text -> f () #
Since: rio-0.1.0.0
runSimpleApp :: MonadIO m => RIO SimpleApp a -> m a #
Run with a default configured SimpleApp
, consisting of:
- Logging to stderr
- If the
RIO_VERBOSE
environment variable is set, turns on verbose logging - Default process context
Since: rio-0.1.3.0
A simple, non-customizable environment type for RIO
, which
provides common functionality. If it's insufficient for your needs,
define your own, custom App
data type.
Since: rio-0.1.3.0
Instances
HasProcessContext SimpleApp | |
Defined in RIO.Prelude.Simple Methods | |
HasLogFunc SimpleApp | |
newUnboxedSomeRef :: (MonadIO m, Unbox a) => a -> m (SomeRef a) #
create a new unboxed SomeRef
Since: rio-0.1.4.0
newSomeRef :: MonadIO m => a -> m (SomeRef a) #
create a new boxed SomeRef
Since: rio-0.1.4.0
modifySomeRef :: MonadIO m => SomeRef a -> (a -> a) -> m () #
Modify a SomeRef This function is subject to change due to the lack of atomic operations
Since: rio-0.1.4.0
writeSomeRef :: MonadIO m => SomeRef a -> a -> m () #
Write to a SomeRef
Since: rio-0.1.4.0
readSomeRef :: MonadIO m => SomeRef a -> m a #
Read from a SomeRef
Since: rio-0.1.4.0
liftRIO :: (MonadIO m, MonadReader env m) => RIO env a -> m a #
The Reader+IO monad. This is different from a ReaderT
because:
- It's not a transformer, it hardcodes IO for simpler usage and error messages.
- Instances of typeclasses like
MonadLogger
are implemented using classes defined on the environment, instead of using an underlying monad.
Instances
(Monoid w, HasWriteRef w env) => MonadWriter w (RIO env) | |
HasStateRef s env => MonadState s (RIO env) | |
MonadReader env (RIO env) | |
Monad (RIO env) | |
Functor (RIO env) | |
Applicative (RIO env) | |
MonadThrow (RIO env) | |
Defined in RIO.Prelude.RIO | |
MonadIO (RIO env) | |
Defined in RIO.Prelude.RIO | |
MonadUnliftIO (RIO env) | |
Defined in RIO.Prelude.RIO | |
PrimMonad (RIO env) | |
type PrimState (RIO env) | |
Defined in RIO.Prelude.RIO |
Abstraction over how to read from and write to a mutable reference
Since: rio-0.1.4.0
Instances
HasStateRef a (SomeRef a) | Identity state reference where the SomeRef is the env Since: rio-0.1.4.0 |
HasWriteRef a (SomeRef a) | Identity write reference where the SomeRef is the env Since: rio-0.1.4.0 |
class HasStateRef s env | env -> s where #
Environment values with stateful capabilities to SomeRef
Since: rio-0.1.4.0
Instances
HasStateRef a (SomeRef a) | Identity state reference where the SomeRef is the env Since: rio-0.1.4.0 |
class HasWriteRef w env | env -> w where #
Environment values with writing capabilities to SomeRef
Since: rio-0.1.4.0
Instances
HasWriteRef a (SomeRef a) | Identity write reference where the SomeRef is the env Since: rio-0.1.4.0 |
modifyURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> (a -> a) -> m () #
Modify a value in a URef
. Note that this action is strict, and
will force evaluation of the result value.
Since: rio-0.0.2.0
writeURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> a -> m () #
Write a value into a URef
. Note that this action is strict, and
will force evalution of the value.
Since: rio-0.0.2.0
readURef :: (PrimMonad m, Unbox a) => URef (PrimState m) a -> m a #
Read the value in a URef
Since: rio-0.0.2.0
newURef :: (PrimMonad m, Unbox a) => a -> m (URef (PrimState m) a) #
Create a new URef
Since: rio-0.0.2.0
An unboxed reference. This works like an IORef
, but the data is
stored in a bytearray instead of a heap object, avoiding
significant allocation overhead in some cases. For a concrete
example, see this Stack Overflow question:
https://stackoverflow.com/questions/27261813/why-is-my-little-stref-int-require-allocating-gigabytes.
The first parameter is the state token type, the same as would be
used for the ST
monad. If you're using an IO
-based monad, you
can use the convenience IOURef
type synonym instead.
Since: rio-0.0.2.0
decodeUtf8Lenient :: ByteString -> Text #
noLogging :: (HasLogFunc env, MonadReader env m) => m a -> m a #
Disable logging capabilities in a given sub-routine
Intended to skip logging in general purpose implementations, where secrets might be logged accidently.
Since: rio-0.1.5.0
logFuncUseColorL :: HasLogFunc env => SimpleGetter env Bool #
Is the log func configured to use color output?
Intended for use by code which wants to optionally add additional color to its log messages.
Since: rio-0.1.0.0
displayCallStack :: CallStack -> Utf8Builder #
Convert a CallStack
value into a Utf8Builder
indicating
the first source location.
TODO Consider showing the entire call stack instead.
Since: rio-0.0.0.0
setLogUseLoc :: Bool -> LogOptions -> LogOptions #
Use code location in the log output.
Default: true if in verbose mode, false otherwise.
Since: rio-0.1.2.0
setLogUseColor :: Bool -> LogOptions -> LogOptions #
Use ANSI color codes in the log output.
Default: true if in verbose mode and the Handle
is a terminal device.
Since: rio-0.0.0.0
setLogUseTime :: Bool -> LogOptions -> LogOptions #
Include the time when printing log messages.
Default: true in debug mode, false otherwise.
Since: rio-0.0.0.0
setLogTerminal :: Bool -> LogOptions -> LogOptions #
Do we treat output as a terminal. If True
, we will enabled
sticky logging functionality.
Default: checks if the Handle
provided to logOptionsHandle
is a
terminal with hIsTerminalDevice
.
Since: rio-0.0.0.0
setLogVerboseFormatIO :: IO Bool -> LogOptions -> LogOptions #
Refer to setLogVerboseFormat
. This modifier allows to alter the verbose
format value dynamically at runtime.
Default: follows the value of the verbose flag.
Since: rio-0.1.3.0
setLogVerboseFormat :: Bool -> LogOptions -> LogOptions #
Use the verbose format for printing log messages.
Default: follows the value of the verbose flag.
Since: rio-0.0.0.0
setLogMinLevelIO :: IO LogLevel -> LogOptions -> LogOptions #
Refer to setLogMinLevel
. This modifier allows to alter the verbose format
value dynamically at runtime.
Default: in verbose mode, LevelDebug
. Otherwise, LevelInfo
.
Since: rio-0.1.3.0
setLogMinLevel :: LogLevel -> LogOptions -> LogOptions #
Set the minimum log level. Messages below this level will not be printed.
Default: in verbose mode, LevelDebug
. Otherwise, LevelInfo
.
Since: rio-0.0.0.0
withLogFunc :: MonadUnliftIO m => LogOptions -> (LogFunc -> m a) -> m a #
Given a LogOptions
value, run the given function with the
specified LogFunc
. A common way to use this function is:
let isVerbose = False -- get from the command line instead logOptions' <- logOptionsHandle stderr isVerbose let logOptions = setLogUseTime True logOptions' withLogFunc logOptions $ lf -> do let app = App -- application specific environment { appLogFunc = lf , appOtherStuff = ... } runRIO app $ do logInfo "Starting app" myApp
Since: rio-0.0.0.0
newLogFunc :: (MonadIO n, MonadIO m) => LogOptions -> n (LogFunc, m ()) #
Given a LogOptions
value, returns both a new LogFunc
and a sub-routine that
disposes it.
Intended for use if you want to deal with the teardown of LogFunc
yourself,
otherwise prefer the withLogFunc
function instead.
@since 0.1.3.0
Arguments
:: MonadIO m | |
=> Handle | |
-> Bool | verbose? |
-> m LogOptions |
Create a LogOptions
value from the given Handle
and whether
to perform verbose logging or not. Individiual settings can be
overridden using appropriate set
functions.
Since: rio-0.0.0.0
logOptionsMemory :: MonadIO m => m (IORef Builder, LogOptions) #
Create a LogOptions
value which will store its data in
memory. This is primarily intended for testing purposes. This will
return both a LogOptions
value and an IORef
containing the
resulting Builder
value.
This will default to non-verbose settings and assume there is a
terminal attached. These assumptions can be overridden using the
appropriate set
functions.
Since: rio-0.0.0.0
logStickyDone :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => Utf8Builder -> m () #
This will print out the given message with a newline and disable
any further stickiness of the line until a new call to logSticky
happens.
Since: rio-0.0.0.0
logSticky :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => Utf8Builder -> m () #
Write a "sticky" line to the terminal. Any subsequent lines will
overwrite this one, and that same line will be repeated below
again. In other words, the line sticks at the bottom of the output
forever. Running this function again will replace the sticky line
with a new sticky line. When you want to get rid of the sticky
line, run logStickyDone
.
Note that not all LogFunc
implementations will support sticky
messages as described. However, the withLogFunc
implementation
provided by this module does.
Since: rio-0.0.0.0
Arguments
:: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) | |
=> Text | level |
-> LogSource | |
-> Utf8Builder | |
-> m () |
Log a message with the specified textual level and the given source.
Since: rio-0.0.0.0
logErrorS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m () #
Log an error level message with the given source.
Since: rio-0.0.0.0
logWarnS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m () #
Log a warn level message with the given source.
Since: rio-0.0.0.0
logInfoS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m () #
Log an info level message with the given source.
Since: rio-0.0.0.0
logDebugS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> Utf8Builder -> m () #
Log a debug level message with the given source.
Since: rio-0.0.0.0
Arguments
:: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) | |
=> Text | level |
-> Utf8Builder | |
-> m () |
Log a message with the specified textual level and no source.
Since: rio-0.0.0.0
logError :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m () #
Log an error level message with no source.
Since: rio-0.0.0.0
logWarn :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m () #
Log a warn level message with no source.
Since: rio-0.0.0.0
logInfo :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m () #
Log an info level message with no source.
Since: rio-0.0.0.0
logDebug :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> m () #
Log a debug level message with no source.
Since: rio-0.0.0.0
logGeneric :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogLevel -> Utf8Builder -> m () #
Generic, basic function for creating other logging functions.
Since: rio-0.0.0.0
mkLogFunc :: (CallStack -> LogSource -> LogLevel -> Utf8Builder -> IO ()) -> LogFunc #
Create a LogFunc
from the given function.
Since: rio-0.0.0.0
The log level of a message.
Since: rio-0.0.0.0
Constructors
LevelDebug | |
LevelInfo | |
LevelWarn | |
LevelError | |
LevelOther !Text |
Where in the application a log message came from. Used for display purposes only.
Since: rio-0.0.0.0
class HasLogFunc env where #
Environment values with a logging function.
Since: rio-0.0.0.0
Instances
HasLogFunc SimpleApp | |
HasLogFunc LoggedProcessContext | |
Defined in RIO.Process Methods | |
HasLogFunc LogFunc | |
HasLogFunc Runner Source # | |
HasLogFunc LoadConfig Source # | |
Defined in Stack.Types.Config Methods | |
HasLogFunc EnvConfig Source # | |
HasLogFunc BuildConfig Source # | |
Defined in Stack.Types.Config Methods | |
HasLogFunc Config Source # | |
HasLogFunc MiniConfig Source # | |
Defined in Stack.Config Methods |
A logging function, wrapped in a newtype for better error messages.
An implementation may choose any behavior of this value it wishes, including printing to standard output or no action at all.
Since: rio-0.0.0.0
data LogOptions #
Configuration for how to create a LogFunc
. Intended to be used
with the withLogFunc
function.
Since: rio-0.0.0.0
toStrictBytes :: LByteString -> ByteString #
type LByteString = ByteString #
Helper function to force an action to run in IO
. Especially
useful for overly general contexts, like hspec tests.
Since: rio-0.1.3.0
foldMapM :: (Monad m, Monoid w, Foldable t) => (a -> m w) -> t a -> m w #
Extend foldMap
to allow side effects.
Internally, this is implemented using a strict left fold. This is used for
performance reasons. It also necessitates that this function has a Monad
constraint and not just an Applicative
constraint. For more information,
see
https://github.com/commercialhaskell/rio/pull/99#issuecomment-394179757.
Since: rio-0.1.3.0
mapMaybeA :: Applicative f => (a -> f (Maybe b)) -> [a] -> f [b] #
Applicative mapMaybe
.
readFileUtf8 :: MonadIO m => FilePath -> m Text #
Read a file in UTF8 encoding, throwing an exception on invalid character encoding.
This function will use OS-specific line ending handling.
writeFileBinary :: MonadIO m => FilePath -> ByteString -> m () #
readFileBinary :: MonadIO m => FilePath -> m ByteString #
hPutBuilder :: MonadIO m => Handle -> Builder -> m () #
writeFileUtf8 :: MonadIO m => FilePath -> Text -> m () #
Write a file in UTF8 encoding
This function will use OS-specific line ending handling.
withLazyFile :: MonadUnliftIO m => FilePath -> (ByteString -> m a) -> m a #
Lazily get the contents of a file. Unlike readFile
, this
ensures that if an exception is thrown, the file handle is closed
immediately.
yieldThread :: MonadIO m => m () #
view :: MonadReader s m => Getting a s a -> m a #
writeFileUtf8Builder :: MonadIO m => FilePath -> Utf8Builder -> m () #
Write the given Utf8Builder
value to a file.
Since: rio-0.1.0.0
utf8BuilderToLazyText :: Utf8Builder -> Text #
Convert a Utf8Builder
value into a lazy Text
.
Since: rio-0.1.0.0
utf8BuilderToText :: Utf8Builder -> Text #
Convert a Utf8Builder
value into a strict Text
.
Since: rio-0.1.0.0
displayBytesUtf8 :: ByteString -> Utf8Builder #
Convert a ByteString
into a Utf8Builder
.
NOTE This function performs no checks to ensure that the data is, in fact, UTF8 encoded. If you provide non-UTF8 data, later functions may fail.
Since: rio-0.1.0.0
displayShow :: Show a => a -> Utf8Builder #
Use the Show
instance for a value to convert it to a
Utf8Builder
.
Since: rio-0.1.0.0
newtype Utf8Builder #
A builder of binary data, with the invariant that the underlying data is supposed to be UTF-8 encoded.
Since: rio-0.1.0.0
Constructors
Utf8Builder | |
Fields |
Instances
IsString Utf8Builder | Since: rio-0.1.0.0 |
Defined in RIO.Prelude.Display Methods fromString :: String -> Utf8Builder # | |
Semigroup Utf8Builder | |
Defined in RIO.Prelude.Display Methods (<>) :: Utf8Builder -> Utf8Builder -> Utf8Builder # sconcat :: NonEmpty Utf8Builder -> Utf8Builder # stimes :: Integral b => b -> Utf8Builder -> Utf8Builder # | |
Monoid Utf8Builder | |
Defined in RIO.Prelude.Display Methods mempty :: Utf8Builder # mappend :: Utf8Builder -> Utf8Builder -> Utf8Builder # mconcat :: [Utf8Builder] -> Utf8Builder # | |
Display Utf8Builder | Since: rio-0.1.0.0 |
Defined in RIO.Prelude.Display Methods display :: Utf8Builder -> Utf8Builder # |
A typeclass for values which can be converted to a
Utf8Builder
. The intention of this typeclass is to provide a
human-friendly display of the data.
Since: rio-0.1.0.0
Methods
display :: a -> Utf8Builder #
Instances
Boxed vectors, supporting efficient slicing.
Instances
class (Vector Vector a, MVector MVector a) => Unbox a #
Instances
A set of values. A set cannot contain duplicate values.
Instances
Foldable HashSet | |
Defined in Data.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 # | |
ToJSON1 HashSet | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> HashSet a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [HashSet a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> HashSet a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [HashSet a] -> Encoding # | |
Eq1 HashSet | |
Ord1 HashSet | |
Defined in Data.HashSet | |
Show1 HashSet | |
Hashable1 HashSet | |
Defined in Data.HashSet | |
(Eq a, Hashable a) => IsList (HashSet a) | |
Eq a => Eq (HashSet a) | |
(Data a, Eq a, Hashable a) => Data (HashSet a) | |
Defined in Data.HashSet Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashSet a -> c (HashSet a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashSet a) # toConstr :: HashSet a -> Constr # dataTypeOf :: HashSet a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HashSet a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashSet a)) # gmapT :: (forall b. Data b => b -> b) -> HashSet a -> HashSet a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashSet a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashSet a -> r # gmapQ :: (forall d. Data d => d -> u) -> HashSet a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HashSet a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # | |
Ord a => Ord (HashSet a) | |
(Eq a, Hashable a, Read a) => Read (HashSet a) | |
Show a => Show (HashSet a) | |
(Hashable a, Eq a) => Semigroup (HashSet a) | |
(Hashable a, Eq a) => Monoid (HashSet a) | |
NFData a => NFData (HashSet a) | |
Defined in Data.HashSet | |
Hashable a => Hashable (HashSet a) | |
Defined in Data.HashSet | |
ToJSON a => ToJSON (HashSet a) | |
Defined in Data.Aeson.Types.ToJSON | |
(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) | |
(Eq element, Hashable element) => SetContainer (HashSet element) | |
Defined in Data.Containers Associated Types type ContainerKey (HashSet element) :: Type # Methods member :: ContainerKey (HashSet element) -> HashSet element -> Bool # notMember :: ContainerKey (HashSet element) -> HashSet element -> Bool # union :: HashSet element -> HashSet element -> HashSet element # unions :: (MonoFoldable mono, Element mono ~ HashSet element) => mono -> HashSet element # difference :: HashSet element -> HashSet element -> HashSet element # intersection :: HashSet element -> HashSet element -> HashSet element # keys :: HashSet element -> [ContainerKey (HashSet element)] # | |
(Eq element, Hashable element) => IsSet (HashSet element) | |
Defined in Data.Containers Methods insertSet :: Element (HashSet element) -> HashSet element -> HashSet element # deleteSet :: Element (HashSet element) -> HashSet element -> HashSet element # singletonSet :: Element (HashSet element) -> HashSet element # setFromList :: [Element (HashSet element)] -> HashSet element # setToList :: HashSet element -> [Element (HashSet element)] # | |
MonoFoldable (HashSet e) | |
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element (HashSet e) -> m) -> HashSet e -> m # ofoldr :: (Element (HashSet e) -> b -> b) -> b -> HashSet e -> b # ofoldl' :: (a -> Element (HashSet e) -> a) -> a -> HashSet e -> a # otoList :: HashSet e -> [Element (HashSet e)] # oall :: (Element (HashSet e) -> Bool) -> HashSet e -> Bool # oany :: (Element (HashSet e) -> Bool) -> HashSet e -> Bool # olength64 :: HashSet e -> Int64 # ocompareLength :: Integral i => HashSet e -> i -> Ordering # otraverse_ :: Applicative f => (Element (HashSet e) -> f b) -> HashSet e -> f () # ofor_ :: Applicative f => HashSet e -> (Element (HashSet e) -> f b) -> f () # omapM_ :: Applicative m => (Element (HashSet e) -> m ()) -> HashSet e -> m () # oforM_ :: Applicative m => HashSet e -> (Element (HashSet e) -> m ()) -> m () # ofoldlM :: Monad m => (a -> Element (HashSet e) -> m a) -> a -> HashSet e -> m a # ofoldMap1Ex :: Semigroup m => (Element (HashSet e) -> m) -> HashSet e -> m # ofoldr1Ex :: (Element (HashSet e) -> Element (HashSet e) -> Element (HashSet e)) -> HashSet e -> Element (HashSet e) # ofoldl1Ex' :: (Element (HashSet e) -> Element (HashSet e) -> Element (HashSet e)) -> HashSet e -> Element (HashSet e) # headEx :: HashSet e -> Element (HashSet e) # lastEx :: HashSet e -> Element (HashSet e) # unsafeHead :: HashSet e -> Element (HashSet e) # unsafeLast :: HashSet e -> Element (HashSet e) # maximumByEx :: (Element (HashSet e) -> Element (HashSet e) -> Ordering) -> HashSet e -> Element (HashSet e) # minimumByEx :: (Element (HashSet e) -> Element (HashSet e) -> Ordering) -> HashSet e -> Element (HashSet e) # | |
Hashable a => MonoPointed (HashSet a) | |
(Eq v, Hashable v) => GrowingAppend (HashSet v) | |
Defined in Data.MonoTraversable | |
ToMustache ω => ToMustache (HashSet ω) | |
Defined in Text.Mustache.Internal.Types | |
type Item (HashSet a) | |
Defined in Data.HashSet | |
type ContainerKey (HashSet element) | |
Defined in Data.Containers | |
type Element (HashSet e) | |
Defined in Data.MonoTraversable |
myThreadId :: MonadIO m => m ThreadId #
Lifted version of myThreadId
.
Since: unliftio-0.1.1.0
threadDelay :: MonadIO m => Int -> m () #
Lifted version of threadDelay
.
Since: unliftio-0.1.1.0
threadWaitRead :: MonadIO m => Fd -> m () #
Lifted version of threadWaitRead
.
Since: unliftio-0.1.1.0
threadWaitWrite :: MonadIO m => Fd -> m () #
Lifted version of threadWaitWrite
.
Since: unliftio-0.1.1.0
isCurrentThreadBound :: MonadIO m => m Bool #
Lifted version of isCurrentThreadBound
.
Since: unliftio-0.1.1.0
data UnicodeException #
An exception type for representing Unicode encoding errors.
Constructors
DecodeError String (Maybe Word8) | Could not decode a byte sequence because it was invalid under the given encoding, or ran out of input in mid-decode. |
EncodeError String (Maybe Char) | Tried to encode a character that could not be represented under the given encoding, or ran out of input in mid-encode. |
Instances
Eq UnicodeException | |
Defined in Data.Text.Encoding.Error Methods (==) :: UnicodeException -> UnicodeException -> Bool # (/=) :: UnicodeException -> UnicodeException -> Bool # | |
Show UnicodeException | |
Defined in Data.Text.Encoding.Error Methods showsPrec :: Int -> UnicodeException -> ShowS # show :: UnicodeException -> String # showList :: [UnicodeException] -> ShowS # | |
NFData UnicodeException | |
Defined in Data.Text.Encoding.Error Methods rnf :: UnicodeException -> () # | |
Exception UnicodeException | |
Defined in Data.Text.Encoding.Error Methods toException :: UnicodeException -> SomeException # |
lenientDecode :: OnDecodeError #
Replace an invalid input byte with the Unicode replacement character U+FFFD.
decodeUtf8With :: OnDecodeError -> ByteString -> Text #
Decode a ByteString
containing UTF-8 encoded text.
NOTE: The replacement character returned by OnDecodeError
MUST be within the BMP plane; surrogate code points will
automatically be remapped to the replacement char U+FFFD
(since 0.11.3.0), whereas code points beyond the BMP will throw an
error
(since 1.2.3.1); For earlier versions of text
using
those unsupported code points would result in undefined behavior.
decodeUtf8' :: ByteString -> Either UnicodeException Text #
Decode a ByteString
containing UTF-8 encoded text.
If the input contains any invalid UTF-8 data, the relevant exception will be returned, otherwise the decoded text.
encodeUtf8Builder :: Text -> Builder #
Encode text to a ByteString Builder
using UTF-8 encoding.
Since: text-1.1.0.0
encodeUtf8 :: Text -> ByteString #
Encode text using UTF-8 encoding.
The Store
typeclass provides efficient serialization and
deserialization to raw pointer addresses.
The peek
and poke
methods should be defined such that
decodeEx (encode x) == x
.