Safe Haskell | None |
---|---|
Language | Haskell2010 |
Untyped representation of abstract syntax trees
Synopsis
- newtype Field = Field {}
- data Mapping k v = Mapping Importance !(HashMap k v)
- data NameType
- data Constr
- data Importance
- data AST n
- record :: HasCallStack => Importance -> [(Field, AST n)] -> AST n
- prettyNamed :: NameType -> Text -> Doc
- class GInspectableArgs rep where
- gInspectArgs :: rep x -> [AST Rational]
- class GInspectableFields rep where
- gInspectFields :: rep x -> [(Field, AST Rational)]
- class GInspectable rep where
- class Inspectable a where
- inspectListAsRec :: Inspectable a => Importance -> (a -> Field) -> [a] -> AST Rational
- toTree :: Show n => AST n -> Tree Text
- showTree :: Show n => AST n -> String
- drawTree :: Show n => AST n -> IO ()
- htmlTree :: Show n => FilePath -> AST n -> IO ()
Representation
A wrapper for String
with a Show
instance that omits quotes
Useful in situations where show
is (ab)used to provide conversion to
String
rather than for displaying values.
Mapping Importance !(HashMap k v) |
Instances
Functor (Mapping k) Source # | |
Foldable (Mapping k) Source # | |
Defined in Dino.AST fold :: Monoid m => Mapping k m -> m # foldMap :: Monoid m => (a -> m) -> Mapping k a -> m # foldr :: (a -> b -> b) -> b -> Mapping k a -> b # foldr' :: (a -> b -> b) -> b -> Mapping k a -> b # foldl :: (b -> a -> b) -> b -> Mapping k a -> b # foldl' :: (b -> a -> b) -> b -> Mapping k a -> b # foldr1 :: (a -> a -> a) -> Mapping k a -> a # foldl1 :: (a -> a -> a) -> Mapping k a -> a # toList :: Mapping k a -> [a] # length :: Mapping k a -> Int # elem :: Eq a => a -> Mapping k a -> Bool # maximum :: Ord a => Mapping k a -> a # minimum :: Ord a => Mapping k a -> a # | |
Traversable (Mapping k) Source # | |
(Eq k, Eq v) => Eq (Mapping k v) Source # | |
(Show k, Show v) => Show (Mapping k v) Source # | |
Generic (Mapping k v) Source # | |
(Pretty a, Show k, Ord k) => Pretty (Mapping k a) Source # | If |
(Pretty a, Pretty (Diff a), Show k, Ord k) => Pretty (Mapping k (ElemOp a)) Source # | If |
(Hashable k, Hashable v) => Hashable (Mapping k v) Source # | |
Inspectable a => Inspectable (Mapping Field a) Source # | |
(Eq k, Hashable k, Diffable a) => Diffable (Mapping k a) Source # | |
type Rep (Mapping k v) Source # | |
Defined in Dino.AST type Rep (Mapping k v) = D1 (MetaData "Mapping" "Dino.AST" "dino-0.1-6MkCTG92eXJDyeFPmd1P4Q" False) (C1 (MetaCons "Mapping" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Importance) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap k v)))) | |
type Diff (Mapping k a) Source # | |
Defined in Dino.AST.Diff |
Constructor | Global constructor or variable |
LocalVar | Local variable |
Annotation | User annotation |
Instances
Bounded NameType Source # | |
Enum NameType Source # | |
Eq NameType Source # | |
Show NameType Source # | |
Generic NameType Source # | |
Hashable NameType Source # | |
type Rep NameType Source # | |
Defined in Dino.AST |
Description of a constructor or variable
Instances
Eq Constr Source # | |
Show Constr Source # | |
IsString Constr Source # | Creates a |
Defined in Dino.AST fromString :: String -> Constr # | |
Generic Constr Source # | |
Hashable Constr Source # | |
type Rep Constr Source # | |
Defined in Dino.AST type Rep Constr = D1 (MetaData "Constr" "Dino.AST" "dino-0.1-6MkCTG92eXJDyeFPmd1P4Q" False) (C1 (MetaCons "Tuple" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "List" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Named" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))) |
data Importance Source #
Instances
Eq Importance Source # | |
Defined in Dino.Pretty (==) :: Importance -> Importance -> Bool # (/=) :: Importance -> Importance -> Bool # | |
Show Importance Source # | |
Defined in Dino.Pretty showsPrec :: Int -> Importance -> ShowS # show :: Importance -> String # showList :: [Importance] -> ShowS # | |
Generic Importance Source # | |
Defined in Dino.Pretty type Rep Importance :: Type -> Type # from :: Importance -> Rep Importance x # to :: Rep Importance x -> Importance # | |
Semigroup Importance Source # | |
Defined in Dino.Pretty (<>) :: Importance -> Importance -> Importance # sconcat :: NonEmpty Importance -> Importance # stimes :: Integral b => b -> Importance -> Importance # | |
Hashable Importance Source # | |
Defined in Dino.Pretty hashWithSalt :: Int -> Importance -> Int # hash :: Importance -> Int # | |
type Rep Importance Source # | |
Representation of abstract syntax and values
AST
is parameterized by the representation of numbers. This makes it
possible to affect the exactness of comparisons. For example a newtype with
approximate equality can be used instead of e.g. Double
.
Number n | Numeric literal |
Text Text | Text literal |
App Constr [AST n] | Application of constructor or variable |
Let Text (AST n) (AST n) |
|
Record (Mapping Field (AST n)) |
Instances
record :: HasCallStack => Importance -> [(Field, AST n)] -> AST n Source #
Generic inspection
class GInspectableArgs rep where Source #
gInspectArgs :: rep x -> [AST Rational] Source #
Instances
GInspectableArgs (U1 :: k -> Type) Source # | |
(GInspectableArgs rep1, GInspectableArgs rep2) => GInspectableArgs (rep1 :*: rep2 :: k -> Type) Source # | |
Inspectable a => GInspectableArgs (S1 (MetaSel (Nothing :: Maybe Symbol) x y z) (Rec0 a) :: k -> Type) Source # | |
class GInspectableFields rep where Source #
Instances
GInspectableFields (U1 :: k -> Type) Source # | |
(GInspectableFields rep1, GInspectableFields rep2) => GInspectableFields (rep1 :*: rep2 :: k -> Type) Source # | |
(Inspectable a, KnownSymbol fld) => GInspectableFields (S1 (MetaSel (Just fld) x y z) (Rec0 a) :: k -> Type) Source # | |
class GInspectable rep where Source #
Instances
(GInspectableFields rep, KnownSymbol con) => GInspectable (C1 (MetaCons con x True) rep :: k -> Type) Source # | |
(GInspectableArgs rep, KnownSymbol con) => GInspectable (C1 (MetaCons con x False) rep :: k -> Type) Source # | |
GInspectable rep => GInspectable (D1 meta rep :: k -> Type) Source # | |
(GInspectable rep1, GInspectable rep2) => GInspectable (rep1 :+: rep2 :: k -> Type) Source # | |
class Inspectable a where Source #
Nothing
inspect :: a -> AST Rational Source #
inspect :: (Generic a, GInspectable (Rep a)) => a -> AST Rational Source #
Instances
Inspectable Bool Source # | |
Inspectable Double Source # | |
Inspectable Float Source # | |
Inspectable Int Source # | |
Inspectable Integer Source # | |
Inspectable Rational Source # | |
Inspectable () Source # | |
Inspectable String Source # | |
Inspectable Text Source # | |
Inspectable a => Inspectable [a] Source # | |
Inspectable a => Inspectable (Maybe a) Source # | |
Real n => Inspectable (AST n) Source # | |
Inspectable (Reified a) Source # | |
(Inspectable a, Inspectable b) => Inspectable (a, b) Source # | |
Inspectable a => Inspectable (Mapping Field a) Source # | |
(Inspectable a, Inspectable b, Inspectable c) => Inspectable (a, b, c) Source # | |
(Inspectable a, Inspectable b, Inspectable c, Inspectable d) => Inspectable (a, b, c, d) Source # | |
:: Inspectable a | |
=> Importance | |
-> (a -> Field) | Extract the key |
-> [a] | |
-> AST Rational |
Represent a list as a record, if the elements contain a value that can be used as key