nvim-hs-2.3.2.1: Haskell plugin backend for neovim
Copyright(c) Sebastian Witte
LicenseApache-2.0
Maintainerwoozletoff@gmail.com
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Neovim.Classes

Description

 
Synopsis

Documentation

class NFData o => NvimObject o where Source #

Conversion from Object files to Haskell types and back with respect to neovim's interpretation.

The NFData constraint has been added to allow forcing results of function evaluations in order to catch exceptions from pure code. This adds more stability to the plugin provider and seems to be a cleaner approach.

Minimal complete definition

toObject, (fromObject | fromObjectUnsafe)

Instances

Instances details
NvimObject Int16 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Int32 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Int64 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Int8 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Word16 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Word32 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Word64 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Word8 Source # 
Instance details

Defined in Neovim.Classes

NvimObject ByteString Source # 
Instance details

Defined in Neovim.Classes

NvimObject Object Source # 
Instance details

Defined in Neovim.Classes

NvimObject Buffer Source # 
Instance details

Defined in Neovim.API.ByteString

NvimObject NeovimExceptionGen Source # 
Instance details

Defined in Neovim.API.ByteString

NvimObject Tabpage Source # 
Instance details

Defined in Neovim.API.ByteString

NvimObject Window Source # 
Instance details

Defined in Neovim.API.ByteString

NvimObject Buffer Source # 
Instance details

Defined in Neovim.API.String

NvimObject NeovimExceptionGen Source # 
Instance details

Defined in Neovim.API.String

NvimObject Tabpage Source # 
Instance details

Defined in Neovim.API.String

NvimObject Window Source # 
Instance details

Defined in Neovim.API.String

NvimObject Buffer Source # 
Instance details

Defined in Neovim.API.Text

NvimObject NeovimExceptionGen Source # 
Instance details

Defined in Neovim.API.Text

NvimObject Tabpage Source # 
Instance details

Defined in Neovim.API.Text

NvimObject Window Source # 
Instance details

Defined in Neovim.API.Text

NvimObject AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

NvimObject QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

NvimObject Message Source # 
Instance details

Defined in Neovim.RPC.Classes

NvimObject Text Source # 
Instance details

Defined in Neovim.Classes

NvimObject Integer Source # 
Instance details

Defined in Neovim.Classes

NvimObject () Source # 
Instance details

Defined in Neovim.Classes

NvimObject Bool Source # 
Instance details

Defined in Neovim.Classes

NvimObject Double Source # 
Instance details

Defined in Neovim.Classes

NvimObject Int Source # 
Instance details

Defined in Neovim.Classes

NvimObject Word Source # 
Instance details

Defined in Neovim.Classes

(Monoid strType, NvimObject strType) => NvimObject (QuickfixListItem strType) Source # 
Instance details

Defined in Neovim.Quickfix

NvimObject o => NvimObject (Vector o) Source # 
Instance details

Defined in Neovim.Classes

NvimObject o => NvimObject (Maybe o) Source # 
Instance details

Defined in Neovim.Classes

NvimObject [Char] Source # 
Instance details

Defined in Neovim.Classes

NvimObject o => NvimObject [o] Source # 
Instance details

Defined in Neovim.Classes

(NvimObject l, NvimObject r) => NvimObject (Either l r) Source #

Right-biased instance for toObject.

Instance details

Defined in Neovim.Classes

(Ord key, NvimObject key, NvimObject val) => NvimObject (Map key val) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: Map key val -> Object Source #

fromObjectUnsafe :: Object -> Map key val Source #

fromObject :: Object -> Either (Doc AnsiStyle) (Map key val) Source #

fromObject' :: MonadIO io => Object -> io (Map key val) Source #

(NvimObject o1, NvimObject o2) => NvimObject (o1, o2) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2) Source #

(NvimObject o1, NvimObject o2, NvimObject o3) => NvimObject (o1, o2, o3) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2, o3) Source #

(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4) => NvimObject (o1, o2, o3, o4) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2, o3, o4) Source #

(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5) => NvimObject (o1, o2, o3, o4, o5) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4, o5) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4, o5) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4, o5) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2, o3, o4, o5) Source #

(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5, NvimObject o6) => NvimObject (o1, o2, o3, o4, o5, o6) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4, o5, o6) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4, o5, o6) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4, o5, o6) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2, o3, o4, o5, o6) Source #

(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5, NvimObject o6, NvimObject o7) => NvimObject (o1, o2, o3, o4, o5, o6, o7) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4, o5, o6, o7) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4, o5, o6, o7) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4, o5, o6, o7) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2, o3, o4, o5, o6, o7) Source #

(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5, NvimObject o6, NvimObject o7, NvimObject o8) => NvimObject (o1, o2, o3, o4, o5, o6, o7, o8) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4, o5, o6, o7, o8) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4, o5, o6, o7, o8) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4, o5, o6, o7, o8) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2, o3, o4, o5, o6, o7, o8) Source #

(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5, NvimObject o6, NvimObject o7, NvimObject o8, NvimObject o9) => NvimObject (o1, o2, o3, o4, o5, o6, o7, o8, o9) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4, o5, o6, o7, o8, o9) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4, o5, o6, o7, o8, o9) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4, o5, o6, o7, o8, o9) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2, o3, o4, o5, o6, o7, o8, o9) Source #

type Dictionary = Map ByteString Object Source #

A generic vim dictionary is a simply a map from strings to objects. This type alias is sometimes useful as a type annotation especially if the OverloadedStrings extension is enabled.

(+:) :: NvimObject o => o -> [Object] -> [Object] infixr 5 Source #

Convenient operator to create a list of Object from normal values. values +: of :+ different :+ types :+ can +: be +: combined +: this +: way +: []

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances

Instances details
Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Version 
Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic Void 
Instance details

Defined in Data.Void

Associated Types

type Rep Void :: Type -> Type #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Fingerprint 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fingerprint :: Type -> Type #

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type #

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic CCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep CCFlags :: Type -> Type #

Methods

from :: CCFlags -> Rep CCFlags x #

