yi-mode-haskell-0.14.1: Yi editor haskell mode

LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • TypeFamilies
  • DeriveFoldable
  • TypeSynonymInstances
  • FlexibleInstances
  • KindSignatures
  • ExplicitNamespaces

Yi.Syntax.Haskell

Description

NOTES: Note if the layout of the first line (not comments) is wrong the parser will only parse what is in the blocks given by Layout.hs

Synopsis

Documentation

data Exp t Source #

Exp can be expression or declaration

Constructors

PModule 

Fields

ProgMod 

Fields

Body 

Fields

PModuleDecl 

Fields

PImport 

Fields

TS t [Exp t]

Type signature

PType

Type declaration

Fields

PData

Data declaration

Fields

PData' 

Fields

PClass 

Fields

Paren (PAtom t) [Exp t] (PAtom t)

A parenthesized, bracked or braced

Block [Exp t]

A block of things separated by layout

PAtom t [t]

An atom is a token followed by many comments

Expr [Exp t] 
PWhere (PAtom t) (Exp t) (Exp t)

Where clause

Bin (Exp t) (Exp t) 
PError 

Fields

RHS (PAtom t) (Exp t)

Righthandside of functions with =

Opt (Maybe (Exp t))

An optional

Modid t [t]

Module identifier

Context (Exp t) (Exp t) (PAtom t) 
PGuard [PGuard t]

Righthandside of functions with | the PAtom in PGuard' does not contain any comments

PGuard' (PAtom t) (Exp t) (PAtom t) 
TC (Exp t)

Type constructor data constructor same as with the TC constructor

DC (Exp t)

Data constructor

PLet (PAtom t) (Exp t) (Exp t)

let expression

PIn t [Exp t] 

Instances

Foldable Exp Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Exp a -> [a] #

null :: Exp a -> Bool #

length :: Exp a -> Int #

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

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

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

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

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

IsTree Exp Source # 

Methods

subtrees :: Exp t -> [Exp t] #

uniplate :: Exp t -> ([Exp t], [Exp t] -> Exp t) #

emptyNode :: Exp t #

Show t => Show (Exp t) Source # 

Methods

showsPrec :: Int -> Exp t -> ShowS #

show :: Exp t -> String #

showList :: [Exp t] -> ShowS #

parse :: P TT (Tree TT) Source #

The parser