yi-0.6.2.3: The Haskell-Scriptable EditorSource codeContentsIndex
Yi.Dynamic
Synopsis
class Typeable a => Initializable a where
initial :: a
toDyn :: Initializable a => a -> Dynamic
fromDynamic :: forall a. Typeable a => Dynamic -> Maybe a
dynamicValueA :: Initializable a => Accessor DynamicValues a
emptyDV :: DynamicValues
class Typeable a
data Dynamic
type DynamicValues = Map String Dynamic
Documentation
class Typeable a => Initializable a whereSource

Class of values that can go in the extensible state component

The default value. If a function tries to get a copy of the state, but the state hasn't yet been created, initial will be called to supply *some* value. The value of initial will probably be something like Nothing, [], "", or Data.Sequence.empty - compare the mempty of Data.Monoid.

Methods
initial :: aSource
show/hide Instances
toDyn :: Initializable a => a -> DynamicSource
fromDynamic :: forall a. Typeable a => Dynamic -> Maybe aSource
dynamicValueA :: Initializable a => Accessor DynamicValues aSource
Accessor for a dynamic component
emptyDV :: DynamicValuesSource
The empty record
class Typeable a Source
The class Typeable allows a concrete representation of a type to be calculated.
show/hide Instances
Typeable Bool
Typeable Char
Typeable Double
Typeable Float
Typeable Int
Typeable Int8
Typeable Int16
Typeable Int32
Typeable Int64
Typeable Integer
Typeable Ordering
Typeable RealWorld
Typeable Word
Typeable Word8
Typeable Word16
Typeable Word32
Typeable Word64
Typeable Exp
Typeable Match
Typeable Clause
Typeable Pat
Typeable Type
Typeable Dec
Typeable Name
Typeable FunDep
Typeable Pred
Typeable TyVarBndr
Typeable ()
Typeable Version
Typeable Handle
Typeable FD
Typeable Handle__
Typeable Exception
Typeable E0
Typeable E1
Typeable E2
Typeable E3
Typeable E6
Typeable E9
Typeable E12
Typeable DataType
Typeable PatternMatchFail
Typeable RecSelError
Typeable RecConError
Typeable RecUpdError
Typeable NoMethodError
Typeable NonTermination
Typeable NestedAtomically
Typeable ThreadId
Typeable CDev
Typeable CIno
Typeable CMode
Typeable COff
Typeable CPid
Typeable CSsize
Typeable CGid
Typeable CNlink
Typeable CUid
Typeable CCc
Typeable CSpeed
Typeable CTcflag
Typeable CRLim
Typeable Fd
Typeable BlockedIndefinitelyOnMVar
Typeable BlockedIndefinitelyOnSTM
Typeable Deadlock
Typeable AssertionFailed
Typeable AsyncException
Typeable ArrayException
Typeable ExitCode
Typeable Dynamic
Typeable CChar
Typeable CSChar
Typeable CUChar
Typeable CShort
Typeable CUShort
Typeable CInt
Typeable CUInt
Typeable CLong
Typeable CULong
Typeable CLLong
Typeable CULLong
Typeable CFloat
Typeable CDouble
Typeable CPtrdiff
Typeable CSize
Typeable CWchar
Typeable CSigAtomic
Typeable CClock
Typeable CTime
Typeable CIntPtr
Typeable CUIntPtr
Typeable CIntMax
Typeable CUIntMax
Typeable IOException
Typeable SomeException
Typeable ErrorCall
Typeable ArithException
Typeable TypeRep
Typeable TyCon
Typeable ByteString
Typeable ByteString
Typeable IntSet
Typeable OccName
Typeable PkgName
Typeable ModName
Typeable Kind
Typeable Con
Typeable Strict
Typeable InlineSpec
Typeable Pragma
Typeable Safety
Typeable Callconv
Typeable Foreign
Typeable FamFlavour
Typeable Range
Typeable Stmt
Typeable Guard
Typeable Body
Typeable FixityDirection
Typeable Fixity
Typeable Info
Typeable NameSpace
Typeable NameFlavour
Typeable GuardedAlt
Typeable GuardedAlts
Typeable Alt
Typeable FieldUpdate
Typeable QualStmt
Typeable Stmt
Typeable PatField
Typeable RPat
Typeable RPatOp
Typeable PXAttr
Typeable Pat
Typeable WarningText
Typeable RuleVar
Typeable Rule
Typeable Activation
Typeable ModulePragma
Typeable CallConv
Typeable Safety
Typeable Splice
Typeable Bracket
Typeable XAttr
Typeable XName
Typeable Exp
Typeable Literal
Typeable Asst
Typeable FunDep
Typeable Kind
Typeable TyVarBind
Typeable Type
Typeable GuardedRhs
Typeable Rhs
Typeable BangType
Typeable InstDecl
Typeable ClassDecl
Typeable GadtDecl
Typeable ConDecl
Typeable QualConDecl
Typeable Match
Typeable IPBind
Typeable Binds
Typeable DataOrNew
Typeable Annotation
Typeable Decl
Typeable Assoc
Typeable ImportSpec
Typeable ImportDecl
Typeable ExportSpec
Typeable Module
Typeable CName
Typeable Op
Typeable QOp
Typeable IPName
Typeable Name
Typeable QName
Typeable SpecialCon
Typeable ModuleName
Typeable Lit
Typeable SourceError
Typeable GhcApiError
Typeable InterpreterError
Typeable SourcePos
Typeable LocalTime
Typeable ZonedTime
Typeable UTCTime
Typeable NominalDiffTime
Typeable Day
Typeable UniversalTime
Typeable DiffTime
Typeable Handler
Typeable Editor
Typeable Direction
Typeable Point
Typeable BufferRef
Typeable Mark
Typeable Region
Typeable Window
Typeable MarkValue
Typeable Update
Typeable Action
Typeable Attributes
Typeable SelectionStyle
Typeable AnyMode
Typeable IndentSettings
Typeable FBuffer
Typeable RegionStyle
Typeable TextUnit
Typeable TempBufferNameHint
Typeable Yi
Typeable Completion
Typeable History
Typeable Isearch
Typeable CommandArguments
Typeable FilePatternTag
Typeable RegexTag
Typeable DiredOpState
Typeable DiredState
Typeable DiredEntry
Typeable DiredFileInfo
Typeable NamesCache
Typeable TagTable
Typeable TagsFileList
Typeable Tags
Typeable CabalBuffer
Typeable ViInsertion
Typeable ViCmd
Typeable ViMove
Typeable VimTagStack
Typeable AbellaBuffer
Typeable JSBuffer
Typeable DependentMarks
Typeable BufferMarks
Typeable GhciBuffer
(Typeable1 s, Typeable a) => Typeable (s a)
data Dynamic Source
type DynamicValues = Map String DynamicSource
An extensible record, indexed by type
Produced by Haddock version 2.6.1