to :: Rep CCFlags x -> CCFlags #

Generic ConcFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ConcFlags :: Type -> Type #

Generic DebugFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DebugFlags :: Type -> Type #

Generic DoCostCentres 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoCostCentres :: Type -> Type #

Generic DoHeapProfile 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoHeapProfile :: Type -> Type #

Generic DoTrace 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoTrace :: Type -> Type #

Methods

from :: DoTrace -> Rep DoTrace x #

to :: Rep DoTrace x -> DoTrace #

Generic GCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GCFlags :: Type -> Type #

Methods

from :: GCFlags -> Rep GCFlags x #

to :: Rep GCFlags x -> GCFlags #

Generic GiveGCStats 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GiveGCStats :: Type -> Type #

Generic MiscFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep MiscFlags :: Type -> Type #

Generic ParFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ParFlags :: Type -> Type #

Methods

from :: ParFlags -> Rep ParFlags x #

to :: Rep ParFlags x -> ParFlags #

Generic ProfFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ProfFlags :: Type -> Type #

Generic RTSFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep RTSFlags :: Type -> Type #

Methods

from :: RTSFlags -> Rep RTSFlags x #

to :: Rep RTSFlags x -> RTSFlags #

Generic TickyFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TickyFlags :: Type -> Type #

Generic TraceFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TraceFlags :: Type -> Type #

Generic SrcLoc 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SrcLoc :: Type -> Type #

Methods

from :: SrcLoc -> Rep SrcLoc x #

to :: Rep SrcLoc x -> SrcLoc #

Generic GeneralCategory 
Instance details

Defined in GHC.Generics

Associated Types

type Rep GeneralCategory :: Type -> Type #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type #

Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic Priority 
Instance details

Defined in System.Log

Associated Types

type Rep Priority :: Type -> Type #

Methods

from :: Priority -> Rep Priority x #

to :: Rep Priority x -> Priority #

Generic InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep InvalidPosException :: Type -> Type #

Generic Pos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep Pos :: Type -> Type #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePos :: Type -> Type #

Generic Object 
Instance details

Defined in Data.MessagePack

Associated Types

type Rep Object :: Type -> Type #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

Generic Buffer Source # 
Instance details

Defined in Neovim.API.ByteString

Associated Types

type Rep Buffer :: Type -> Type #

Methods

from :: Buffer -> Rep Buffer x #

to :: Rep Buffer x -> Buffer #

Generic NeovimExceptionGen Source # 
Instance details

Defined in Neovim.API.ByteString

Associated Types

type Rep NeovimExceptionGen :: Type -> Type #

Generic Tabpage Source # 
Instance details

Defined in Neovim.API.ByteString

Associated Types

type Rep Tabpage :: Type -> Type #

Methods

from :: Tabpage -> Rep Tabpage x #

to :: Rep Tabpage x -> Tabpage #

Generic Window Source # 
Instance details

Defined in Neovim.API.ByteString

Associated Types

type Rep Window :: Type -> Type #

Methods

from :: Window -> Rep Window x #

to :: Rep Window x -> Window #

Generic Buffer Source # 
Instance details

Defined in Neovim.API.String

Associated Types

type Rep Buffer :: Type -> Type #

Methods

from :: Buffer -> Rep Buffer x #

to :: Rep Buffer x -> Buffer #

Generic NeovimExceptionGen Source # 
Instance details

Defined in Neovim.API.String

Associated Types

type Rep NeovimExceptionGen :: Type -> Type #

Generic Tabpage Source # 
Instance details

Defined in Neovim.API.String

Associated Types

type Rep Tabpage :: Type -> Type #

Methods

from :: Tabpage -> Rep Tabpage x #

to :: Rep Tabpage x -> Tabpage #

Generic Window Source # 
Instance details

Defined in Neovim.API.String

Associated Types

type Rep Window :: Type -> Type #

Methods

from :: Window -> Rep Window x #

to :: Rep Window x -> Window #

Generic Buffer Source # 
Instance details

Defined in Neovim.API.Text

Associated Types

type Rep Buffer :: Type -> Type #

Methods

from :: Buffer -> Rep Buffer x #

to :: Rep Buffer x -> Buffer #

Generic NeovimExceptionGen Source # 
Instance details

Defined in Neovim.API.Text

Associated Types

type Rep NeovimExceptionGen :: Type -> Type #

Generic Tabpage Source # 
Instance details

Defined in Neovim.API.Text

Associated Types

type Rep Tabpage :: Type -> Type #

Methods

from :: Tabpage -> Rep Tabpage x #

to :: Rep Tabpage x -> Tabpage #

Generic Window Source # 
Instance details

Defined in Neovim.API.Text

Associated Types

type Rep Window :: Type -> Type #

Methods

from :: Window -> Rep Window x #

to :: Rep Window x -> Window #

Generic AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep AutocmdOptions :: Type -> Type #

Generic CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep CommandArguments :: Type -> Type #

Generic CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep CommandOption :: Type -> Type #

Generic CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep CommandOptions :: Type -> Type #

Generic FunctionName Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep FunctionName :: Type -> Type #

Generic FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep FunctionalityDescription :: Type -> Type #

Generic NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep NeovimEventId :: Type -> Type #

Generic NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep NvimMethod :: Type -> Type #

Generic RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep RangeSpecification :: Type -> Type #

Generic Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep Synchronous :: Type -> Type #

Generic FunctionCall Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Associated Types

type Rep FunctionCall :: Type -> Type #

Generic Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Associated Types

type Rep Notification :: Type -> Type #

Generic Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Associated Types

type Rep Request :: Type -> Type #

Methods

from :: Request -> Rep Request x #

to :: Rep Request x -> Request #

Generic ColumnNumber Source # 
Instance details

Defined in Neovim.Quickfix

Associated Types

type Rep ColumnNumber :: Type -> Type #

Generic QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

Associated Types

type Rep QuickfixAction :: Type -> Type #

Generic QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

Associated Types

type Rep QuickfixErrorType :: Type -> Type #

Generic Message Source # 
Instance details

