cornelis-0.2.0.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cornelis.Types

Synopsis

Documentation

newtype Type Source #

Constructors

Type Text 

Instances

Instances details
FromJSON Type Source # 
Instance details

Defined in Cornelis.Types

Show Type Source # 
Instance details

Defined in Cornelis.Types

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type Source # 
Instance details

Defined in Cornelis.Types

Methods

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

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

Ord Type Source # 
Instance details

Defined in Cornelis.Types

Methods

compare :: Type -> Type -> Ordering #

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

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

(>) :: Type -> Type -> Bool #

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

newtype Message Source #

Constructors

Message 

Fields

Instances

Instances details
FromJSON Message Source # 
Instance details

Defined in Cornelis.Types

Show Message Source # 
Instance details

Defined in Cornelis.Types

Eq Message Source # 
Instance details

Defined in Cornelis.Types

Methods

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

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

Ord Message Source # 
Instance details

Defined in Cornelis.Types

data Agda Source #

Constructors

Agda 

Instances

Instances details
Generic Agda Source # 
Instance details

Defined in Cornelis.Types

Associated Types

type Rep Agda :: Type -> Type #

Methods

from :: Agda -> Rep Agda x #

to :: Rep Agda x -> Agda #

type Rep Agda Source # 
Instance details

Defined in Cornelis.Types

data BufferStuff Source #

data InteractionPoint f Source #

Instances

Instances details
FromJSON (InteractionPoint (Const () :: Type -> Type)) Source # 
Instance details

Defined in Cornelis.Types

FromJSON (InteractionPoint Identity) Source # 
Instance details

Defined in Cornelis.Types

FromJSON (InteractionPoint Maybe) Source # 
Instance details

Defined in Cornelis.Types

Generic (InteractionPoint f) Source # 
Instance details

Defined in Cornelis.Types

Associated Types

type Rep (InteractionPoint f) :: Type -> Type #

Show (f AgdaInterval) => Show (InteractionPoint f) Source # 
Instance details

Defined in Cornelis.Types

Eq (f AgdaInterval) => Eq (InteractionPoint f) Source # 
Instance details

Defined in Cornelis.Types

Ord (f AgdaInterval) => Ord (InteractionPoint f) Source # 
Instance details

Defined in Cornelis.Types

type Rep (InteractionPoint f) Source # 
Instance details

Defined in Cornelis.Types

