purescript-0.13.0: PureScript Programming Language Compiler

Safe HaskellNone
LanguageHaskell2010

Language.PureScript.CST.Types

Description

This module contains data types for the entire PureScript surface language. Every token is represented in the tree, and every token is annotated with whitespace and comments (both leading and trailing). This means one can write an exact printer so that `print . parse = id`. Every constructor is laid out with tokens in left-to-right order. The core productions are given a slot for arbitrary annotations, however this is not used by the parser.

Documentation

data SourcePos Source #

Constructors

SourcePos 

Fields

Instances
Eq SourcePos Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord SourcePos Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show SourcePos Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic SourcePos Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep SourcePos :: Type -> Type #

type Rep SourcePos Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep SourcePos = D1 (MetaData "SourcePos" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "SourcePos" PrefixI True) (S1 (MetaSel (Just "srcLine") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "srcColumn") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)))

data SourceRange Source #

Constructors

SourceRange 

data Comment l Source #

Constructors

Comment !Text 
Space !Int 
Line !l 
Instances
Functor Comment Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Eq l => Eq (Comment l) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: Comment l -> Comment l -> Bool #

(/=) :: Comment l -> Comment l -> Bool #

Ord l => Ord (Comment l) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: Comment l -> Comment l -> Ordering #

(<) :: Comment l -> Comment l -> Bool #

(<=) :: Comment l -> Comment l -> Bool #

(>) :: Comment l -> Comment l -> Bool #

(>=) :: Comment l -> Comment l -> Bool #

max :: Comment l -> Comment l -> Comment l #

min :: Comment l -> Comment l -> Comment l #

Show l => Show (Comment l) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> Comment l -> ShowS #

show :: Comment l -> String #

showList :: [Comment l] -> ShowS #

Generic (Comment l) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (Comment l) :: Type -> Type #

Methods

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

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

type Rep (Comment l) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data LineFeed Source #

Constructors

LF 
CRLF 
Instances
Eq LineFeed Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord LineFeed Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show LineFeed Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic LineFeed Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep LineFeed :: Type -> Type #

Methods

from :: LineFeed -> Rep LineFeed x #

to :: Rep LineFeed x -> LineFeed #