Defined in Neovim.RPC.Classes

Associated Types

type Rep Message :: Type -> Type #

Methods

from :: Message -> Rep Message x #

to :: Rep Message x -> Message #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

Generic TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetails :: Type -> Type #

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc :: Type -> Type #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: Type -> Type #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: Type -> Type #

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body :: Type -> Type #

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Generic Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bytes :: Type -> Type #

Methods

from :: Bytes -> Rep Bytes x #

to :: Rep Bytes x -> Bytes #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv :: Type -> Type #

Methods

from :: Callconv -> Rep Callconv x #

to :: Rep Callconv x -> Callconv #

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause :: Type -> Type #

Methods

from :: Clause -> Rep Clause x #

to :: Rep Clause x -> Clause #

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Con :: Type -> Type #

Methods

from :: Con -> Rep Con x #

to :: Rep Con x -> Con #

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Dec :: Type -> Type #

Methods

from :: Dec -> Rep Dec x #

to :: Rep Dec x -> Dec #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type #

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type #

Generic DocLoc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DocLoc :: Type -> Type #

Methods

from :: DocLoc -> Rep DocLoc x #

to :: Rep DocLoc x -> DocLoc #

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Exp :: Type -> Type #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig :: Type -> Type #

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityDirection :: Type -> Type #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: Type -> Type #

Methods

from :: Foreign -> Rep Foreign x #

to :: Rep Foreign x -> Foreign #

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep :: Type -> Type #

Methods

from :: FunDep -> Rep FunDep x #

to :: Rep FunDep x -> FunDep #

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Guard :: Type -> Type #

Methods

from :: Guard -> Rep Guard x #

to :: Rep Guard x -> Guard #

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Info :: Type -> Type #

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: Type -> Type #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: Type -> Type #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Lit :: Type -> Type #

Methods

from :: Lit -> Rep Lit x #

to :: Rep Lit x -> Lit #

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Loc :: Type -> Type #

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Match :: Type -> Type #

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName :: Type -> Type #

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module :: Type -> Type #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo :: Type -> Type #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavour :: Type -> Type #

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace :: Type -> Type #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: Type -> Type #

Methods

from :: OccName -> Rep OccName x #

to :: Rep OccName x -> OccName #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type #

Methods

from :: Overlap -> Rep Overlap x #

to :: Rep Overlap x -> Overlap #

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pat :: Type -> Type #

Methods

from :: Pat -> Rep Pat x #

to :: Rep Pat x -> Pat #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type #

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: Type -> Type #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: Type -> Type #

Methods

from :: Phases -> Rep Phases x #

to :: Rep Phases x -> Phases #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName :: Type -> Type #

Methods

from :: PkgName -> Rep PkgName x #

to :: Rep PkgName x -> PkgName #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma :: Type -> Type #

Methods

from :: Pragma -> Rep Pragma x #

to :: Rep Pragma x -> Pragma #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Range :: Type -> Type #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role :: Type -> Type #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr :: Type -> Type #

Methods

from :: RuleBndr -> Rep RuleBndr x #

to :: Rep RuleBndr x -> RuleBndr #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch :: Type -> Type #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: Type -> Type #

Methods

from :: Safety -> Rep Safety x #

to :: Rep Safety x -> Safety #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Specificity :: Type -> Type #

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Stmt :: Type -> Type #

Methods

from :: Stmt -> Rep Stmt x #

to :: Rep Stmt x -> Stmt #

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLit :: Type -> Type #

Methods

from :: TyLit -> Rep TyLit x #

to :: Rep TyLit x -> TyLit #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: Type -> Type #

Methods

from :: TySynEqn -> Rep TySynEqn x #

to :: Rep TySynEqn x -> TySynEqn #

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: Type -> Type #

Generic ConcException 
Instance details

Defined in UnliftIO.Internals.Async

Associated Types

type Rep ConcException :: Type -> Type #

Generic () 
Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type #

Methods

from :: () -> Rep () x #

to :: Rep () x -> () #

Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic (ZipList a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (ZipList a) :: Type -> Type #

Methods

from :: ZipList a -> Rep (ZipList a) x #

to :: Rep (ZipList a) x -> ZipList a #

Generic (Complex a) 
Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a) :: Type -> Type #

Methods

from :: Complex a -> Rep (Complex a) x #

to :: Rep (Complex a) x -> Complex a #

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: Type -> Type #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) :: Type -> Type #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a) :: Type -> Type #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (Down a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type #

Methods

from :: Down a -> Rep (Down a) x #

to :: Rep (Down a) x -> Down a #

Generic (First a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (First a) :: Type -> Type #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Last a) :: Type -> Type #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (Max a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a) :: Type -> Type #

Methods

from :: Max a -> Rep (Max a) x #

to :: Rep (Max a) x -> Max a #

Generic (Min a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a) :: Type -> Type #

Methods

from :: Min a -> Rep (Min a) x #

to :: Rep (Min a) x -> Min a #

Generic (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m) :: Type -> Type #

Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) :: Type -> Type #

Methods

from :: Dual a -> Rep (Dual a) x #

to :: Rep (Dual a) x -> Dual a #

Generic (Endo a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a) :: Type -> Type #

Methods

from :: Endo a -> Rep (Endo a) x #

to :: Rep (Endo a) x -> Endo a #

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: Type -> Type #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: Type -> Type #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Generic (Par1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p) :: Type -> Type #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (Digit a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Digit a) :: Type -> Type #

Methods

from :: Digit a -> Rep (Digit a) x #

to :: Rep (Digit a) x -> Digit a #

Generic (Elem a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Elem a) :: Type -> Type #

Methods

from :: Elem a -> Rep (Elem a) x #

to :: Rep (Elem a) x -> Elem a #