type Rep (InteractionPoint f) = D1 ('MetaData "InteractionPoint" "Cornelis.Types" "cornelis-0.2.0.0-6a1gQdmcW6s9D29V5A3o0J" 'False) (C1 ('MetaCons "InteractionPoint" 'PrefixI 'True) (S1 ('MetaSel ('Just "ip_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InteractionId) :*: S1 ('MetaSel ('Just "ip_intervalM") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f AgdaInterval))))

newtype Extmark Source #

Constructors

Extmark Int64 

Instances

Instances details
Show Extmark Source # 
Instance details

Defined in Cornelis.Types

Eq Extmark Source # 
Instance details

Defined in Cornelis.Types

Methods

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

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

Ord Extmark Source # 
Instance details

Defined in Cornelis.Types

data DisplayInfo Source #

Instances

Instances details
FromJSON DisplayInfo Source # 
Instance details

Defined in Cornelis.Types

Generic DisplayInfo Source # 
Instance details

Defined in Cornelis.Types

Associated Types

type Rep DisplayInfo :: Type -> Type #

Show DisplayInfo Source # 
Instance details

Defined in Cornelis.Types

Eq DisplayInfo Source # 
Instance details

Defined in Cornelis.Types

Ord DisplayInfo Source # 
Instance details

Defined in Cornelis.Types

type Rep DisplayInfo Source # 
Instance details

Defined in Cornelis.Types

type Rep DisplayInfo = D1 ('MetaData "DisplayInfo" "Cornelis.Types" "cornelis-0.2.0.0-6a1gQdmcW6s9D29V5A3o0J" 'False) (((C1 ('MetaCons "AllGoalsWarnings" 'PrefixI 'True) ((S1 ('MetaSel ('Just "di_all_visible") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GoalInfo (InteractionPoint Identity)]) :*: S1 ('MetaSel ('Just "di_all_invisible") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GoalInfo NamedPoint])) :*: (S1 ('MetaSel ('Just "di_errors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Message]) :*: S1 ('MetaSel ('Just "di_warnings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Message]))) :+: C1 ('MetaCons "GoalSpecific" 'PrefixI 'True) ((S1 ('MetaSel ('Just "di_ips") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (InteractionPoint Identity)) :*: (S1 ('MetaSel ('Just "di_in_scope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InScope]) :*: S1 ('MetaSel ('Just "di_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :*: (S1 ('MetaSel ('Just "di_type_aux") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Type)) :*: (S1 ('MetaSel ('Just "di_boundary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Just "di_output_forms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])))))) :+: (C1 ('MetaCons "HelperFunction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "InferredType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: ((C1 ('MetaCons "DisplayError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "WhyInScope" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "NormalForm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "UnknownDisplayInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))))

newtype InfoBuffer Source #

Constructors

InfoBuffer 

Fields

Instances

Instances details
Generic InfoBuffer Source # 
Instance details

Defined in Cornelis.Types

Associated Types

type Rep InfoBuffer :: Type -> Type #

type Rep InfoBuffer Source # 
Instance details

Defined in Cornelis.Types

type Rep InfoBuffer = D1 ('MetaData "InfoBuffer" "Cornelis.Types" "cornelis-0.2.0.0-6a1gQdmcW6s9D29V5A3o0J" 'True) (C1 ('MetaCons "InfoBuffer" 'PrefixI 'True) (S1 ('MetaSel ('Just "iw_buffer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Buffer)))

newtype LineIntervals Source #

Data for mapping code point indices to byte indices

Constructors

LineIntervals 

Fields

data CornelisState Source #

Instances

Instances details
Generic CornelisState Source # 
Instance details

Defined in Cornelis.Types

Associated Types

type Rep CornelisState :: Type -> Type #

MonadState CornelisState (Neovim CornelisEnv) Source # 
Instance details

Defined in Cornelis.Types

type Rep CornelisState Source # 
Instance details

Defined in Cornelis.Types

type Rep CornelisState = D1 ('MetaData "CornelisState" "Cornelis.Types" "cornelis-0.2.0.0-6a1gQdmcW6s9D29V5A3o0J" 'False) (C1 ('MetaCons "CornelisState" 'PrefixI 'True) (S1 ('MetaSel ('Just "cs_buffers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Buffer BufferStuff)) :*: S1 ('MetaSel ('Just "cs_diff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map BufferNum Diff0))))

type BufferNum = Int64 Source #

Buffer update events give us this instead of a proper Buffer There is buffer_get_number :: Buffer -> Neovim env BufferNum but nothing the other way???

data SplitLocation Source #

data CornelisConfig Source #

Instances

Instances details
Generic CornelisConfig Source # 
Instance details

Defined in Cornelis.Types

Associated Types

type Rep CornelisConfig :: Type -> Type #

Show CornelisConfig Source # 
Instance details

Defined in Cornelis.Types

type Rep CornelisConfig Source # 
Instance details

Defined in Cornelis.Types

type Rep CornelisConfig = D1 ('MetaData "CornelisConfig" "Cornelis.Types" "cornelis-0.2.0.0-6a1gQdmcW6s9D29V5A3o0J" 'False) (C1 ('MetaCons "CornelisConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "cc_max_height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "cc_max_width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64) :*: S1 ('MetaSel ('Just "cc_split_location") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SplitLocation))))

data CornelisEnv Source #

Instances

Instances details
Generic CornelisEnv Source # 
Instance details

Defined in Cornelis.Types

Associated Types

type Rep CornelisEnv :: Type -> Type #

MonadState CornelisState (Neovim CornelisEnv) Source # 
Instance details

Defined in Cornelis.Types

type Rep CornelisEnv Source # 
Instance details

Defined in Cornelis.Types

type Rep CornelisEnv = D1 ('MetaData "CornelisEnv" "Cornelis.Types" "cornelis-0.2.0.0-6a1gQdmcW6s9D29V5A3o0J" 'False) (C1 ('MetaCons "CornelisEnv" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ce_state") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IORef CornelisState)) :*: S1 ('MetaSel ('Just "ce_stream") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (InChan AgdaResp))) :*: (S1 ('MetaSel ('Just "ce_namespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64) :*: S1 ('MetaSel ('Just "ce_config") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CornelisConfig))))

data AgdaResp Source #

Constructors

AgdaResp 

Instances

Instances details
Generic AgdaResp Source # 
Instance details

Defined in Cornelis.Types

Associated Types

type Rep AgdaResp :: Type -> Type #

Methods

from :: AgdaResp -> Rep AgdaResp x #

to :: Rep AgdaResp x -> AgdaResp #

type Rep AgdaResp Source # 
Instance details

Defined in Cornelis.Types

type Rep AgdaResp = D1 ('MetaData "AgdaResp" "Cornelis.Types" "cornelis-0.2.0.0-6a1gQdmcW6s9D29V5A3o0J" 'False) (C1 ('MetaCons "AgdaResp" 'PrefixI 'True) (S1 ('MetaSel ('Just "ar_buffer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Buffer) :*: S1 ('MetaSel ('Just "ar_message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Response)))

data MakeCase Source #

Instances

Instances details
FromJSON MakeCase Source # 
Instance details

Defined in Cornelis.Types

Generic MakeCase Source # 
Instance details

Defined in Cornelis.Types

Associated Types

type Rep MakeCase :: Type -> Type #

Methods

from :: MakeCase -> Rep MakeCase x #

to :: Rep MakeCase x -> MakeCase #

Show MakeCase Source # 
Instance details

Defined in Cornelis.Types

Eq MakeCase Source # 
Instance details

Defined in Cornelis.Types

Ord MakeCase Source # 
Instance details

Defined in Cornelis.Types

type Rep MakeCase Source # 
Instance details

Defined in Cornelis.Types

data Solution Source #

Constructors

Solution 

Instances

Instances details
FromJSON Solution Source # 
Instance details

Defined in Cornelis.Types

Show Solution Source # 
Instance details

Defined in Cornelis.Types

Eq Solution Source # 
Instance details

Defined in Cornelis.Types

Ord Solution Source # 
Instance details

Defined in Cornelis.Types

data MakeCaseVariant Source #

Constructors

Function 
ExtendedLambda 

Instances

Instances details
FromJSON MakeCaseVariant Source # 
Instance details

Defined in Cornelis.Types

Generic MakeCaseVariant Source # 
Instance details

Defined in Cornelis.Types

Associated Types

type Rep MakeCaseVariant :: Type -> Type #

Show MakeCaseVariant Source # 
Instance details

Defined in Cornelis.Types

Eq MakeCaseVariant Source # 
Instance details

Defined in Cornelis.Types

Ord MakeCaseVariant Source # 
Instance details

Defined in Cornelis.Types

type Rep MakeCaseVariant Source # 
Instance details

Defined in Cornelis.Types

type Rep MakeCaseVariant = D1 ('MetaData "MakeCaseVariant" "Cornelis.Types" "cornelis-0.2.0.0-6a1gQdmcW6s9D29V5A3o0J" 'False) (C1 ('MetaCons "Function" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExtendedLambda" 'PrefixI 'False) (U1 :: Type -> Type))

newtype AgdaPos' Source #

Constructors

AgdaPos AgdaPos 

Instances

Instances details
FromJSON AgdaPos' Source # 
Instance details

Defined in Cornelis.Types

data GoalInfo a Source #

Constructors

GoalInfo 

Fields

Instances

Instances details
Functor GoalInfo Source # 
Instance details

Defined in Cornelis.Types

Methods

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

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

FromJSON a => FromJSON (GoalInfo a) Source # 
Instance details

Defined in Cornelis.Types

Show a => Show (GoalInfo a) Source # 
Instance details

Defined in Cornelis.Types

Methods

showsPrec :: Int -> GoalInfo a -> ShowS #

show :: GoalInfo a -> String #

showList :: [GoalInfo a] -> ShowS #

Eq a => Eq (GoalInfo a) Source # 
Instance details

Defined in Cornelis.Types

Methods

(==) :: GoalInfo a -> GoalInfo a -> Bool #

(/=) :: GoalInfo a -> GoalInfo a -> Bool #

Ord a => Ord (GoalInfo a) Source # 
Instance details

Defined in Cornelis.Types

Methods

compare :: GoalInfo a -> GoalInfo a -> Ordering #

(<) :: GoalInfo a -> GoalInfo a -> Bool #

(<=) :: GoalInfo a -> GoalInfo a -> Bool #

(>) :: GoalInfo a -> GoalInfo a -> Bool #

(>=) :: GoalInfo a -> GoalInfo a -> Bool #

max :: GoalInfo a -> GoalInfo a -> GoalInfo a #

min :: GoalInfo a -> GoalInfo a -> GoalInfo a #

data InScope Source #

Instances

Instances details
FromJSON InScope Source # 
Instance details

Defined in Cornelis.Types

Show InScope Source # 
Instance details

Defined in Cornelis.Types

Eq InScope Source # 
Instance details

Defined in Cornelis.Types

Methods

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

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

Ord InScope Source # 
Instance details

Defined in Cornelis.Types

newtype TypeAux Source #

Constructors

TypeAux 

Fields

Instances

Instances details
FromJSON TypeAux Source # 
Instance details

Defined in Cornelis.Types

data DebugCommand Source #

Constructors

DumpIPs 

Instances

Instances details
Bounded DebugCommand Source # 
Instance details

Defined in Cornelis.Types

Enum DebugCommand Source # 
Instance details

Defined in Cornelis.Types

Read DebugCommand Source # 
Instance details

Defined in Cornelis.Types

Show DebugCommand Source # 
Instance details

Defined in Cornelis.Types

Eq DebugCommand Source # 
Instance details

Defined in Cornelis.Types

Ord DebugCommand Source # 
Instance details

Defined in Cornelis.Types

data InteractionId Source #

Instances

Instances details
FromJSON InteractionId Source # 
Instance details

Defined in Cornelis.Types.Agda

ToJSON InteractionId Source # 
Instance details

Defined in Cornelis.Types.Agda

Enum InteractionId Source # 
Instance details

Defined in Cornelis.Types.Agda

Num InteractionId Source # 
Instance details

Defined in Cornelis.Types.Agda

Read InteractionId Source # 
Instance details

Defined in Cornelis.Types.Agda

Integral InteractionId Source # 
Instance details

Defined in Cornelis.Types.Agda

Real InteractionId Source # 
Instance details

Defined in Cornelis.Types.Agda

Show InteractionId Source # 
Instance details

Defined in Cornelis.Types.Agda

Eq InteractionId Source # 
Instance details

Defined in Cornelis.Types.Agda

Ord InteractionId Source # 
Instance details

Defined in Cornelis.Types.Agda

data Buffer #

Instances

Instances details
Generic Buffer 
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 #

Show Buffer 
Instance details

Defined in Neovim.API.Text

NFData Buffer 
Instance details

Defined in Neovim.API.Text

Methods

rnf :: Buffer -> () #

Eq Buffer 
Instance details

Defined in Neovim.API.Text

Methods

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

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

Ord Buffer Source # 
Instance details

Defined in Cornelis.Types

NvimObject Buffer 
Instance details

Defined in Neovim.API.Text

type Rep Buffer 
Instance details

Defined in Neovim.API.Text

type Rep Buffer = D1 ('MetaData "Buffer" "Neovim.API.Text" "nvim-hs-2.3.2.3-EiEXbDxSBLL2xZh1tUwc4J" 'False) (C1 ('MetaCons "Buffer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))

data Window #

Instances

Instances details
Generic Window 
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 #

Show Window 
Instance details

Defined in Neovim.API.Text

NFData Window 
Instance details

Defined in Neovim.API.Text

Methods

rnf :: Window -> () #

Eq Window 
Instance details

Defined in Neovim.API.Text

Methods

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

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

NvimObject Window 
Instance details

Defined in Neovim.API.Text

type Rep Window 
Instance details

Defined in Neovim.API.Text

type Rep Window = D1 ('MetaData "Window" "Neovim.API.Text" "nvim-hs-2.3.2.3-EiEXbDxSBLL2xZh1tUwc4J" 'False) (C1 ('MetaCons "Window" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances

Instances details
FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Ixed Text 
Instance details

Defined in Control.Lens.At

AsEmpty Text 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' Text () #

Reversing Text 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Text -> Text #

Prefixed Text 
Instance details

Defined in Control.Lens.Prism

Methods

prefixed :: Text -> Prism' Text Text #

Suffixed Text 
Instance details

Defined in Control.Lens.Prism

Methods

suffixed :: Text -> Prism' Text Text #

Stream Text 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token Text #

type Tokens Text #

TraversableStream Text 
Instance details

Defined in Text.Megaparsec.Stream

VisualStream Text 
Instance details

Defined in Text.Megaparsec.Stream

GrowingAppend Text 
Instance details

Defined in Data.MonoTraversable

MonoFoldable Text 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element Text -> m) -> Text -> m #

ofoldr :: (Element Text -> b -> b) -> b -> Text -> b #

ofoldl' :: (a -> Element Text -> a) -> a -> Text -> a #

otoList :: Text -> [Element Text] #

oall :: (Element Text -> Bool) -> Text -> Bool #

oany :: (Element Text -> Bool) -> Text -> Bool #

onull :: Text -> Bool #

olength :: Text -> Int #

olength64 :: Text -> Int64 #

ocompareLength :: Integral i => Text -> i -> Ordering #

otraverse_ :: Applicative f => (Element Text -> f b) -> Text -> f () #

ofor_ :: Applicative f => Text -> (Element Text -> f b) -> f () #

omapM_ :: Applicative m => (Element Text -> m ()) -> Text -> m () #

oforM_ :: Applicative m => Text -> (Element Text -> m ()) -> m () #

ofoldlM :: Monad m => (a -> Element Text -> m a) -> a -> Text -> m a #

ofoldMap1Ex :: Semigroup m => (Element Text -> m) -> Text -> m #

ofoldr1Ex :: (Element Text -> Element Text -> Element Text) -> Text -> Element Text #

ofoldl1Ex' :: (Element Text -> Element Text -> Element Text) -> Text -> Element Text #

headEx :: Text -> Element Text #

lastEx :: Text -> Element Text #

unsafeHead :: Text -> Element Text #

unsafeLast :: Text -> Element Text #

maximumByEx :: (Element Text -> Element Text -> Ordering) -> Text -> Element Text #

minimumByEx :: (Element Text -> Element Text -> Ordering) -> Text -> Element Text #

oelem :: Element Text -> Text -> Bool #

onotElem :: Element Text -> Text -> Bool #

MonoFunctor Text 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element Text -> Element Text) -> Text -> Text #

MonoPointed Text 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element Text -> Text #

MonoTraversable Text 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element Text -> f (Element Text)) -> Text -> f Text #

omapM :: Applicative m => (Element Text -> m (Element Text)) -> Text -> m Text #

IsSequence Text 
Instance details

Defined in Data.Sequences

Methods

fromList :: [Element Text] -> Text #

lengthIndex :: Text -> Index Text #

break :: (Element Text -> Bool) -> Text -> (Text, Text) #

span :: (Element Text -> Bool) -> Text -> (Text, Text) #

dropWhile :: (Element Text -> Bool) -> Text -> Text #

takeWhile :: (Element Text -> Bool) -> Text -> Text #

splitAt :: Index Text -> Text -> (Text, Text) #

unsafeSplitAt :: Index Text -> Text -> (Text, Text) #

take :: Index Text -> Text -> Text #

unsafeTake :: Index Text -> Text -> Text #

drop :: Index Text -> Text -> Text #

unsafeDrop :: Index Text -> Text -> Text #

dropEnd :: Index Text -> Text -> Text #

partition :: (Element Text -> Bool) -> Text -> (Text, Text) #

uncons :: Text -> Maybe (Element Text, Text) #

unsnoc :: Text -> Maybe (Text, Element Text) #

filter :: (Element Text -> Bool) -> Text -> Text #

filterM :: Monad m => (Element Text -> m Bool) -> Text -> m Text #

replicate :: Index Text -> Element Text -> Text #

replicateM :: Monad m => Index Text -> m (Element Text) -> m Text #

groupBy :: (Element Text -> Element Text -> Bool) -> Text -> [Text] #

groupAllOn :: Eq b => (Element Text -> b) -> Text -> [Text] #

subsequences :: Text -> [Text] #

permutations :: Text -> [Text] #

tailEx :: Text -> Text #

tailMay :: Text -> Maybe Text #

initEx :: Text -> Text #

initMay :: Text -> Maybe Text #

unsafeTail :: Text -> Text #

unsafeInit :: Text -> Text #

index :: Text -> Index Text -> Maybe (Element Text) #

indexEx :: Text -> Index Text -> Element Text #

unsafeIndex :: Text -> Index Text -> Element Text #

splitWhen :: (Element Text -> Bool) -> Text -> [Text] #

tails :: Text -> [Text] #

inits :: Text -> [Text] #

initTails :: Text -> [(Text, Text)] #

SemiSequence Text 
Instance details

Defined in Data.Sequences

Associated Types

type Index Text #

Textual Text 
Instance details

Defined in Data.Sequences

Methods

words :: Text -> [Text] #

unwords :: (Element seq ~ Text, MonoFoldable seq) => seq -> Text #

lines :: Text -> [Text] #

unlines :: (Element seq ~ Text, MonoFoldable seq) => seq -> Text #

toLower :: Text -> Text #

toUpper :: Text -> Text #

toCaseFold :: Text -> Text #

breakWord :: Text -> (Text, Text) #

breakLine :: Text -> (Text, Text) #

NvimObject Text 
Instance details

Defined in Neovim.Classes

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 #

LazySequence Text Text 
Instance details

Defined in Data.Sequences

Utf8 Text ByteString 
Instance details

Defined in Data.Sequences

Cons Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Snoc Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

(a ~ Char, b ~ Char) => Each Text Text a b
each :: Traversal Text Text Char Char
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal Text Text a b #

Stream (NoShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token (NoShareInput Text) #

type Tokens (NoShareInput Text) #

Stream (ShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token (ShareInput Text) #

type Tokens (ShareInput Text) #

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char
type Index Text 
Instance details

Defined in Control.Lens.At

type Index Text = Int
type IxValue Text 
Instance details

Defined in Control.Lens.At

type Token Text 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens Text 
Instance details

Defined in Text.Megaparsec.Stream

type Element Text 
Instance details

Defined in Data.MonoTraversable

type Index Text 
Instance details

Defined in Data.Sequences

type Index Text = Int
type Token (NoShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

type Token (ShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens (NoShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens (ShareInput Text) 
Instance details

Defined in Text.Megaparsec.Stream

traceMX :: Show a => String -> a -> Neovim env () Source #

type HasCallStack = ?callStack :: CallStack #

Request a CallStack.

NOTE: The implicit parameter ?callStack :: CallStack is an implementation detail and should not be considered part of the CallStack API, we may decide to change the implementation in the future.

Since: base-4.9.0.0

Orphan instances