type Rep LineFeed Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep LineFeed = D1 (MetaData "LineFeed" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "LF" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CRLF" PrefixI False) (U1 :: Type -> Type))

data TokenAnn Source #

Instances
Eq TokenAnn Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord TokenAnn Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show TokenAnn Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic TokenAnn Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep TokenAnn :: Type -> Type #

Methods

from :: TokenAnn -> Rep TokenAnn x #

to :: Rep TokenAnn x -> TokenAnn #

type Rep TokenAnn Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep TokenAnn = D1 (MetaData "TokenAnn" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "TokenAnn" PrefixI True) (S1 (MetaSel (Just "tokRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SourceRange) :*: (S1 (MetaSel (Just "tokLeadingComments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Comment LineFeed]) :*: S1 (MetaSel (Just "tokTrailingComments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Comment Void]))))

data SourceStyle Source #

Constructors

ASCII 
Unicode 
Instances
Eq SourceStyle Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord SourceStyle Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show SourceStyle Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic SourceStyle Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep SourceStyle :: Type -> Type #

type Rep SourceStyle Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep SourceStyle = D1 (MetaData "SourceStyle" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "ASCII" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Unicode" PrefixI False) (U1 :: Type -> Type))

data Token Source #

Instances
Eq Token Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Ord Token Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: Token -> Token -> Ordering #

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

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

(>) :: Token -> Token -> Bool #

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

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

Show Token Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep Token :: Type -> Type #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

type Rep Token Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep Token = D1 (MetaData "Token" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (((((C1 (MetaCons "TokLeftParen" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TokRightParen" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TokLeftBrace" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TokRightBrace" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "TokLeftSquare" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TokRightSquare" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TokLeftArrow" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SourceStyle)) :+: C1 (MetaCons "TokRightArrow" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SourceStyle))))) :+: (((C1 (MetaCons "TokRightFatArrow" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SourceStyle)) :+: C1 (MetaCons "TokDoubleColon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SourceStyle))) :+: (C1 (MetaCons "TokForall" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SourceStyle)) :+: C1 (MetaCons "TokEquals" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "TokPipe" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TokTick" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TokDot" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TokComma" PrefixI False) (U1 :: Type -> Type))))) :+: ((((C1 (MetaCons "TokUnderscore" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TokBackslash" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TokLowerName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "TokUpperName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) :+: ((C1 (MetaCons "TokOperator" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "TokSymbolName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) :+: (C1 (MetaCons "TokSymbolArr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SourceStyle)) :+: C1 (MetaCons "TokHole" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))) :+: (((C1 (MetaCons "TokChar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Char)) :+: C1 (MetaCons "TokString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PSString))) :+: (C1 (MetaCons "TokRawString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "TokInt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Integer)))) :+: ((C1 (MetaCons "TokNumber" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :+: C1 (MetaCons "TokLayoutStart" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TokLayoutSep" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TokLayoutEnd" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TokEof" PrefixI False) (U1 :: Type -> Type)))))))

data SourceToken Source #

Constructors

SourceToken 

Fields

data Ident Source #

Constructors

Ident 

Fields

Instances
Eq Ident Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Ord Ident Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: Ident -> Ident -> Ordering #

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

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

(>) :: Ident -> Ident -> Bool #

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

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Show Ident Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Generic Ident Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep Ident :: Type -> Type #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

type Rep Ident Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep Ident = D1 (MetaData "Ident" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "Ident" PrefixI True) (S1 (MetaSel (Just "getIdent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Name a Source #

Constructors

Name 

Fields

Instances
Functor Name Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Name Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Name a -> [a] #

null :: Name a -> Bool #

length :: Name a -> Int #

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

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

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

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

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

Traversable Name Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Name a -> Name a -> Ordering #

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

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

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

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

max :: Name a -> Name a -> Name a #

min :: Name a -> Name a -> Name a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Name a -> String #

showList :: [Name a] -> ShowS #

Generic (Name a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Name a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Name a) = D1 (MetaData "Name" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "Name" PrefixI True) (S1 (MetaSel (Just "nameTok") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Just "nameValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data QualifiedName a Source #

Instances
Functor QualifiedName Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable QualifiedName Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: QualifiedName a -> [a] #

null :: QualifiedName a -> Bool #

length :: QualifiedName a -> Int #

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

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

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

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

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

Traversable QualifiedName Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (QualifiedName a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

type Rep (QualifiedName a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (QualifiedName a) = D1 (MetaData "QualifiedName" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "QualifiedName" PrefixI True) (S1 (MetaSel (Just "qualTok") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: (S1 (MetaSel (Just "qualModule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ModuleName)) :*: S1 (MetaSel (Just "qualName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))

data Label Source #

Constructors

Label 
Instances
Eq Label Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Ord Label Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: Label -> Label -> Ordering #

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

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

(>) :: Label -> Label -> Bool #

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

max :: Label -> Label -> Label #

min :: Label -> Label -> Label #

Show Label Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

Generic Label Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep Label :: Type -> Type #

Methods

from :: Label -> Rep Label x #

to :: Rep Label x -> Label #

type Rep Label Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep Label = D1 (MetaData "Label" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "Label" PrefixI True) (S1 (MetaSel (Just "lblTok") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Just "lblName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PSString)))

data Wrapped a Source #

Constructors

Wrapped 
Instances
Functor Wrapped Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Wrapped Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Wrapped a -> [a] #

null :: Wrapped a -> Bool #

length :: Wrapped a -> Int #

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

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

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

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

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

Traversable Wrapped Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Wrapped a -> Wrapped a -> Ordering #

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

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

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

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

max :: Wrapped a -> Wrapped a -> Wrapped a #

min :: Wrapped a -> Wrapped a -> Wrapped a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Wrapped a -> String #

showList :: [Wrapped a] -> ShowS #

Generic (Wrapped a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Wrapped a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Wrapped a) = D1 (MetaData "Wrapped" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "Wrapped" PrefixI True) (S1 (MetaSel (Just "wrpOpen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: (S1 (MetaSel (Just "wrpValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "wrpClose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken))))

data Separated a Source #

Constructors

Separated 

Fields

Instances
Functor Separated Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Separated Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Separated a -> [a] #

null :: Separated a -> Bool #

length :: Separated a -> Int #

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

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

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

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

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

Traversable Separated Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (Separated a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Separated a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Separated a) = D1 (MetaData "Separated" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "Separated" PrefixI True) (S1 (MetaSel (Just "sepHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "sepTail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(SourceToken, a)])))

data Labeled a b Source #

Constructors

Labeled 

Fields

Instances
Functor (Labeled a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a0 -> b) -> Labeled a a0 -> Labeled a b #

(<$) :: a0 -> Labeled a b -> Labeled a a0 #

Foldable (Labeled a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => Labeled a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Labeled a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> Labeled a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Labeled a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Labeled a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Labeled a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Labeled a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Labeled a a0 -> a0 #

toList :: Labeled a a0 -> [a0] #

null :: Labeled a a0 -> Bool #

length :: Labeled a a0 -> Int #

elem :: Eq a0 => a0 -> Labeled a a0 -> Bool #

maximum :: Ord a0 => Labeled a a0 -> a0 #

minimum :: Ord a0 => Labeled a a0 -> a0 #

sum :: Num a0 => Labeled a a0 -> a0 #

product :: Num a0 => Labeled a a0 -> a0 #

Traversable (Labeled a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

sequenceA :: Applicative f => Labeled a (f a0) -> f (Labeled a a0) #

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

sequence :: Monad m => Labeled a (m a0) -> m (Labeled a a0) #

(Eq a, Eq b) => Eq (Labeled a b) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: Labeled a b -> Labeled a b -> Bool #

(/=) :: Labeled a b -> Labeled a b -> Bool #

(Ord a, Ord b) => Ord (Labeled a b) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: Labeled a b -> Labeled a b -> Ordering #

(<) :: Labeled a b -> Labeled a b -> Bool #

(<=) :: Labeled a b -> Labeled a b -> Bool #

(>) :: Labeled a b -> Labeled a b -> Bool #

(>=) :: Labeled a b -> Labeled a b -> Bool #

max :: Labeled a b -> Labeled a b -> Labeled a b #

min :: Labeled a b -> Labeled a b -> Labeled a b #

(Show a, Show b) => Show (Labeled a b) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> Labeled a b -> ShowS #

show :: Labeled a b -> String #

showList :: [Labeled a b] -> ShowS #

Generic (Labeled a b) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Labeled a b) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Labeled a b) = D1 (MetaData "Labeled" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "Labeled" PrefixI True) (S1 (MetaSel (Just "lblLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "lblSep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Just "lblValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b))))

data OneOrDelimited a Source #

Constructors

One a 
Many (DelimitedNonEmpty a) 
Instances
Functor OneOrDelimited Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable OneOrDelimited Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: OneOrDelimited a -> [a] #

null :: OneOrDelimited a -> Bool #

length :: OneOrDelimited a -> Int #

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

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

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

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

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

Traversable OneOrDelimited Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (OneOrDelimited a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

type Rep (OneOrDelimited a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (OneOrDelimited a) = D1 (MetaData "OneOrDelimited" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "One" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Many" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DelimitedNonEmpty a))))

data Kind a Source #

Instances
Functor Kind Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Kind Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Kind a -> [a] #

null :: Kind a -> Bool #

length :: Kind a -> Int #

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

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

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

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

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

Traversable Kind Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Kind a -> Kind a -> Ordering #

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

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

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

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

max :: Kind a -> Kind a -> Kind a #

min :: Kind a -> Kind a -> Kind a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Kind a -> String #

showList :: [Kind a] -> ShowS #

Generic (Kind a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Kind a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Kind a) = D1 (MetaData "Kind" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) ((C1 (MetaCons "KindName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QualifiedName (ProperName KindName)))) :+: C1 (MetaCons "KindArr" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Kind a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Kind a))))) :+: (C1 (MetaCons "KindRow" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Kind a)))) :+: C1 (MetaCons "KindParens" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Wrapped (Kind a))))))

data Type a Source #

Instances
Functor Type Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Type Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Type a -> [a] #

null :: Type a -> Bool #

length :: Type a -> Int #

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

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

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

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

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

Traversable Type Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Type a -> Type a -> Ordering #

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

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

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

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

max :: Type a -> Type a -> Type a #

min :: Type a -> Type a -> Type a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Type a -> String #

showList :: [Type a] -> ShowS #

Generic (Type a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Type a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Type a) = D1 (MetaData "Type" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) ((((C1 (MetaCons "TypeVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name Ident))) :+: C1 (MetaCons "TypeConstructor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QualifiedName (ProperName TypeName))))) :+: (C1 (MetaCons "TypeWildcard" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken)) :+: C1 (MetaCons "TypeHole" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name Ident))))) :+: ((C1 (MetaCons "TypeString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PSString))) :+: C1 (MetaCons "TypeRow" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Wrapped (Row a))))) :+: (C1 (MetaCons "TypeRecord" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Wrapped (Row a)))) :+: C1 (MetaCons "TypeForall" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (TypeVarBinding a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a)))))))) :+: (((C1 (MetaCons "TypeKinded" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Kind a)))) :+: C1 (MetaCons "TypeApp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a))))) :+: (C1 (MetaCons "TypeOp" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QualifiedName (OpName TypeOpName))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a)))) :+: C1 (MetaCons "TypeOpName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QualifiedName (OpName TypeOpName)))))) :+: ((C1 (MetaCons "TypeArr" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a)))) :+: C1 (MetaCons "TypeArrName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken))) :+: (C1 (MetaCons "TypeConstrained" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Constraint a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a)))) :+: C1 (MetaCons "TypeParens" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Wrapped (Type a))))))))

data TypeVarBinding a Source #

Instances
Functor TypeVarBinding Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable TypeVarBinding Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: TypeVarBinding a -> [a] #

null :: TypeVarBinding a -> Bool #

length :: TypeVarBinding a -> Int #

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

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

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

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

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

Traversable TypeVarBinding Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (TypeVarBinding a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

type Rep (TypeVarBinding a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (TypeVarBinding a) = D1 (MetaData "TypeVarBinding" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "TypeVarKinded" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Wrapped (Labeled (Name Ident) (Kind a))))) :+: C1 (MetaCons "TypeVarName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name Ident))))

data Constraint a Source #

Instances
Functor Constraint Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Constraint Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Constraint a -> [a] #

null :: Constraint a -> Bool #

length :: Constraint a -> Int #

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

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

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

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

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

Traversable Constraint Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (Constraint a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Constraint a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data Row a Source #

Constructors

Row 
Instances
Functor Row Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Row Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Row a -> [a] #

null :: Row a -> Bool #

length :: Row a -> Int #

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

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

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

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

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

Traversable Row Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Row a -> Row a -> Ordering #

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

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

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

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

max :: Row a -> Row a -> Row a #

min :: Row a -> Row a -> Row a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Row a -> String #

showList :: [Row a] -> ShowS #

Generic (Row a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Row a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Row a) = D1 (MetaData "Row" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "Row" PrefixI True) (S1 (MetaSel (Just "rowLabels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Separated (Labeled Label (Type a))))) :*: S1 (MetaSel (Just "rowTail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (SourceToken, Type a)))))

data Module a Source #

Instances
Functor Module Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Module Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Module a -> [a] #

null :: Module a -> Bool #

length :: Module a -> Int #

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

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

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

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

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

Traversable Module Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Module a -> Module a -> Ordering #

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

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

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

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

max :: Module a -> Module a -> Module a #

min :: Module a -> Module a -> Module a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Module a -> String #

showList :: [Module a] -> ShowS #

Generic (Module a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Module a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data Export a Source #

Instances
Functor Export Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Export Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Export a -> [a] #

null :: Export a -> Bool #

length :: Export a -> Int #

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

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

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

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

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

Traversable Export Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Export a -> Export a -> Ordering #

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

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

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

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

max :: Export a -> Export a -> Export a #

min :: Export a -> Export a -> Export a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Export a -> String #

showList :: [Export a] -> ShowS #

Generic (Export a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Export a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Export a) = D1 (MetaData "Export" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) ((C1 (MetaCons "ExportValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name Ident))) :+: (C1 (MetaCons "ExportOp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (OpName ValueOpName)))) :+: C1 (MetaCons "ExportType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (ProperName TypeName))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (DataMembers a))))))) :+: ((C1 (MetaCons "ExportTypeOp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (OpName TypeOpName))))) :+: C1 (MetaCons "ExportClass" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (ProperName ClassName)))))) :+: (C1 (MetaCons "ExportKind" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (ProperName KindName))))) :+: C1 (MetaCons "ExportModule" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name ModuleName)))))))