Generic (FingerTree a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (FingerTree a) :: Type -> Type #

Methods

from :: FingerTree a -> Rep (FingerTree a) x #

to :: Rep (FingerTree a) x -> FingerTree a #

Generic (Node a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Node a) :: Type -> Type #

Methods

from :: Node a -> Rep (Node a) x #

to :: Rep (Node a) x -> Node a #

Generic (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewL a) :: Type -> Type #

Methods

from :: ViewL a -> Rep (ViewL a) x #

to :: Rep (ViewL a) x -> ViewL a #

Generic (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewR a) :: Type -> Type #

Methods

from :: ViewR a -> Rep (ViewR a) x #

to :: Rep (ViewR a) x -> ViewR a #

Generic (Tree a) 
Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) :: Type -> Type #

Methods

from :: Tree a -> Rep (Tree a) x #

to :: Rep (Tree a) x -> Tree a #

Generic (ErrorFancy e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ErrorFancy e) :: Type -> Type #

Methods

from :: ErrorFancy e -> Rep (ErrorFancy e) x #

to :: Rep (ErrorFancy e) x -> ErrorFancy e #

Generic (ErrorItem t) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ErrorItem t) :: Type -> Type #

Methods

from :: ErrorItem t -> Rep (ErrorItem t) x #

to :: Rep (ErrorItem t) x -> ErrorItem t #

Generic (PosState s) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

type Rep (PosState s) :: Type -> Type #

Methods

from :: PosState s -> Rep (PosState s) x #

to :: Rep (PosState s) x -> PosState s #

Generic (QuickfixListItem strType) Source # 
Instance details

Defined in Neovim.Quickfix

Associated Types

type Rep (QuickfixListItem strType) :: Type -> Type #

Methods

from :: QuickfixListItem strType -> Rep (QuickfixListItem strType) x #

to :: Rep (QuickfixListItem strType) x -> QuickfixListItem strType #

Generic (SignLocation strType) Source # 
Instance details

Defined in Neovim.Quickfix

Associated Types

type Rep (SignLocation strType) :: Type -> Type #

Methods

from :: SignLocation strType -> Rep (SignLocation strType) x #

to :: Rep (SignLocation strType) x -> SignLocation strType #

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep (Doc a) :: Type -> Type #

Methods

from :: Doc a -> Rep (Doc a) x #

to :: Rep (Doc a) x -> Doc a #

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (Doc ann) :: Type -> Type #

Methods

from :: Doc ann -> Rep (Doc ann) x #

to :: Rep (Doc ann) x -> Doc ann #

Generic (SimpleDocStream ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (SimpleDocStream ann) :: Type -> Type #

Methods

from :: SimpleDocStream ann -> Rep (SimpleDocStream ann) x #

to :: Rep (SimpleDocStream ann) x -> SimpleDocStream ann #

Generic (TyVarBndr flag) 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep (TyVarBndr flag) :: Type -> Type #

Methods

from :: TyVarBndr flag -> Rep (TyVarBndr flag) x #

to :: Rep (TyVarBndr flag) x -> TyVarBndr flag #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a) :: Type -> Type #

Methods

from :: (a) -> Rep (a) x #

to :: Rep (a) x -> (a) #

Generic [a] 
Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] :: Type -> Type #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (WrappedMonad m a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedMonad m a) :: Type -> Type #

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a #

Generic (Either a b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) :: Type -> Type #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Generic (Arg a b) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b) :: Type -> Type #

Methods

from :: Arg a b -> Rep (Arg a b) x #

to :: Rep (Arg a b) x -> Arg a b #

Generic (U1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) :: Type -> Type #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (V1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p) :: Type -> Type #

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (ParseError s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ParseError s e) :: Type -> Type #

Methods

from :: ParseError s e -> Rep (ParseError s e) x #

to :: Rep (ParseError s e) x -> ParseError s e #

Generic (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ParseErrorBundle s e) :: Type -> Type #

Generic (State s e) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

type Rep (State s e) :: Type -> Type #

Methods

from :: State s e -> Rep (State s e) x #

to :: Rep (State s e) x -> State s e #

Generic (a, b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b) :: Type -> Type #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (WrappedArrow a b c) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedArrow a b c) :: Type -> Type #

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c #

Generic (Kleisli m a b) 
Instance details

Defined in Control.Arrow

Associated Types

type Rep (Kleisli m a b) :: Type -> Type #

Methods

from :: Kleisli m a b -> Rep (Kleisli m a b) x #

to :: Rep (Kleisli m a b) x -> Kleisli m a b #

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: Type -> Type #

Methods

from :: Const a b -> Rep (Const a b) x #

to :: Rep (Const a b) x -> Const a b #

