elm-syntax-0.1.0.0: Elm syntax and pretty-printing

Safe HaskellNone
LanguageHaskell2010

Language.Elm.Name

Documentation

type Module = [Text] Source #

newtype Local Source #

Constructors

Local Text 
Instances
Eq Local Source # 
Instance details

Defined in Language.Elm.Name

Methods

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

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

Ord Local Source # 
Instance details

Defined in Language.Elm.Name

Methods

compare :: Local -> Local -> Ordering #

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

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

(>) :: Local -> Local -> Bool #

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

max :: Local -> Local -> Local #

min :: Local -> Local -> Local #

Show Local Source # 
Instance details

Defined in Language.Elm.Name

Methods

showsPrec :: Int -> Local -> ShowS #

show :: Local -> String #

showList :: [Local] -> ShowS #

IsString Local Source # 
Instance details

Defined in Language.Elm.Name

Methods

fromString :: String -> Local #

Generic Local Source # 
Instance details

Defined in Language.Elm.Name

Associated Types

type Rep Local :: Type -> Type #

Methods

from :: Local -> Rep Local x #

to :: Rep Local x -> Local #

Hashable Local Source # 
Instance details

Defined in Language.Elm.Name

Methods

hashWithSalt :: Int -> Local -> Int #

hash :: Local -> Int #

type Rep Local Source # 
Instance details

Defined in Language.Elm.Name

type Rep Local = D1 (MetaData "Local" "Language.Elm.Name" "elm-syntax-0.1.0.0-HzVRNvYqSxCGwv3BbwGjH7" True) (C1 (MetaCons "Local" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Qualified Source #

Constructors

Qualified Module Text 
Instances
Eq Qualified Source # 
Instance details

Defined in Language.Elm.Name

Ord Qualified Source # 
Instance details

Defined in Language.Elm.Name

Show Qualified Source # 
Instance details

Defined in Language.Elm.Name

IsString Qualified Source # 
Instance details

Defined in Language.Elm.Name

Generic Qualified Source # 
Instance details

Defined in Language.Elm.Name

Associated Types

type Rep Qualified :: Type -> Type #

Hashable Qualified Source # 
Instance details

Defined in Language.Elm.Name

type Rep Qualified Source # 
Instance details

Defined in Language.Elm.Name

type Rep Qualified = D1 (MetaData "Qualified" "Language.Elm.Name" "elm-syntax-0.1.0.0-HzVRNvYqSxCGwv3BbwGjH7" False) (C1 (MetaCons "Qualified" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Module) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Field Source #

Constructors

Field Text 
Instances
Eq Field Source # 
Instance details

Defined in Language.Elm.Name

Methods

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

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

Ord Field Source # 
Instance details

Defined in Language.Elm.Name

Methods

compare :: Field -> Field -> Ordering #

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

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

(>) :: Field -> Field -> Bool #

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

max :: Field -> Field -> Field #

min :: Field -> Field -> Field #

Show Field Source # 
Instance details

Defined in Language.Elm.Name

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

IsString Field Source # 
Instance details

Defined in Language.Elm.Name

Methods

fromString :: String -> Field #

Generic Field Source # 
Instance details

Defined in Language.Elm.Name

Associated Types

type Rep Field :: Type -> Type #

Methods

from :: Field -> Rep Field x #

to :: Rep Field x -> Field #

Hashable Field Source # 
Instance details

Defined in Language.Elm.Name

Methods

hashWithSalt :: Int -> Field -> Int #

hash :: Field -> Int #

type Rep Field Source # 
Instance details

Defined in Language.Elm.Name

type Rep Field = D1 (MetaData "Field" "Language.Elm.Name" "elm-syntax-0.1.0.0-HzVRNvYqSxCGwv3BbwGjH7" True) (C1 (MetaCons "Field" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Constructor Source #

Constructors

Constructor Text 
Instances
Eq Constructor Source # 
Instance details

Defined in Language.Elm.Name

Ord Constructor Source # 
Instance details

Defined in Language.Elm.Name

Show Constructor Source # 
Instance details

Defined in Language.Elm.Name

IsString Constructor Source # 
Instance details

Defined in Language.Elm.Name

Generic Constructor Source # 
Instance details

Defined in Language.Elm.Name

Associated Types

type Rep Constructor :: Type -> Type #

Hashable Constructor Source # 
Instance details

Defined in Language.Elm.Name

type Rep Constructor Source # 
Instance details

Defined in Language.Elm.Name

type Rep Constructor = D1 (MetaData "Constructor" "Language.Elm.Name" "elm-syntax-0.1.0.0-HzVRNvYqSxCGwv3BbwGjH7" True) (C1 (MetaCons "Constructor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))