data DataMembers a Source #

Instances
Functor DataMembers Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable DataMembers Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: DataMembers a -> [a] #

null :: DataMembers a -> Bool #

length :: DataMembers a -> Int #

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

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

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

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

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

Traversable DataMembers Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (DataMembers a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (DataMembers a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data Declaration a Source #

Instances
Functor Declaration Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Declaration Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Declaration a -> [a] #

null :: Declaration a -> Bool #

length :: Declaration a -> Int #

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

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

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

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

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

Traversable Declaration Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (Declaration a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Declaration a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Declaration a) = D1 (MetaData "Declaration" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (((C1 (MetaCons "DeclData" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DataHead a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (SourceToken, Separated (DataCtor a)))))) :+: C1 (MetaCons "DeclType" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DataHead a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a))))) :+: (C1 (MetaCons "DeclNewtype" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DataHead a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (ProperName ConstructorName))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a))))) :+: (C1 (MetaCons "DeclClass" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ClassHead a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (SourceToken, NonEmpty (Labeled (Name Ident) (Type a))))))) :+: C1 (MetaCons "DeclInstanceChain" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Separated (Instance a))))))) :+: ((C1 (MetaCons "DeclDerive" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SourceToken)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InstanceHead a)))) :+: C1 (MetaCons "DeclSignature" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Labeled (Name Ident) (Type a))))) :+: (C1 (MetaCons "DeclValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ValueBindingFields a))) :+: (C1 (MetaCons "DeclFixity" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FixityFields)) :+: C1 (MetaCons "DeclForeign" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Foreign a))))))))

data Instance a Source #

Instances
Functor Instance Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Instance Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Instance a -> [a] #

null :: Instance a -> Bool #

length :: Instance a -> Int #

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

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

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

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

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

Traversable Instance Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Instance a -> Instance a -> Ordering #

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

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

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

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

max :: Instance a -> Instance a -> Instance a #

min :: Instance a -> Instance a -> Instance a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Instance a -> String #

showList :: [Instance a] -> ShowS #

Generic (Instance a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Instance a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Instance a) = D1 (MetaData "Instance" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "Instance" PrefixI True) (S1 (MetaSel (Just "instHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InstanceHead a)) :*: S1 (MetaSel (Just "instBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (SourceToken, NonEmpty (InstanceBinding a))))))

data InstanceBinding a Source #

Instances
Functor InstanceBinding Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable InstanceBinding Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: InstanceBinding a -> [a] #

null :: InstanceBinding a -> Bool #

length :: InstanceBinding a -> Int #

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

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

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

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

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

Traversable InstanceBinding Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (InstanceBinding a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

type Rep (InstanceBinding a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data ImportDecl a Source #

Instances
Functor ImportDecl Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable ImportDecl Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: ImportDecl a -> [a] #

null :: ImportDecl a -> Bool #

length :: ImportDecl a -> Int #

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

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

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

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

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

Traversable ImportDecl Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (ImportDecl a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (ImportDecl a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data Import a Source #

Instances
Functor Import Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Import Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Import a -> [a] #

null :: Import a -> Bool #

length :: Import a -> Int #

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

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

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

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

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

Traversable Import Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Import a -> Import a -> Ordering #

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

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

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

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

max :: Import a -> Import a -> Import a #

min :: Import a -> Import a -> Import a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Import a -> String #

showList :: [Import a] -> ShowS #

Generic (Import a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Import a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Import a) = D1 (MetaData "Import" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) ((C1 (MetaCons "ImportValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name Ident))) :+: (C1 (MetaCons "ImportOp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (OpName ValueOpName)))) :+: C1 (MetaCons "ImportType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (ProperName TypeName))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (DataMembers a))))))) :+: (C1 (MetaCons "ImportTypeOp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (OpName TypeOpName))))) :+: (C1 (MetaCons "ImportClass" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (ProperName ClassName))))) :+: C1 (MetaCons "ImportKind" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (ProperName KindName))))))))

data DataHead a Source #

Instances
Functor DataHead Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable DataHead Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: DataHead a -> [a] #

null :: DataHead a -> Bool #

length :: DataHead a -> Int #

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

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

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

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

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

Traversable DataHead Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: DataHead a -> DataHead a -> Ordering #

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

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

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

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

max :: DataHead a -> DataHead a -> DataHead a #

min :: DataHead a -> DataHead a -> DataHead a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: DataHead a -> String #

showList :: [DataHead a] -> ShowS #

Generic (DataHead a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (DataHead a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (DataHead a) = D1 (MetaData "DataHead" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "DataHead" PrefixI True) (S1 (MetaSel (Just "dataHdKeyword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: (S1 (MetaSel (Just "dataHdName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (ProperName TypeName))) :*: S1 (MetaSel (Just "dataHdVars") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeVarBinding a]))))

data DataCtor a Source #

Instances
Functor DataCtor Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable DataCtor Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: DataCtor a -> [a] #

null :: DataCtor a -> Bool #

length :: DataCtor a -> Int #

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

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

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

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

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

Traversable DataCtor Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: DataCtor a -> DataCtor a -> Ordering #

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

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

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

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

max :: DataCtor a -> DataCtor a -> DataCtor a #

min :: DataCtor a -> DataCtor a -> DataCtor a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: DataCtor a -> String #

showList :: [DataCtor a] -> ShowS #