Generic (Ap f a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type #

Methods

from :: Ap f a -> Rep (Ap f a) x #

to :: Rep (Ap f a) x -> Ap f a #

Generic (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: Type -> Type #

Methods

from :: Alt f a -> Rep (Alt f a) x #

to :: Rep (Alt f a) x -> Alt f a #

Generic (Rec1 f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p) :: Type -> Type #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

Generic (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

Generic (URec Char p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

Generic (URec Double p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

Generic (URec Int p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

Generic (URec Word p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (a, b, c) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c) :: Type -> Type #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) :: Type -> Type #

Methods

from :: Product f g a -> Rep (Product f g a) x #

to :: Rep (Product f g a) x -> Product f g a #

Generic (Sum f g a) 
Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep (Sum f g a) :: Type -> Type #

Methods

from :: Sum f g a -> Rep (Sum f g a) x #

to :: Rep (Sum f g a) x -> Sum f g a #

Generic ((f :*: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: Type -> Type #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic ((f :+: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: Type -> Type #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic (K1 i c p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p) :: Type -> Type #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic (a, b, c, d) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d) :: Type -> Type #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (Compose f g a) 
Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep (Compose f g a) :: Type -> Type #

Methods

from :: Compose f g a -> Rep (Compose f g a) x #

to :: Rep (Compose f g a) x -> Compose f g a #

Generic ((f :.: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p) :: Type -> Type #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (M1 i c f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) :: Type -> Type #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic (a, b, c, d, e) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e) :: Type -> Type #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (a, b, c, d, e, f) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #

Generic (a, b, c, d, e, f, g, h) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h) -> Rep (a, b, c, d, e, f, g, h) x #

to :: Rep (a, b, c, d, e, f, g, h) x -> (a, b, c, d, e, f, g, h) #

Generic (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i) -> Rep (a, b, c, d, e, f, g, h, i) x #

to :: Rep (a, b, c, d, e, f, g, h, i) x -> (a, b, c, d, e, f, g, h, i) #

Generic (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j) -> Rep (a, b, c, d, e, f, g, h, i, j) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j) x -> (a, b, c, d, e, f, g, h, i, j) #

Generic (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k) -> Rep (a, b, c, d, e, f, g, h, i, j, k) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k) x -> (a, b, c, d, e, f, g, h, i, j, k) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l) x -> (a, b, c, d, e, f, g, h, i, j, k, l) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

docToObject :: Doc AnsiStyle -> Object Source #

Convert a Doc-ument to a messagepack Object. This is more a convenience method to transport error message from and to neovim. It generally does not hold that 'docToObject . docFromObject' = id.

data Doc ann #

The abstract data type Doc ann represents pretty documents that have been annotated with data of type ann.

More specifically, a value of type Doc represents a non-empty set of possible layouts of a document. The layout functions select one of these possibilities, taking into account things like the width of the output document.

The annotation is an arbitrary piece of data associated with (part of) a document. Annotations may be used by the rendering backends in order to display output differently, such as

  • color information (e.g. when rendering to the terminal)
  • mouseover text (e.g. when rendering to rich HTML)
  • whether to show something or not (to allow simple or detailed versions)

The simplest way to display a Doc is via the Show class.

>>> putStrLn (show (vsep ["hello", "world"]))
hello
world

Instances

Instances details
Functor Doc

Alter the document’s annotations.

This instance makes Doc more flexible (because it can be used in Functor-polymorphic values), but fmap is much less readable compared to using reAnnotate in code that only works for Doc anyway. Consider using the latter when the type does not matter.

Instance details

Defined in Prettyprinter.Internal

Methods

fmap :: (a -> b) -> Doc a -> Doc b #

(<$) :: a -> Doc b -> Doc a #

IsString (Doc ann)
>>> pretty ("hello\nworld")
hello
world

This instance uses the Pretty Doc instance, and uses the same newline to line conversion.

Instance details

Defined in Prettyprinter.Internal

Methods

fromString :: String -> Doc ann #

Monoid (Doc ann)
mempty = emptyDoc
mconcat = hcat
>>> mappend "hello" "world" :: Doc ann
helloworld
Instance details

Defined in Prettyprinter.Internal

Methods

mempty :: Doc ann #

mappend :: Doc ann -> Doc ann -> Doc ann #

mconcat :: [Doc ann] -> Doc ann #

Semigroup (Doc ann)
x <> y = hcat [x, y]
>>> "hello" <> "world" :: Doc ann
helloworld
Instance details

Defined in Prettyprinter.Internal

Methods

(<>) :: Doc ann -> Doc ann -> Doc ann #

sconcat :: NonEmpty (Doc ann) -> Doc ann #

stimes :: Integral b => b -> Doc ann -> Doc ann #

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (Doc ann) :: Type -> Type #

Methods

from :: Doc ann -> Rep (Doc ann) x #

to :: Rep (Doc ann) x -> Doc ann #

Show (Doc ann)

(show doc) prettyprints document doc with defaultLayoutOptions, ignoring all annotations.

Instance details

Defined in Prettyprinter.Internal

Methods

showsPrec :: Int -> Doc ann -> ShowS #

show :: Doc ann -> String #

showList :: [Doc ann] -> ShowS #

type Rep (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

type Rep (Doc ann) = D1 ('MetaData "Doc" "Prettyprinter.Internal" "prettyprinter-1.7.1-Fnq1Vt2JMTY81kvR0W9kdP" 'False) (((C1 ('MetaCons "Fail" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Char" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char)))) :+: (C1 ('MetaCons "Text" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "Line" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlatAlt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)))))) :+: ((C1 ('MetaCons "Cat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))) :+: (C1 ('MetaCons "Nest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))) :+: C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))))) :+: ((C1 ('MetaCons "Column" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int -> Doc ann))) :+: C1 ('MetaCons "WithPageWidth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PageWidth -> Doc ann)))) :+: (C1 ('MetaCons "Nesting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int -> Doc ann))) :+: C1 ('MetaCons "Annotated" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ann) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)))))))

data AnsiStyle #

Render the annotated document in a certain style. Styles not set in the annotation will use the style of the surrounding document, or the terminal’s default if none has been set yet.

style = color Green <> bold
styledDoc = annotate style "hello world"

Instances

Instances details
Monoid AnsiStyle

mempty does nothing, which is equivalent to inheriting the style of the surrounding doc, or the terminal’s default if no style has been set yet.

Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Semigroup AnsiStyle

Keep the first decision for each of foreground color, background color, boldness, italication, and underlining. If a certain style is not set, the terminal’s default will be used.

Example:

color Red <> color Green

is red because the first color wins, and not bold because (or if) that’s the terminal’s default.

Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Show AnsiStyle 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Eq AnsiStyle 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Ord AnsiStyle 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

class Pretty a where #

Overloaded conversion to Doc.

Laws:

  1. output should be pretty. :-)

Minimal complete definition

pretty

Methods

pretty :: a -> Doc ann #

>>> pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234

prettyList :: [a] -> Doc ann #

prettyList is only used to define the instance Pretty a => Pretty [a]. In normal circumstances only the pretty function is used.

>>> prettyList [1, 23, 456]
[1, 23, 456]

Instances

Instances details
Pretty Void

Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.

>>> pretty ([] :: [Void])
[]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Void -> Doc ann #

prettyList :: [Void] -> Doc ann #

Pretty Int16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Pretty Int32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Pretty Int64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Pretty Int8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Pretty Word16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Pretty Word32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Pretty Word64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Pretty Word8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Pretty FunctionType Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

pretty :: FunctionType -> Doc ann #

prettyList :: [FunctionType] -> Doc ann #

Pretty AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: AutocmdOptions -> Doc ann #

prettyList :: [AutocmdOptions] -> Doc ann #

Pretty CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: CommandOption -> Doc ann #

