| License | MIT |
|---|---|
| Safe Haskell | None |
| Language | GHC2021 |
Language.Egison.IExpr
Description
This module defines internal representation of Egison language.
Documentation
Constructors
Constructors
data ILoopRange Source #
Constructors
| ILoopRange IExpr IExpr IPattern |
Instances
| Show ILoopRange Source # | |
Defined in Language.Egison.IExpr Methods showsPrec :: Int -> ILoopRange -> ShowS # show :: ILoopRange -> String # showList :: [ILoopRange] -> ShowS # | |
type IBindingExpr = (IPrimitiveDataPattern, IExpr) Source #
type IMatchClause = (IPattern, IExpr) Source #
type IPatternDef = (PrimitivePatPattern, IExpr, [(IPrimitiveDataPattern, IExpr)]) Source #
type IPrimitiveDataPattern = PDPatternBase Var Source #
Instances
stringToVar :: String -> Var Source #
extractNameFromVar :: Var -> String Source #
Constructors
| Sub a | |
| Sup a | |
| MultiSub a Integer a | |
| MultiSup a Integer a | |
| SupSub a | |
| User a | |
| DF Integer Integer |
Instances
| Foldable Index Source # | |||||
Defined in Language.Egison.IExpr Methods fold :: Monoid m => Index m -> m # foldMap :: Monoid m => (a -> m) -> Index a -> m # foldMap' :: Monoid m => (a -> m) -> Index a -> m # foldr :: (a -> b -> b) -> b -> Index a -> b # foldr' :: (a -> b -> b) -> b -> Index a -> b # foldl :: (b -> a -> b) -> b -> Index a -> b # foldl' :: (b -> a -> b) -> b -> Index a -> b # foldr1 :: (a -> a -> a) -> Index a -> a # foldl1 :: (a -> a -> a) -> Index a -> a # elem :: Eq a => a -> Index a -> Bool # maximum :: Ord a => Index a -> a # minimum :: Ord a => Index a -> a # | |||||
| Traversable Index Source # | |||||
| Functor Index Source # | |||||
| Generic (Index a) Source # | |||||
Defined in Language.Egison.IExpr Associated Types
| |||||
| Show (Index EgisonValue) Source # | |||||
Defined in Language.Egison.Data | |||||
| Show (Index ScalarData) Source # | |||||
Defined in Language.Egison.Math.Expr | |||||
| Show (Index String) Source # | |||||
| Show a => Show (Index a) Source # | |||||
| Eq a => Eq (Index a) Source # | |||||
| Hashable a => Hashable (Index a) Source # | |||||
Defined in Language.Egison.IExpr | |||||
| type Rep (Index a) Source # | |||||
Defined in Language.Egison.IExpr type Rep (Index a) = D1 ('MetaData "Index" "Language.Egison.IExpr" "egison-4.2.1-1HsolijfuDl5ZG5Ec9RpuZ" 'False) ((C1 ('MetaCons "Sub" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: (C1 ('MetaCons "Sup" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "MultiSub" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) :+: ((C1 ('MetaCons "MultiSup" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) :+: C1 ('MetaCons "SupSub" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) :+: (C1 ('MetaCons "User" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "DF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))))) | |||||
extractSupOrSubIndex :: Index a -> Maybe a Source #
extractIndex :: Index a -> a Source #
data ConstantExpr Source #
Constructors
| CharExpr Char | |
| StringExpr Text | |
| BoolExpr Bool | |
| IntegerExpr Integer | |
| FloatExpr Double | |
| SomethingExpr | |
| UndefinedExpr |
Instances
| Show ConstantExpr Source # | |
Defined in Language.Egison.AST Methods showsPrec :: Int -> ConstantExpr -> ShowS # show :: ConstantExpr -> String # showList :: [ConstantExpr] -> ShowS # | |
| Pretty ConstantExpr Source # | |
Defined in Language.Egison.Pretty | |
data PrimitivePatPattern Source #
Constructors
| PPWildCard | |
| PPPatVar | |
| PPValuePat String | |
| PPInductivePat String [PrimitivePatPattern] | |
| PPTuplePat [PrimitivePatPattern] |
Instances
| Show PrimitivePatPattern Source # | |
Defined in Language.Egison.AST Methods showsPrec :: Int -> PrimitivePatPattern -> ShowS # show :: PrimitivePatPattern -> String # showList :: [PrimitivePatPattern] -> ShowS # | |
| Pretty PrimitivePatPattern Source # | |
Defined in Language.Egison.Pretty | |
data PDPatternBase var Source #
Constructors
| PDWildCard | |
| PDPatVar var | |
| PDInductivePat String [PDPatternBase var] | |
| PDTuplePat [PDPatternBase var] | |
| PDEmptyPat | |
| PDConsPat (PDPatternBase var) (PDPatternBase var) | |
| PDSnocPat (PDPatternBase var) (PDPatternBase var) | |
| PDConstantPat ConstantExpr |
Instances
| Foldable PDPatternBase Source # | |
Defined in Language.Egison.AST Methods fold :: Monoid m => PDPatternBase m -> m # foldMap :: Monoid m => (a -> m) -> PDPatternBase a -> m # foldMap' :: Monoid m => (a -> m) -> PDPatternBase a -> m # foldr :: (a -> b -> b) -> b -> PDPatternBase a -> b # foldr' :: (a -> b -> b) -> b -> PDPatternBase a -> b # foldl :: (b -> a -> b) -> b -> PDPatternBase a -> b # foldl' :: (b -> a -> b) -> b -> PDPatternBase a -> b # foldr1 :: (a -> a -> a) -> PDPatternBase a -> a # foldl1 :: (a -> a -> a) -> PDPatternBase a -> a # toList :: PDPatternBase a -> [a] # null :: PDPatternBase a -> Bool # length :: PDPatternBase a -> Int # elem :: Eq a => a -> PDPatternBase a -> Bool # maximum :: Ord a => PDPatternBase a -> a # minimum :: Ord a => PDPatternBase a -> a # sum :: Num a => PDPatternBase a -> a # product :: Num a => PDPatternBase a -> a # | |
| Functor PDPatternBase Source # | |
Defined in Language.Egison.AST Methods fmap :: (a -> b) -> PDPatternBase a -> PDPatternBase b # (<$) :: a -> PDPatternBase b -> PDPatternBase a # | |
| Pretty PrimitiveDataPattern Source # | |
Defined in Language.Egison.Pretty | |
| Show var => Show (PDPatternBase var) Source # | |
Defined in Language.Egison.AST Methods showsPrec :: Int -> PDPatternBase var -> ShowS # show :: PDPatternBase var -> String # showList :: [PDPatternBase var] -> ShowS # | |