Generic (DataCtor a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (DataCtor a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (DataCtor a) = D1 (MetaData "DataCtor" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "DataCtor" PrefixI True) (S1 (MetaSel (Just "dataCtorAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "dataCtorName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name (ProperName ConstructorName))) :*: S1 (MetaSel (Just "dataCtorFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type a]))))

data ClassHead a Source #

Instances
Functor ClassHead Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable ClassHead Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: ClassHead a -> [a] #

null :: ClassHead a -> Bool #

length :: ClassHead a -> Int #

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

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

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

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

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

Traversable ClassHead Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (ClassHead a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (ClassHead a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data ClassFundep Source #

Instances
Eq ClassFundep Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord ClassFundep Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show ClassFundep Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic ClassFundep Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep ClassFundep :: Type -> Type #

type Rep ClassFundep Source # 
Instance details

Defined in Language.PureScript.CST.Types

data InstanceHead a Source #

Instances
Functor InstanceHead Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable InstanceHead Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: InstanceHead a -> [a] #

null :: InstanceHead a -> Bool #

length :: InstanceHead a -> Int #

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

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

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

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

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

Traversable InstanceHead Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (InstanceHead a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (InstanceHead a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data Fixity Source #

Constructors

Infix 
Infixl 
Infixr 
Instances
Eq Fixity Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Ord Fixity Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show Fixity Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic Fixity Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

type Rep Fixity Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep Fixity = D1 (MetaData "Fixity" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "Infix" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Infixl" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Infixr" PrefixI False) (U1 :: Type -> Type)))

data FixityOp Source #

Instances
Eq FixityOp Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord FixityOp Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show FixityOp Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic FixityOp Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep FixityOp :: Type -> Type #

Methods

from :: FixityOp -> Rep FixityOp x #

to :: Rep FixityOp x -> FixityOp #

type Rep FixityOp Source # 
Instance details

Defined in Language.PureScript.CST.Types

data FixityFields Source #

Instances
Eq FixityFields Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord FixityFields Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show FixityFields Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic FixityFields Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep FixityFields :: Type -> Type #

type Rep FixityFields Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep FixityFields = D1 (MetaData "FixityFields" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "FixityFields" PrefixI True) (S1 (MetaSel (Just "fxtKeyword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SourceToken, Fixity)) :*: (S1 (MetaSel (Just "fxtPrec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SourceToken, Integer)) :*: S1 (MetaSel (Just "fxtOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FixityOp))))

data ValueBindingFields a Source #

Constructors

ValueBindingFields 
Instances
Functor ValueBindingFields Source # 
Instance details

Defined in Language.PureScript.CST.Types

Foldable ValueBindingFields Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: ValueBindingFields a -> [a] #

null :: ValueBindingFields a -> Bool #

length :: ValueBindingFields a -> Int #

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

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

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

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

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

Traversable ValueBindingFields Source # 
Instance details

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (ValueBindingFields a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

type Rep (ValueBindingFields a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (ValueBindingFields a) = D1 (MetaData "ValueBindingFields" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "ValueBindingFields" PrefixI True) (S1 (MetaSel (Just "valName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name Ident)) :*: (S1 (MetaSel (Just "valBinders") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Binder a]) :*: S1 (MetaSel (Just "valGuarded") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Guarded a)))))

data Guarded a Source #

Instances
Functor Guarded Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Guarded Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Guarded a -> [a] #

null :: Guarded a -> Bool #

length :: Guarded a -> Int #

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

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

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

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

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

Traversable Guarded Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Guarded a -> Guarded a -> Ordering #

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

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

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

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

max :: Guarded a -> Guarded a -> Guarded a #

min :: Guarded a -> Guarded a -> Guarded a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Guarded a -> String #

showList :: [Guarded a] -> ShowS #

Generic (Guarded a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Guarded a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data GuardedExpr a Source #

Instances
Functor GuardedExpr Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable GuardedExpr Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: GuardedExpr a -> [a] #

null :: GuardedExpr a -> Bool #

length :: GuardedExpr a -> Int #

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

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

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

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

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

Traversable GuardedExpr Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (GuardedExpr a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (GuardedExpr a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data PatternGuard a Source #

Constructors

PatternGuard 
Instances
Functor PatternGuard Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable PatternGuard Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: PatternGuard a -> [a] #

null :: PatternGuard a -> Bool #

length :: PatternGuard a -> Int #

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

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

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

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

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

Traversable PatternGuard Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

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

Defined in Language.PureScript.CST.Types

Generic (PatternGuard a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (PatternGuard a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (PatternGuard a) = D1 (MetaData "PatternGuard" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "PatternGuard" PrefixI True) (S1 (MetaSel (Just "patBinder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Binder a, SourceToken))) :*: S1 (MetaSel (Just "patExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a))))

data Foreign a Source #

Instances
Functor Foreign Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Foreign Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Foreign a -> [a] #

null :: Foreign a -> Bool #

length :: Foreign a -> Int #

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

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

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

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

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

Traversable Foreign Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

Defined in Language.PureScript.CST.Types

Methods

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

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

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

Defined in Language.PureScript.CST.Types

Methods

compare :: Foreign a -> Foreign a -> Ordering #

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

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

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

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

max :: Foreign a -> Foreign a -> Foreign a #

min :: Foreign a -> Foreign a -> Foreign a #

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

Defined in Language.PureScript.CST.Types

Methods

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

show :: Foreign a -> String #

showList :: [Foreign a] -> ShowS #

Generic (Foreign a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

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

Methods

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

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

type Rep (Foreign a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data Expr a Source #

Instances
Functor Expr Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

Foldable Expr Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

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

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

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

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

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

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

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

toList :: Expr a -> [a] #

null :: Expr a -> Bool #

length :: Expr a -> Int #

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

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

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

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

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

Traversable Expr Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

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

sequenceA :: Applicative f => Expr (f a) -> f (Expr a) #

mapM :: Monad m => (a -> m b) -> Expr a -> m (Expr b) #

sequence :: Monad m => Expr (m a) -> m (Expr a) #

Eq a => Eq (Expr a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: Expr a -> Expr a -> Bool #

(/=) :: Expr a -> Expr a -> Bool #

Ord a => Ord (Expr a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: Expr a -> Expr a -> Ordering #

(<) :: Expr a -> Expr a -> Bool #

(<=) :: Expr a -> Expr a -> Bool #

(>) :: Expr a -> Expr a -> Bool #

(>=) :: Expr a -> Expr a -> Bool #

max :: Expr a -> Expr a -> Expr a #

min :: Expr a -> Expr a -> Expr a #

Show a => Show (Expr a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> Expr a -> ShowS #

show :: Expr a -> String #

showList :: [Expr a] -> ShowS #

Generic (Expr a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (Expr a) :: Type -> Type #

Methods

from :: Expr a -> Rep (Expr a) x #

to :: Rep (Expr a) x -> Expr a #

type Rep (Expr a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Expr a) = D1 (MetaData "Expr" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) ((((C1 (MetaCons "ExprHole" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name Ident))) :+: (C1 (MetaCons "ExprSection" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken)) :+: C1 (MetaCons "ExprIdent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QualifiedName Ident))))) :+: (C1 (MetaCons "ExprConstructor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QualifiedName (ProperName ConstructorName)))) :+: (C1 (MetaCons "ExprBoolean" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) :+: C1 (MetaCons "ExprChar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)))))) :+: ((C1 (MetaCons "ExprString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PSString))) :+: (C1 (MetaCons "ExprNumber" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Integer Double)))) :+: C1 (MetaCons "ExprArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Delimited (Expr a)))))) :+: (C1 (MetaCons "ExprRecord" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Delimited (RecordLabeled (Expr a))))) :+: (C1 (MetaCons "ExprParens" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Wrapped (Expr a)))) :+: C1 (MetaCons "ExprTyped" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a)))))))) :+: (((C1 (MetaCons "ExprInfix" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Wrapped (Expr a))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a)))) :+: (C1 (MetaCons "ExprOp" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QualifiedName (OpName ValueOpName))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a)))) :+: C1 (MetaCons "ExprOpName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QualifiedName (OpName ValueOpName)))))) :+: (C1 (MetaCons "ExprNegate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a)))) :+: (C1 (MetaCons "ExprRecordAccessor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RecordAccessor a))) :+: C1 (MetaCons "ExprRecordUpdate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DelimitedNonEmpty (RecordUpdate a)))))))) :+: ((C1 (MetaCons "ExprApp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a)))) :+: (C1 (MetaCons "ExprLambda" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Lambda a))) :+: C1 (MetaCons "ExprIf" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IfThenElse a))))) :+: ((C1 (MetaCons "ExprCase" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CaseOf a))) :+: C1 (MetaCons "ExprLet" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (LetIn a)))) :+: (C1 (MetaCons "ExprDo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DoBlock a))) :+: C1 (MetaCons "ExprAdo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AdoBlock a))))))))

data RecordLabeled a Source #

Instances
Functor RecordLabeled Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> RecordLabeled a -> RecordLabeled b #

(<$) :: a -> RecordLabeled b -> RecordLabeled a #

Foldable RecordLabeled Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => RecordLabeled m -> m #

foldMap :: Monoid m => (a -> m) -> RecordLabeled a -> m #

foldr :: (a -> b -> b) -> b -> RecordLabeled a -> b #

foldr' :: (a -> b -> b) -> b -> RecordLabeled a -> b #

foldl :: (b -> a -> b) -> b -> RecordLabeled a -> b #

foldl' :: (b -> a -> b) -> b -> RecordLabeled a -> b #

foldr1 :: (a -> a -> a) -> RecordLabeled a -> a #

foldl1 :: (a -> a -> a) -> RecordLabeled a -> a #

toList :: RecordLabeled a -> [a] #

null :: RecordLabeled a -> Bool #

length :: RecordLabeled a -> Int #

elem :: Eq a => a -> RecordLabeled a -> Bool #

maximum :: Ord a => RecordLabeled a -> a #

minimum :: Ord a => RecordLabeled a -> a #

sum :: Num a => RecordLabeled a -> a #

product :: Num a => RecordLabeled a -> a #

Traversable RecordLabeled Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> RecordLabeled a -> f (RecordLabeled b) #

sequenceA :: Applicative f => RecordLabeled (f a) -> f (RecordLabeled a) #

mapM :: Monad m => (a -> m b) -> RecordLabeled a -> m (RecordLabeled b) #

sequence :: Monad m => RecordLabeled (m a) -> m (RecordLabeled a) #

Eq a => Eq (RecordLabeled a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord a => Ord (RecordLabeled a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show a => Show (RecordLabeled a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic (RecordLabeled a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (RecordLabeled a) :: Type -> Type #

type Rep (RecordLabeled a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data RecordUpdate a Source #

Instances
Functor RecordUpdate Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> RecordUpdate a -> RecordUpdate b #

(<$) :: a -> RecordUpdate b -> RecordUpdate a #

Foldable RecordUpdate Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => RecordUpdate m -> m #

foldMap :: Monoid m => (a -> m) -> RecordUpdate a -> m #

foldr :: (a -> b -> b) -> b -> RecordUpdate a -> b #

foldr' :: (a -> b -> b) -> b -> RecordUpdate a -> b #

foldl :: (b -> a -> b) -> b -> RecordUpdate a -> b #

foldl' :: (b -> a -> b) -> b -> RecordUpdate a -> b #

foldr1 :: (a -> a -> a) -> RecordUpdate a -> a #

foldl1 :: (a -> a -> a) -> RecordUpdate a -> a #

toList :: RecordUpdate a -> [a] #

null :: RecordUpdate a -> Bool #

length :: RecordUpdate a -> Int #

elem :: Eq a => a -> RecordUpdate a -> Bool #

maximum :: Ord a => RecordUpdate a -> a #

minimum :: Ord a => RecordUpdate a -> a #

sum :: Num a => RecordUpdate a -> a #

product :: Num a => RecordUpdate a -> a #

Traversable RecordUpdate Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> RecordUpdate a -> f (RecordUpdate b) #

sequenceA :: Applicative f => RecordUpdate (f a) -> f (RecordUpdate a) #

mapM :: Monad m => (a -> m b) -> RecordUpdate a -> m (RecordUpdate b) #

sequence :: Monad m => RecordUpdate (m a) -> m (RecordUpdate a) #

Eq a => Eq (RecordUpdate a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord a => Ord (RecordUpdate a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show a => Show (RecordUpdate a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic (RecordUpdate a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (RecordUpdate a) :: Type -> Type #

Methods

from :: RecordUpdate a -> Rep (RecordUpdate a) x #

to :: Rep (RecordUpdate a) x -> RecordUpdate a #

type Rep (RecordUpdate a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data RecordAccessor a Source #

Instances
Functor RecordAccessor Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> RecordAccessor a -> RecordAccessor b #

(<$) :: a -> RecordAccessor b -> RecordAccessor a #

Foldable RecordAccessor Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => RecordAccessor m -> m #

foldMap :: Monoid m => (a -> m) -> RecordAccessor a -> m #

foldr :: (a -> b -> b) -> b -> RecordAccessor a -> b #

foldr' :: (a -> b -> b) -> b -> RecordAccessor a -> b #

foldl :: (b -> a -> b) -> b -> RecordAccessor a -> b #

foldl' :: (b -> a -> b) -> b -> RecordAccessor a -> b #

foldr1 :: (a -> a -> a) -> RecordAccessor a -> a #

foldl1 :: (a -> a -> a) -> RecordAccessor a -> a #

toList :: RecordAccessor a -> [a] #

null :: RecordAccessor a -> Bool #

length :: RecordAccessor a -> Int #

elem :: Eq a => a -> RecordAccessor a -> Bool #

maximum :: Ord a => RecordAccessor a -> a #

minimum :: Ord a => RecordAccessor a -> a #

sum :: Num a => RecordAccessor a -> a #

product :: Num a => RecordAccessor a -> a #

Traversable RecordAccessor Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> RecordAccessor a -> f (RecordAccessor b) #

sequenceA :: Applicative f => RecordAccessor (f a) -> f (RecordAccessor a) #

mapM :: Monad m => (a -> m b) -> RecordAccessor a -> m (RecordAccessor b) #

sequence :: Monad m => RecordAccessor (m a) -> m (RecordAccessor a) #

Eq a => Eq (RecordAccessor a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord a => Ord (RecordAccessor a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show a => Show (RecordAccessor a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic (RecordAccessor a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (RecordAccessor a) :: Type -> Type #

type Rep (RecordAccessor a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (RecordAccessor a) = D1 (MetaData "RecordAccessor" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "RecordAccessor" PrefixI True) (S1 (MetaSel (Just "recExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a)) :*: (S1 (MetaSel (Just "recDot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Just "recPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Separated Label)))))

data Lambda a Source #

Instances
Functor Lambda Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> Lambda a -> Lambda b #

(<$) :: a -> Lambda b -> Lambda a #

Foldable Lambda Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => Lambda m -> m #

foldMap :: Monoid m => (a -> m) -> Lambda a -> m #

foldr :: (a -> b -> b) -> b -> Lambda a -> b #

foldr' :: (a -> b -> b) -> b -> Lambda a -> b #

foldl :: (b -> a -> b) -> b -> Lambda a -> b #

foldl' :: (b -> a -> b) -> b -> Lambda a -> b #

foldr1 :: (a -> a -> a) -> Lambda a -> a #

foldl1 :: (a -> a -> a) -> Lambda a -> a #

toList :: Lambda a -> [a] #

null :: Lambda a -> Bool #

length :: Lambda a -> Int #

elem :: Eq a => a -> Lambda a -> Bool #

maximum :: Ord a => Lambda a -> a #

minimum :: Ord a => Lambda a -> a #

sum :: Num a => Lambda a -> a #

product :: Num a => Lambda a -> a #

Traversable Lambda Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> Lambda a -> f (Lambda b) #

sequenceA :: Applicative f => Lambda (f a) -> f (Lambda a) #

mapM :: Monad m => (a -> m b) -> Lambda a -> m (Lambda b) #

sequence :: Monad m => Lambda (m a) -> m (Lambda a) #

Eq a => Eq (Lambda a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: Lambda a -> Lambda a -> Bool #

(/=) :: Lambda a -> Lambda a -> Bool #

Ord a => Ord (Lambda a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: Lambda a -> Lambda a -> Ordering #

(<) :: Lambda a -> Lambda a -> Bool #

(<=) :: Lambda a -> Lambda a -> Bool #

(>) :: Lambda a -> Lambda a -> Bool #

(>=) :: Lambda a -> Lambda a -> Bool #

max :: Lambda a -> Lambda a -> Lambda a #

min :: Lambda a -> Lambda a -> Lambda a #

Show a => Show (Lambda a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> Lambda a -> ShowS #

show :: Lambda a -> String #

showList :: [Lambda a] -> ShowS #

Generic (Lambda a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (Lambda a) :: Type -> Type #

Methods

from :: Lambda a -> Rep (Lambda a) x #

to :: Rep (Lambda a) x -> Lambda a #

type Rep (Lambda a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data IfThenElse a Source #

Instances
Functor IfThenElse Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> IfThenElse a -> IfThenElse b #

(<$) :: a -> IfThenElse b -> IfThenElse a #

Foldable IfThenElse Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => IfThenElse m -> m #

foldMap :: Monoid m => (a -> m) -> IfThenElse a -> m #

foldr :: (a -> b -> b) -> b -> IfThenElse a -> b #

foldr' :: (a -> b -> b) -> b -> IfThenElse a -> b #

foldl :: (b -> a -> b) -> b -> IfThenElse a -> b #

foldl' :: (b -> a -> b) -> b -> IfThenElse a -> b #

foldr1 :: (a -> a -> a) -> IfThenElse a -> a #

foldl1 :: (a -> a -> a) -> IfThenElse a -> a #

toList :: IfThenElse a -> [a] #

null :: IfThenElse a -> Bool #

length :: IfThenElse a -> Int #

elem :: Eq a => a -> IfThenElse a -> Bool #

maximum :: Ord a => IfThenElse a -> a #

minimum :: Ord a => IfThenElse a -> a #

sum :: Num a => IfThenElse a -> a #

product :: Num a => IfThenElse a -> a #

Traversable IfThenElse Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> IfThenElse a -> f (IfThenElse b) #

sequenceA :: Applicative f => IfThenElse (f a) -> f (IfThenElse a) #

mapM :: Monad m => (a -> m b) -> IfThenElse a -> m (IfThenElse b) #

sequence :: Monad m => IfThenElse (m a) -> m (IfThenElse a) #

Eq a => Eq (IfThenElse a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: IfThenElse a -> IfThenElse a -> Bool #

(/=) :: IfThenElse a -> IfThenElse a -> Bool #

Ord a => Ord (IfThenElse a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show a => Show (IfThenElse a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic (IfThenElse a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (IfThenElse a) :: Type -> Type #

Methods

from :: IfThenElse a -> Rep (IfThenElse a) x #

to :: Rep (IfThenElse a) x -> IfThenElse a #

type Rep (IfThenElse a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data CaseOf a Source #

Instances
Functor CaseOf Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> CaseOf a -> CaseOf b #

(<$) :: a -> CaseOf b -> CaseOf a #

Foldable CaseOf Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => CaseOf m -> m #

foldMap :: Monoid m => (a -> m) -> CaseOf a -> m #

foldr :: (a -> b -> b) -> b -> CaseOf a -> b #

foldr' :: (a -> b -> b) -> b -> CaseOf a -> b #

foldl :: (b -> a -> b) -> b -> CaseOf a -> b #

foldl' :: (b -> a -> b) -> b -> CaseOf a -> b #

foldr1 :: (a -> a -> a) -> CaseOf a -> a #

foldl1 :: (a -> a -> a) -> CaseOf a -> a #

toList :: CaseOf a -> [a] #

null :: CaseOf a -> Bool #

length :: CaseOf a -> Int #

elem :: Eq a => a -> CaseOf a -> Bool #

maximum :: Ord a => CaseOf a -> a #

minimum :: Ord a => CaseOf a -> a #

sum :: Num a => CaseOf a -> a #

product :: Num a => CaseOf a -> a #

Traversable CaseOf Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> CaseOf a -> f (CaseOf b) #

sequenceA :: Applicative f => CaseOf (f a) -> f (CaseOf a) #

mapM :: Monad m => (a -> m b) -> CaseOf a -> m (CaseOf b) #

sequence :: Monad m => CaseOf (m a) -> m (CaseOf a) #

Eq a => Eq (CaseOf a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: CaseOf a -> CaseOf a -> Bool #

(/=) :: CaseOf a -> CaseOf a -> Bool #

Ord a => Ord (CaseOf a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: CaseOf a -> CaseOf a -> Ordering #

(<) :: CaseOf a -> CaseOf a -> Bool #

(<=) :: CaseOf a -> CaseOf a -> Bool #

(>) :: CaseOf a -> CaseOf a -> Bool #

(>=) :: CaseOf a -> CaseOf a -> Bool #

max :: CaseOf a -> CaseOf a -> CaseOf a #

min :: CaseOf a -> CaseOf a -> CaseOf a #

Show a => Show (CaseOf a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> CaseOf a -> ShowS #

show :: CaseOf a -> String #

showList :: [CaseOf a] -> ShowS #

Generic (CaseOf a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (CaseOf a) :: Type -> Type #

Methods

from :: CaseOf a -> Rep (CaseOf a) x #

to :: Rep (CaseOf a) x -> CaseOf a #

type Rep (CaseOf a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data LetIn a Source #

Instances
Functor LetIn Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> LetIn a -> LetIn b #

(<$) :: a -> LetIn b -> LetIn a #

Foldable LetIn Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => LetIn m -> m #

foldMap :: Monoid m => (a -> m) -> LetIn a -> m #

foldr :: (a -> b -> b) -> b -> LetIn a -> b #

foldr' :: (a -> b -> b) -> b -> LetIn a -> b #

foldl :: (b -> a -> b) -> b -> LetIn a -> b #

foldl' :: (b -> a -> b) -> b -> LetIn a -> b #

foldr1 :: (a -> a -> a) -> LetIn a -> a #

foldl1 :: (a -> a -> a) -> LetIn a -> a #

toList :: LetIn a -> [a] #

null :: LetIn a -> Bool #

length :: LetIn a -> Int #

elem :: Eq a => a -> LetIn a -> Bool #

maximum :: Ord a => LetIn a -> a #

minimum :: Ord a => LetIn a -> a #

sum :: Num a => LetIn a -> a #

product :: Num a => LetIn a -> a #

Traversable LetIn Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> LetIn a -> f (LetIn b) #

sequenceA :: Applicative f => LetIn (f a) -> f (LetIn a) #

mapM :: Monad m => (a -> m b) -> LetIn a -> m (LetIn b) #

sequence :: Monad m => LetIn (m a) -> m (LetIn a) #

Eq a => Eq (LetIn a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: LetIn a -> LetIn a -> Bool #

(/=) :: LetIn a -> LetIn a -> Bool #

Ord a => Ord (LetIn a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: LetIn a -> LetIn a -> Ordering #

(<) :: LetIn a -> LetIn a -> Bool #

(<=) :: LetIn a -> LetIn a -> Bool #

(>) :: LetIn a -> LetIn a -> Bool #

(>=) :: LetIn a -> LetIn a -> Bool #

max :: LetIn a -> LetIn a -> LetIn a #

min :: LetIn a -> LetIn a -> LetIn a #

Show a => Show (LetIn a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> LetIn a -> ShowS #

show :: LetIn a -> String #

showList :: [LetIn a] -> ShowS #

Generic (LetIn a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (LetIn a) :: Type -> Type #

Methods

from :: LetIn a -> Rep (LetIn a) x #

to :: Rep (LetIn a) x -> LetIn a #

type Rep (LetIn a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data Where a Source #

Constructors

Where 
Instances
Functor Where Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> Where a -> Where b #

(<$) :: a -> Where b -> Where a #

Foldable Where Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => Where m -> m #

foldMap :: Monoid m => (a -> m) -> Where a -> m #

foldr :: (a -> b -> b) -> b -> Where a -> b #

foldr' :: (a -> b -> b) -> b -> Where a -> b #

foldl :: (b -> a -> b) -> b -> Where a -> b #

foldl' :: (b -> a -> b) -> b -> Where a -> b #

foldr1 :: (a -> a -> a) -> Where a -> a #

foldl1 :: (a -> a -> a) -> Where a -> a #

toList :: Where a -> [a] #

null :: Where a -> Bool #

length :: Where a -> Int #

elem :: Eq a => a -> Where a -> Bool #

maximum :: Ord a => Where a -> a #

minimum :: Ord a => Where a -> a #

sum :: Num a => Where a -> a #

product :: Num a => Where a -> a #

Traversable Where Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> Where a -> f (Where b) #

sequenceA :: Applicative f => Where (f a) -> f (Where a) #

mapM :: Monad m => (a -> m b) -> Where a -> m (Where b) #

sequence :: Monad m => Where (m a) -> m (Where a) #

Eq a => Eq (Where a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: Where a -> Where a -> Bool #

(/=) :: Where a -> Where a -> Bool #

Ord a => Ord (Where a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: Where a -> Where a -> Ordering #

(<) :: Where a -> Where a -> Bool #

(<=) :: Where a -> Where a -> Bool #

(>) :: Where a -> Where a -> Bool #

(>=) :: Where a -> Where a -> Bool #

max :: Where a -> Where a -> Where a #

min :: Where a -> Where a -> Where a #

Show a => Show (Where a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> Where a -> ShowS #

show :: Where a -> String #

showList :: [Where a] -> ShowS #

Generic (Where a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (Where a) :: Type -> Type #

Methods

from :: Where a -> Rep (Where a) x #

to :: Rep (Where a) x -> Where a #

type Rep (Where a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Where a) = D1 (MetaData "Where" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "Where" PrefixI True) (S1 (MetaSel (Just "whereExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a)) :*: S1 (MetaSel (Just "whereBindings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (SourceToken, NonEmpty (LetBinding a))))))

data LetBinding a Source #

Instances
Functor LetBinding Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> LetBinding a -> LetBinding b #

(<$) :: a -> LetBinding b -> LetBinding a #

Foldable LetBinding Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => LetBinding m -> m #

foldMap :: Monoid m => (a -> m) -> LetBinding a -> m #

foldr :: (a -> b -> b) -> b -> LetBinding a -> b #

foldr' :: (a -> b -> b) -> b -> LetBinding a -> b #

foldl :: (b -> a -> b) -> b -> LetBinding a -> b #

foldl' :: (b -> a -> b) -> b -> LetBinding a -> b #

foldr1 :: (a -> a -> a) -> LetBinding a -> a #

foldl1 :: (a -> a -> a) -> LetBinding a -> a #

toList :: LetBinding a -> [a] #

null :: LetBinding a -> Bool #

length :: LetBinding a -> Int #

elem :: Eq a => a -> LetBinding a -> Bool #

maximum :: Ord a => LetBinding a -> a #

minimum :: Ord a => LetBinding a -> a #

sum :: Num a => LetBinding a -> a #

product :: Num a => LetBinding a -> a #

Traversable LetBinding Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> LetBinding a -> f (LetBinding b) #

sequenceA :: Applicative f => LetBinding (f a) -> f (LetBinding a) #

mapM :: Monad m => (a -> m b) -> LetBinding a -> m (LetBinding b) #

sequence :: Monad m => LetBinding (m a) -> m (LetBinding a) #

Eq a => Eq (LetBinding a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: LetBinding a -> LetBinding a -> Bool #

(/=) :: LetBinding a -> LetBinding a -> Bool #

Ord a => Ord (LetBinding a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show a => Show (LetBinding a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic (LetBinding a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (LetBinding a) :: Type -> Type #

Methods

from :: LetBinding a -> Rep (LetBinding a) x #

to :: Rep (LetBinding a) x -> LetBinding a #

type Rep (LetBinding a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data DoBlock a Source #

Instances
Functor DoBlock Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> DoBlock a -> DoBlock b #

(<$) :: a -> DoBlock b -> DoBlock a #

Foldable DoBlock Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => DoBlock m -> m #

foldMap :: Monoid m => (a -> m) -> DoBlock a -> m #

foldr :: (a -> b -> b) -> b -> DoBlock a -> b #

foldr' :: (a -> b -> b) -> b -> DoBlock a -> b #

foldl :: (b -> a -> b) -> b -> DoBlock a -> b #

foldl' :: (b -> a -> b) -> b -> DoBlock a -> b #

foldr1 :: (a -> a -> a) -> DoBlock a -> a #

foldl1 :: (a -> a -> a) -> DoBlock a -> a #

toList :: DoBlock a -> [a] #

null :: DoBlock a -> Bool #

length :: DoBlock a -> Int #

elem :: Eq a => a -> DoBlock a -> Bool #

maximum :: Ord a => DoBlock a -> a #

minimum :: Ord a => DoBlock a -> a #

sum :: Num a => DoBlock a -> a #

product :: Num a => DoBlock a -> a #

Traversable DoBlock Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> DoBlock a -> f (DoBlock b) #

sequenceA :: Applicative f => DoBlock (f a) -> f (DoBlock a) #

mapM :: Monad m => (a -> m b) -> DoBlock a -> m (DoBlock b) #

sequence :: Monad m => DoBlock (m a) -> m (DoBlock a) #

Eq a => Eq (DoBlock a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: DoBlock a -> DoBlock a -> Bool #

(/=) :: DoBlock a -> DoBlock a -> Bool #

Ord a => Ord (DoBlock a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: DoBlock a -> DoBlock a -> Ordering #

(<) :: DoBlock a -> DoBlock a -> Bool #

(<=) :: DoBlock a -> DoBlock a -> Bool #

(>) :: DoBlock a -> DoBlock a -> Bool #

(>=) :: DoBlock a -> DoBlock a -> Bool #

max :: DoBlock a -> DoBlock a -> DoBlock a #

min :: DoBlock a -> DoBlock a -> DoBlock a #

Show a => Show (DoBlock a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> DoBlock a -> ShowS #

show :: DoBlock a -> String #

showList :: [DoBlock a] -> ShowS #

Generic (DoBlock a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (DoBlock a) :: Type -> Type #

Methods

from :: DoBlock a -> Rep (DoBlock a) x #

to :: Rep (DoBlock a) x -> DoBlock a #

type Rep (DoBlock a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (DoBlock a) = D1 (MetaData "DoBlock" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "DoBlock" PrefixI True) (S1 (MetaSel (Just "doKeyword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Just "doStatements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (DoStatement a)))))

data DoStatement a Source #

Instances
Functor DoStatement Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> DoStatement a -> DoStatement b #

(<$) :: a -> DoStatement b -> DoStatement a #

Foldable DoStatement Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => DoStatement m -> m #

foldMap :: Monoid m => (a -> m) -> DoStatement a -> m #

foldr :: (a -> b -> b) -> b -> DoStatement a -> b #

foldr' :: (a -> b -> b) -> b -> DoStatement a -> b #

foldl :: (b -> a -> b) -> b -> DoStatement a -> b #

foldl' :: (b -> a -> b) -> b -> DoStatement a -> b #

foldr1 :: (a -> a -> a) -> DoStatement a -> a #

foldl1 :: (a -> a -> a) -> DoStatement a -> a #

toList :: DoStatement a -> [a] #

null :: DoStatement a -> Bool #

length :: DoStatement a -> Int #

elem :: Eq a => a -> DoStatement a -> Bool #

maximum :: Ord a => DoStatement a -> a #

minimum :: Ord a => DoStatement a -> a #

sum :: Num a => DoStatement a -> a #

product :: Num a => DoStatement a -> a #

Traversable DoStatement Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> DoStatement a -> f (DoStatement b) #

sequenceA :: Applicative f => DoStatement (f a) -> f (DoStatement a) #

mapM :: Monad m => (a -> m b) -> DoStatement a -> m (DoStatement b) #

sequence :: Monad m => DoStatement (m a) -> m (DoStatement a) #

Eq a => Eq (DoStatement a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Ord a => Ord (DoStatement a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Show a => Show (DoStatement a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Generic (DoStatement a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (DoStatement a) :: Type -> Type #

Methods

from :: DoStatement a -> Rep (DoStatement a) x #

to :: Rep (DoStatement a) x -> DoStatement a #

type Rep (DoStatement a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

data AdoBlock a Source #

Instances
Functor AdoBlock Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> AdoBlock a -> AdoBlock b #

(<$) :: a -> AdoBlock b -> AdoBlock a #

Foldable AdoBlock Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => AdoBlock m -> m #

foldMap :: Monoid m => (a -> m) -> AdoBlock a -> m #

foldr :: (a -> b -> b) -> b -> AdoBlock a -> b #

foldr' :: (a -> b -> b) -> b -> AdoBlock a -> b #

foldl :: (b -> a -> b) -> b -> AdoBlock a -> b #

foldl' :: (b -> a -> b) -> b -> AdoBlock a -> b #

foldr1 :: (a -> a -> a) -> AdoBlock a -> a #

foldl1 :: (a -> a -> a) -> AdoBlock a -> a #

toList :: AdoBlock a -> [a] #

null :: AdoBlock a -> Bool #

length :: AdoBlock a -> Int #

elem :: Eq a => a -> AdoBlock a -> Bool #

maximum :: Ord a => AdoBlock a -> a #

minimum :: Ord a => AdoBlock a -> a #

sum :: Num a => AdoBlock a -> a #

product :: Num a => AdoBlock a -> a #

Traversable AdoBlock Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> AdoBlock a -> f (AdoBlock b) #

sequenceA :: Applicative f => AdoBlock (f a) -> f (AdoBlock a) #

mapM :: Monad m => (a -> m b) -> AdoBlock a -> m (AdoBlock b) #

sequence :: Monad m => AdoBlock (m a) -> m (AdoBlock a) #

Eq a => Eq (AdoBlock a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: AdoBlock a -> AdoBlock a -> Bool #

(/=) :: AdoBlock a -> AdoBlock a -> Bool #

Ord a => Ord (AdoBlock a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: AdoBlock a -> AdoBlock a -> Ordering #

(<) :: AdoBlock a -> AdoBlock a -> Bool #

(<=) :: AdoBlock a -> AdoBlock a -> Bool #

(>) :: AdoBlock a -> AdoBlock a -> Bool #

(>=) :: AdoBlock a -> AdoBlock a -> Bool #

max :: AdoBlock a -> AdoBlock a -> AdoBlock a #

min :: AdoBlock a -> AdoBlock a -> AdoBlock a #

Show a => Show (AdoBlock a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> AdoBlock a -> ShowS #

show :: AdoBlock a -> String #

showList :: [AdoBlock a] -> ShowS #

Generic (AdoBlock a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (AdoBlock a) :: Type -> Type #

Methods

from :: AdoBlock a -> Rep (AdoBlock a) x #

to :: Rep (AdoBlock a) x -> AdoBlock a #

type Rep (AdoBlock a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (AdoBlock a) = D1 (MetaData "AdoBlock" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (C1 (MetaCons "AdoBlock" PrefixI True) ((S1 (MetaSel (Just "adoKeyword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Just "adoStatements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DoStatement a])) :*: (S1 (MetaSel (Just "adoIn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Just "adoResult") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr a)))))

data Binder a Source #

Instances
Functor Binder Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fmap :: (a -> b) -> Binder a -> Binder b #

(<$) :: a -> Binder b -> Binder a #

Foldable Binder Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

fold :: Monoid m => Binder m -> m #

foldMap :: Monoid m => (a -> m) -> Binder a -> m #

foldr :: (a -> b -> b) -> b -> Binder a -> b #

foldr' :: (a -> b -> b) -> b -> Binder a -> b #

foldl :: (b -> a -> b) -> b -> Binder a -> b #

foldl' :: (b -> a -> b) -> b -> Binder a -> b #

foldr1 :: (a -> a -> a) -> Binder a -> a #

foldl1 :: (a -> a -> a) -> Binder a -> a #

toList :: Binder a -> [a] #

null :: Binder a -> Bool #

length :: Binder a -> Int #

elem :: Eq a => a -> Binder a -> Bool #

maximum :: Ord a => Binder a -> a #

minimum :: Ord a => Binder a -> a #

sum :: Num a => Binder a -> a #

product :: Num a => Binder a -> a #

Traversable Binder Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

traverse :: Applicative f => (a -> f b) -> Binder a -> f (Binder b) #

sequenceA :: Applicative f => Binder (f a) -> f (Binder a) #

mapM :: Monad m => (a -> m b) -> Binder a -> m (Binder b) #

sequence :: Monad m => Binder (m a) -> m (Binder a) #

Eq a => Eq (Binder a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

(==) :: Binder a -> Binder a -> Bool #

(/=) :: Binder a -> Binder a -> Bool #

Ord a => Ord (Binder a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

compare :: Binder a -> Binder a -> Ordering #

(<) :: Binder a -> Binder a -> Bool #

(<=) :: Binder a -> Binder a -> Bool #

(>) :: Binder a -> Binder a -> Bool #

(>=) :: Binder a -> Binder a -> Bool #

max :: Binder a -> Binder a -> Binder a #

min :: Binder a -> Binder a -> Binder a #

Show a => Show (Binder a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Methods

showsPrec :: Int -> Binder a -> ShowS #

show :: Binder a -> String #

showList :: [Binder a] -> ShowS #

Generic (Binder a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

Associated Types

type Rep (Binder a) :: Type -> Type #

Methods

from :: Binder a -> Rep (Binder a) x #

to :: Rep (Binder a) x -> Binder a #

type Rep (Binder a) Source # 
Instance details

Defined in Language.PureScript.CST.Types

type Rep (Binder a) = D1 (MetaData "Binder" "Language.PureScript.CST.Types" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" False) (((C1 (MetaCons "BinderWildcard" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken)) :+: (C1 (MetaCons "BinderVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name Ident))) :+: C1 (MetaCons "BinderNamed" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Name Ident))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Binder a)))))) :+: (C1 (MetaCons "BinderConstructor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QualifiedName (ProperName ConstructorName))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Binder a]))) :+: (C1 (MetaCons "BinderBoolean" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) :+: C1 (MetaCons "BinderChar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)))))) :+: ((C1 (MetaCons "BinderString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PSString))) :+: (C1 (MetaCons "BinderNumber" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SourceToken))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Integer Double)))) :+: C1 (MetaCons "BinderArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Delimited (Binder a)))))) :+: ((C1 (MetaCons "BinderRecord" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Delimited (RecordLabeled (Binder a))))) :+: C1 (MetaCons "BinderParens" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Wrapped (Binder a))))) :+: (C1 (MetaCons "BinderTyped" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Binder a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceToken) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type a)))) :+: C1 (MetaCons "BinderOp" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Binder a))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QualifiedName (OpName ValueOpName))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Binder a))))))))