prettyList :: [CommandOption] -> Doc ann #

Pretty CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: CommandOptions -> Doc ann #

prettyList :: [CommandOptions] -> Doc ann #

Pretty FunctionName Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: FunctionName -> Doc ann #

prettyList :: [FunctionName] -> Doc ann #

Pretty FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: NeovimEventId -> Doc ann #

prettyList :: [NeovimEventId] -> Doc ann #

Pretty NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: NvimMethod -> Doc ann #

prettyList :: [NvimMethod] -> Doc ann #

Pretty RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: Synchronous -> Doc ann #

prettyList :: [Synchronous] -> Doc ann #

Pretty FunctionCall Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

pretty :: FunctionCall -> Doc ann #

prettyList :: [FunctionCall] -> Doc ann #

Pretty Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

pretty :: Notification -> Doc ann #

prettyList :: [Notification] -> Doc ann #

Pretty Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

pretty :: Request -> Doc ann #

prettyList :: [Request] -> Doc ann #

Pretty Message Source # 
Instance details

Defined in Neovim.RPC.Classes

Methods

pretty :: Message -> Doc ann #

prettyList :: [Message] -> Doc ann #

Pretty Text

Automatically converts all newlines to line.

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group:

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Text

(lazy Doc instance, identical to the strict version)

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Integer
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Integer -> Doc ann #

prettyList :: [Integer] -> Doc ann #

Pretty Natural 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Natural -> Doc ann #

prettyList :: [Natural] -> Doc ann #

Pretty ()
>>> pretty ()
()

The argument is not used:

>>> pretty (error "Strict?" :: ())
()
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: () -> Doc ann #

prettyList :: [()] -> Doc ann #

Pretty Bool
>>> pretty True
True
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Bool -> Doc ann #

prettyList :: [Bool] -> Doc ann #

Pretty Char

Instead of (pretty 'n'), consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Char -> Doc ann #

prettyList :: [Char] -> Doc ann #

Pretty Double
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Double -> Doc ann #

prettyList :: [Double] -> Doc ann #

Pretty Float
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Float -> Doc ann #

prettyList :: [Float] -> Doc ann #

Pretty Int
>>> pretty (123 :: Int)
123
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int -> Doc ann #

prettyList :: [Int] -> Doc ann #

Pretty Word 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Pretty a => Pretty (Identity a)
>>> pretty (Identity 1)
1
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Identity a -> Doc ann #

prettyList :: [Identity a] -> Doc ann #

Pretty a => Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: NonEmpty a -> Doc ann #

prettyList :: [NonEmpty a] -> Doc ann #

Pretty a => Pretty (Maybe a)

Ignore Nothings, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Maybe a -> Doc ann #

prettyList :: [Maybe a] -> Doc ann #

Pretty a => Pretty [a]
>>> pretty [1,2,3]
[1, 2, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: [a] -> Doc ann #

prettyList :: [[a]] -> Doc ann #

(Pretty a1, Pretty a2) => Pretty (a1, a2)
>>> pretty (123, "hello")
(123, hello)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2) -> Doc ann #

prettyList :: [(a1, a2)] -> Doc ann #

Pretty a => Pretty (Const a b) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Const a b -> Doc ann #

prettyList :: [Const a b] -> Doc ann #

(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3)
>>> pretty (123, "hello", False)
(123, hello, False)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann #

prettyList :: [(a1, a2, a3)] -> Doc ann #

(<+>) :: Doc ann -> Doc ann -> Doc ann infixr 6 #

(x <+> y) concatenates document x and y with a space in between.

>>> "hello" <+> "world"
hello world
x <+> y = x <> space <> y

data Int8 #

8-bit signed integer type

Instances

Instances details
Data Int8

Since: base-4.0.0.0

Instance details

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 #

toConstr :: Int8 -> Constr #

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 :: forall r r'. (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 #

Storable Int8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Bits Int8

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int8

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Bounded Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

succ :: Int8 -> Int8 #

pred :: Int8 -> Int8 #

toEnum :: Int -> Int8 #

fromEnum :: Int8 -> Int #

enumFrom :: Int8 -> [Int8] #

enumFromThen :: Int8 -> Int8 -> [Int8] #

enumFromTo :: Int8 -> Int8 -> [Int8] #

enumFromThenTo :: Int8 -> Int8 -> Int8 -> [Int8] #

Ix Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

range :: (Int8, Int8) -> [Int8] #

index :: (Int8, Int8) -> Int8 -> Int #

unsafeIndex :: (Int8, Int8) -> Int8 -> Int #

inRange :: (Int8, Int8) -> Int8 -> Bool #

rangeSize :: (Int8, Int8) -> Int #

unsafeRangeSize :: (Int8, Int8) -> Int #

Num Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(+) :: Int8 -> Int8 -> Int8 #

(-) :: Int8 -> Int8 -> Int8 #

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Read Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

quot :: Int8 -> Int8 -> Int8 #

rem :: Int8 -> Int8 -> Int8 #

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

quotRem :: Int8 -> Int8 -> (Int8, Int8) #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

toInteger :: Int8 -> Integer #

Real Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int8 -> Rational #

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Serialize Int8 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Int8 #

get :: Get Int8 #

Default Int8 
Instance details

Defined in Data.Default.Class

Methods

def :: Int8 #

NFData Int8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int8 -> () #

Eq Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int8 -> Int8 -> Bool #

(/=) :: Int8 -> Int8 -> Bool #

Ord Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int8 -> Int8 -> Ordering #

(<) :: Int8 -> Int8 -> Bool #

(<=) :: Int8 -> Int8 -> Bool #

(>) :: Int8 -> Int8 -> Bool #

(>=) :: Int8 -> Int8 -> Bool #

max :: Int8 -> Int8 -> Int8 #

min :: Int8 -> Int8 -> Int8 #

Hashable Int8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

NvimObject Int8 Source # 
Instance details

Defined in Neovim.Classes

Pretty Int8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Prim Int8 
Instance details

Defined in Data.Primitive.Types

Uniform Int8 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int8 #

UniformRange Int8 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int8, Int8) -> g -> m Int8 #

