ide-backend-common-0.10.0: Shared library used be ide-backend and ide-backend-server

Safe HaskellNone
LanguageHaskell2010

IdeSession.Strict.Container

Contents

Synopsis

Documentation

class StrictContainer t where Source

Associated Types

data Strict t :: * -> * Source

Methods

force :: t a -> Strict t a Source

project :: Strict t a -> t a Source

For convenience, we export the names of the lazy types too

data Maybe a :: * -> *

The Maybe type encapsulates an optional value. A value of type Maybe a either contains a value of type a (represented as Just a), or it is empty (represented as Nothing). Using Maybe is a good way to deal with errors or exceptional cases without resorting to drastic measures such as error.

The Maybe type is also a monad. It is a simple kind of error monad, where all errors are represented by Nothing. A richer error monad can be built using the Either type.

Instances

Alternative Maybe 
Monad Maybe 
Functor Maybe 
MonadPlus Maybe 
Applicative Maybe 
Foldable Maybe 
Generic1 Maybe 
MonadThrow Maybe 
Eq1 Maybe 
Ord1 Maybe 
Read1 Maybe 
Show1 Maybe 
StrictContainer Maybe 
MonadBaseControl Maybe Maybe 
Alternative (Strict Maybe) 
Eq a => Eq (Maybe a) 
Functor (Strict Maybe) 
Ord a => Ord (Maybe a) 
Read a => Read (Maybe a) 
Show a => Show (Maybe a) 
Applicative (Strict Maybe) 
Generic (Maybe a) 
FromJSON a => LookupField (Maybe a) 
ToJSON a => ToJSON (Maybe a) 
FromJSON a => FromJSON (Maybe a) 
Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Binary a => Binary (Maybe a) 
Serialize a => Serialize (Maybe a) 
Hashable a => Hashable (Maybe a) 
PrettyVal a => PrettyVal (Maybe a) 
Semigroup a => Semigroup (Maybe a) 
Lift a => Lift (Maybe a) 
Eq a => Eq (Strict Maybe a) 
Ord a => Ord (Strict Maybe a) 
Show a => Show (Strict Maybe a) 
(Selector s, ToJSON a) => RecordToPairs (S1 s (K1 i (Maybe a))) 
(Selector s, FromJSON a) => FromRecord (S1 s (K1 i (Maybe a))) 
Binary a => Binary (Strict Maybe a) 
PrettyVal a => PrettyVal (Strict Maybe a) 
Typeable (* -> *) Maybe 
type Rep1 Maybe = D1 D1Maybe ((:+:) (C1 C1_0Maybe U1) (C1 C1_1Maybe (S1 NoSelector Par1))) 
data Strict Maybe = StrictMaybe {} 
type StM Maybe a = a 
type Rep (Maybe a) = D1 D1Maybe ((:+:) (C1 C1_0Maybe U1) (C1 C1_1Maybe (S1 NoSelector (Rec0 a)))) 
type (==) (Maybe k) a b = EqMaybe k a b 

data Map k a :: * -> * -> *

A Map from keys k to values a.

Instances

Functor (Map k) 
Foldable (Map k) 
Traversable (Map k) 
StrictContainer (Map k) 
(Eq k, Eq a) => Eq (Map k a) 
(Eq k, Eq v) => Eq (Strict (Map k) v) 
(Data k, Data a, Ord k) => Data (Map k a) 
(Ord k, Ord v) => Ord (Map k v) 
(Ord k, Read k, Read e) => Read (Map k e) 
(Show k, Show a) => Show (Map k a) 
(Show k, Show v) => Show (Strict (Map k) v) 
ToJSON v => ToJSON (Map String v) 
ToJSON v => ToJSON (Map Text v) 
ToJSON v => ToJSON (Map Text v) 
FromJSON v => FromJSON (Map String v) 
FromJSON v => FromJSON (Map Text v) 
FromJSON v => FromJSON (Map Text v) 
Ord k => Monoid (Map k v) 
(Binary k, Binary e) => Binary (Map k e) 
(Ord k, Binary k, Binary v) => Binary (Strict (Map k) v) 
(Ord k, Serialize k, Serialize e) => Serialize (Map k e) 
(NFData k, NFData a) => NFData (Map k a) 
(PrettyVal k, PrettyVal a) => PrettyVal (Map k a) 
(PrettyVal k, PrettyVal v) => PrettyVal (Strict (Map k) v) 
Ord k => Semigroup (Map k v) 
Typeable (* -> * -> *) Map 
data Strict (Map k) = StrictMap {} 

data IntMap a :: * -> *

A map of integers to values a.

data Trie a :: * -> *

A map from ByteStrings to a. For all the generic functions, note that tries are strict in the Maybe but not in a.

The Monad instance is strange. If a key k1 is a prefix of other keys, then results from binding the value at k1 will override values from longer keys when they collide. If this is useful for anything, or if there's a more sensible instance, I'd be curious to know.