Unbox Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Int8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int8 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int8 -> Code m Int8 #

Vector Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 = MV_Int8 (MVector s Int8)

data Int16 #

16-bit signed integer type

Instances

Instances details
Data Int16

Since: base-4.0.0.0

Instance details

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 #

toConstr :: Int16 -> Constr #

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 :: forall r r'. (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 #

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Bits Int16

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int16

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Bounded Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int16 -> Rational #

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Serialize Int16 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Int16 #

get :: Get Int16 #

Default Int16 
Instance details

Defined in Data.Default.Class

Methods

def :: Int16 #

NFData Int16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int16 -> () #

Eq Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int16 -> Int16 -> Bool #

(/=) :: Int16 -> Int16 -> Bool #

Ord Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int16 -> Int16 -> Ordering #

(<) :: Int16 -> Int16 -> Bool #

(<=) :: Int16 -> Int16 -> Bool #

(>) :: Int16 -> Int16 -> Bool #

(>=) :: Int16 -> Int16 -> Bool #

max :: Int16 -> Int16 -> Int16 #

min :: Int16 -> Int16 -> Int16 #

Hashable Int16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

NvimObject Int16 Source # 
Instance details

Defined in Neovim.Classes

Pretty Int16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Prim Int16 
Instance details

Defined in Data.Primitive.Types

Uniform Int16 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int16 #

UniformRange Int16 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int16, Int16) -> g -> m Int16 #

Unbox Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Int16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int16 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int16 -> Code m Int16 #

Vector Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Int32 #

32-bit signed integer type

Instances

Instances details
Data Int32

Since: base-4.0.0.0

Instance details

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 #

toConstr :: Int32 -> Constr #

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 :: forall r r'. (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 #

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Bits Int32

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int32

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Bounded Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int32 -> Rational #

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Serialize Int32 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Int32 #

get :: Get Int32 #

Default Int32 
Instance details

Defined in Data.Default.Class

Methods

def :: Int32 #

NFData Int32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int32 -> () #

Eq Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int32 -> Int32 -> Bool #

(/=) :: Int32 -> Int32 -> Bool #

Ord Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int32 -> Int32 -> Ordering #

(<) :: Int32 -> Int32 -> Bool #

(<=) :: Int32 -> Int32 -> Bool #

(>) :: Int32 -> Int32 -> Bool #

(>=) :: Int32 -> Int32 -> Bool #

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Hashable Int32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

NvimObject Int32 Source # 
Instance details

Defined in Neovim.Classes

Pretty Int32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Prim Int32 
Instance details

Defined in Data.Primitive.Types

Uniform Int32 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int32 #

UniformRange Int32 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int32, Int32) -> g -> m Int32 #

Unbox Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Int32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int32 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int32 -> Code m Int32 #

Vector Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Int64 #

64-bit signed integer type

Instances

Instances details
Data Int64

Since: base-4.0.0.0

Instance details

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 #

toConstr :: Int64 -> Constr #

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 :: forall r r'. (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 #

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Bits Int64

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int64

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Bounded Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int64 -> Rational #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Serialize Int64 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Int64 #

get :: Get Int64 #

Default Int64 
Instance details

Defined in Data.Default.Class

Methods

def :: Int64 #

NFData Int64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int64 -> () #

Eq Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int64 -> Int64 -> Bool #

(/=) :: Int64 -> Int64 -> Bool #

Ord Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int64 -> Int64 -> Ordering #

(<) :: Int64 -> Int64 -> Bool #

(<=) :: Int64 -> Int64 -> Bool #

(>) :: Int64 -> Int64 -> Bool #

(>=) :: Int64 -> Int64 -> Bool #

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Hashable Int64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

NvimObject Int64 Source # 
Instance details

Defined in Neovim.Classes

Pretty Int64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Prim Int64 
Instance details

Defined in Data.Primitive.Types

Uniform Int64 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int64 #

UniformRange Int64 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int64, Int64) -> g -> m Int64 #

Unbox Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int64 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int64 -> Code m Int64 #

Vector Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word #

A Word is an unsigned integral type, with the same size as Int.

Instances

Instances details
Data Word

Since: base-4.0.0.0

Instance details

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 #

toConstr :: Word -> Constr #

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 :: forall r r'. (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 #

Storable Word

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

pokeElemOff :: Ptr Word -> Int -> Word -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word #

pokeByteOff :: Ptr b -> Int -> Word -> IO () #

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Bounded Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Word -> Word #

pred :: Word -> Word #

toEnum :: Int -> Word #

fromEnum :: Word -> Int #

enumFrom :: Word -> [Word] #

enumFromThen :: Word -> Word -> [Word] #

enumFromTo :: Word -> Word -> [Word] #

enumFromThenTo :: Word -> Word -> Word -> [Word] #

Ix Word

Since: base-4.6.0.0

Instance details

Defined in GHC.Ix

Methods

range :: (Word, Word) -> [Word] #

index :: (Word, Word) -> Word -> Int #

unsafeIndex :: (Word, Word) -> Word -> Int #

inRange :: (Word, Word) -> Word -> Bool #

rangeSize :: (Word, Word) -> Int #

unsafeRangeSize :: (Word, Word) -> Int #

Num Word

Since: base-2.1

Instance details

Defined in GHC.Num

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Read Word

Since: base-4.5.0.0

Instance details

Defined in GHC.Read

Integral Word

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

Real Word

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

toRational :: Word -> Rational #

Show Word

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Serialize Word 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Word #

get :: Get Word #

Default Word 
Instance details

Defined in Data.Default.Class

Methods

def :: Word #

NFData Word 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word -> () #

Eq Word 
Instance details

Defined in GHC.Classes

Methods

(==) :: Word -> Word -> Bool #

(/=) :: Word -> Word -> Bool #

Ord Word 
Instance details

Defined in GHC.Classes

Methods

compare :: Word -> Word -> Ordering #

(<) :: Word -> Word -> Bool #

(<=) :: Word -> Word -> Bool #

(>) :: Word -> Word -> Bool #

(>=) :: Word -> Word -> Bool #

max :: Word -> Word -> Word #

min :: Word -> Word -> Word #

Hashable Word 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

NvimObject Word Source # 
Instance details

Defined in Neovim.Classes

Pretty Word 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Prim Word 
Instance details

Defined in Data.Primitive.Types

Uniform Word 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word #

UniformRange Word 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word, Word) -> g -> m Word #

Unbox Word 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Word 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word -> Code m Word #

Vector Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

Generic1 (URec Word :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Word) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec Word a -> Rep1 (URec Word) a #

to1 :: forall (a :: k0). Rep1 (URec Word) a -> URec Word a #

Foldable (UWord :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UWord m -> m #

foldMap :: Monoid m => (a -> m) -> UWord a -> m #

foldMap' :: Monoid m => (a -> m) -> UWord a -> m #

foldr :: (a -> b -> b) -> b -> UWord a -> b #

foldr' :: (a -> b -> b) -> b -> UWord a -> b #

foldl :: (b -> a -> b) -> b -> UWord a -> b #

foldl' :: (b -> a -> b) -> b -> UWord a -> b #

foldr1 :: (a -> a -> a) -> UWord a -> a #

foldl1 :: (a -> a -> a) -> UWord a -> a #

toList :: UWord a -> [a] #

null :: UWord a -> Bool #

length :: UWord a -> Int #

elem :: Eq a => a -> UWord a -> Bool #

maximum :: Ord a => UWord a -> a #

minimum :: Ord a => UWord a -> a #

sum :: Num a => UWord a -> a #

product :: Num a => UWord a -> a #

Traversable (UWord :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UWord a -> f (UWord b) #

sequenceA :: Applicative f => UWord (f a) -> f (UWord a) #

mapM :: Monad m => (a -> m b) -> UWord a -> m (UWord b) #

sequence :: Monad m => UWord (m a) -> m (UWord a) #

Functor (URec Word :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b #

(<$) :: a -> URec Word b -> URec Word a #

Generic (URec Word p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Show (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

Eq (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Word p -> URec Word p -> Ordering #

(<) :: URec Word p -> URec Word p -> Bool #

(<=) :: URec Word p -> URec Word p -> Bool #

(>) :: URec Word p -> URec Word p -> Bool #

(>=) :: URec Word p -> URec Word p -> Bool #

max :: URec Word p -> URec Word p -> URec Word p #

min :: URec Word p -> URec Word p -> URec Word p #

newtype Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

data URec Word (p :: k)

Used for marking occurrences of Word#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Word (p :: k) = UWord {}
newtype MVector s Word 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word = MV_Word (MVector s Word)
type Rep1 (URec Word :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (URec Word :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: k -> Type)))
type Rep (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec Word p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: Type -> Type)))

data Word8 #

8-bit unsigned integer type

Instances

Instances details
Data Word8

Since: base-4.0.0.0

Instance details

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 #

toConstr :: Word8 -> Constr #

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 :: forall r r'. (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 #

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Bits Word8

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word8

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Serialize Word8 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Word8 #

get :: Get Word8 #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

def :: Word8 #

NFData Word8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word8 -> () #

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

(>=) :: Word8 -> Word8 -> Bool #

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

NvimObject Word8 Source # 
Instance details

Defined in Neovim.Classes

Pretty Word8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Uniform Word8 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word8 #

UniformRange Word8 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word8, Word8) -> g -> m Word8 #

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word8 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word8 -> Code m Word8 #

Vector Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word16 #

16-bit unsigned integer type

Instances

Instances details
Data Word16

Since: base-4.0.0.0

Instance details

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 :: forall r r'. (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 #

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word16

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word16

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Bounded Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word16

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Real Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Serialize Word16 
Instance details

Defined in Data.Serialize

Default Word16 
Instance details

Defined in Data.Default.Class

Methods

def :: Word16 #

NFData Word16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word16 -> () #

Eq Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word16 -> Word16 -> Bool #

(/=) :: Word16 -> Word16 -> Bool #

Ord Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Hashable Word16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

NvimObject Word16 Source # 
Instance details

Defined in Neovim.Classes

Pretty Word16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Prim Word16 
Instance details

Defined in Data.Primitive.Types

Uniform Word16 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word16 #

UniformRange Word16 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word16, Word16) -> g -> m Word16 #

Unbox Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Word16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word16 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word16 -> Code m Word16 #

Vector Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word32 #

32-bit unsigned integer type

Instances

Instances details
Data Word32

Since: base-4.0.0.0

Instance details

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 :: forall r r'. (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 #

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word32

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word32

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Bounded Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word32

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Real Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Serialize Word32 
Instance details

Defined in Data.Serialize

Default Word32 
Instance details

Defined in Data.Default.Class

Methods

def :: Word32 #

NFData Word32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word32 -> () #

Eq Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word32 -> Word32 -> Bool #

(/=) :: Word32 -> Word32 -> Bool #

Ord Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Hashable Word32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

NvimObject Word32 Source # 
Instance details

Defined in Neovim.Classes

Pretty Word32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Uniform Word32 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word32 #

UniformRange Word32 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word32, Word32) -> g -> m Word32 #

Unbox Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word32 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word32 -> Code m Word32 #

Vector Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word64 #

64-bit unsigned integer type

Instances

Instances details
Data Word64

Since: base-4.0.0.0

Instance details

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 :: forall r r'. (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 #

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word64

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word64

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Bounded Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word64

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Real Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Serialize Word64 
Instance details

Defined in Data.Serialize

Default Word64 
Instance details

Defined in Data.Default.Class

Methods

def :: Word64 #

NFData Word64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word64 -> () #

Eq Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word64 -> Word64 -> Bool #

(/=) :: Word64 -> Word64 -> Bool #

Ord Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Hashable Word64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

NvimObject Word64 Source # 
Instance details

Defined in Neovim.Classes

Pretty Word64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Prim Word64 
Instance details

Defined in Data.Primitive.Types

Uniform Word64 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word64 #

UniformRange Word64 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word64, Word64) -> g -> m Word64 #

Unbox Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Lift Word64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Word64 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word64 -> Code m Word64 #

Vector Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base