Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- parseWith :: ([Token] -> Either String a) -> String -> Either String a
- unsafeParseWith :: ([Token] -> Either String a) -> String -> a
- type EvaluationState = ()
- type NamedRule = (String, Rule)
- type Atoms = HashMap String (String -> Object -> EvaluationState -> DataizeChain (Object, EvaluationState))
- data Context = Context {}
- sameContext :: Context -> Context -> Bool
- type Rule = Context -> Object -> [Object]
- applyOneRuleAtRoot :: Context -> Object -> [(String, Object)]
- extendContextWith :: Object -> Context -> Context
- isEmptyBinding :: Binding -> Bool
- withSubObject :: (Context -> Object -> [(String, Object)]) -> Context -> Object -> [(String, Object)]
- propagateName1 :: (a -> b) -> (name, a) -> (name, b)
- propagateName2 :: (a -> b -> c) -> (name, a) -> b -> (name, c)
- withSubObjectBindings :: (Context -> Object -> [(String, Object)]) -> Context -> [Binding] -> [(String, [Binding])]
- withSubObjectBinding :: (Context -> Object -> [(String, Object)]) -> Context -> Binding -> [(String, Binding)]
- applyOneRule :: Context -> Object -> [(String, Object)]
- isNF :: Context -> Object -> Bool
- applyRules :: Context -> Object -> [Object]
- data ApplicationLimits = ApplicationLimits {
- maxDepth :: Int
- maxTermSize :: Int
- defaultApplicationLimits :: Int -> ApplicationLimits
- objectSize :: Object -> Int
- bindingSize :: Binding -> Int
- applyRulesWith :: ApplicationLimits -> Context -> Object -> [Object]
- equalProgram :: Program -> Program -> Bool
- equalObject :: Object -> Object -> Bool
- equalObjectNamed :: (String, Object) -> (String, Object) -> Bool
- equalBindings :: [Binding] -> [Binding] -> Bool
- equalBinding :: Binding -> Binding -> Bool
- data LogEntry log = LogEntry {
- logEntryMessage :: String
- logEntryLog :: log
- logEntryLevel :: Int
- newtype Chain log result = Chain {}
- type NormalizeChain = Chain Object
- type DataizeChain = Chain (Either Object Bytes)
- logStep :: String -> info -> Chain info ()
- incLogLevel :: Chain info a -> Chain info a
- choose :: [a] -> Chain log a
- msplit :: Chain log a -> Chain log (Maybe (a, Chain log a))
- transformLogs :: (log1 -> log2) -> Chain log1 a -> Chain log2 a
- transformNormLogs :: NormalizeChain a -> DataizeChain a
- listen :: Chain log a -> Chain log (a, [LogEntry log])
- minimizeObject' :: DataizeChain (Either Object Bytes) -> DataizeChain (Either Object Bytes)
- minimizeObject :: DataizeChain (Either Object Bytes) -> DataizeChain (Either Object Bytes)
- smallestObject :: [Either Object bytes] -> Object -> Object
- getContext :: Chain a Context
- withContext :: Context -> Chain log a -> Chain log a
- modifyContext :: (Context -> Context) -> Chain log a -> Chain log a
- applyRulesChain' :: Context -> Object -> [([LogEntry Object], Object)]
- applyRulesChain :: Object -> NormalizeChain Object
- applyRulesChainWith' :: ApplicationLimits -> Context -> Object -> [([LogEntry Object], Object)]
- applyRulesChainWith :: ApplicationLimits -> Object -> NormalizeChain Object
- lookupBinding :: Attribute -> [Binding] -> Maybe Object
- objectBindings :: Object -> [Binding]
- padLeft :: Int -> [Char] -> [Char]
- chunksOf :: Int -> [a] -> [[a]]
- paddedLeftChunksOf :: a -> Int -> [a] -> [[a]]
- normalizeBytes :: String -> String
- concatBytes :: Bytes -> Bytes -> Bytes
- sliceBytes :: Bytes -> Int -> Int -> Bytes
- intToBytes :: Int -> Bytes
- bytesToInt :: Bytes -> Int
- boolToBytes :: Bool -> Bytes
- bytesToBool :: Bytes -> Bool
- stringToBytes :: String -> Bytes
- bytestringToBytes :: ByteString -> Bytes
- bytesToByteString :: Bytes -> ByteString
- bytesToString :: Bytes -> String
- floatToBytes :: Double -> Bytes
- bytesToFloat :: Bytes -> Double
- isRhoBinding :: Binding -> Bool
- hideRhoInBinding :: Binding -> Binding
- hideRho :: Object -> Object
- hideRhoInBinding1 :: Binding -> Binding
- hideRho1 :: Object -> Object
Documentation
>>>
:set -XOverloadedStrings
>>>
:set -XOverloadedLists
>>>
import Language.EO.Phi.Syntax
type EvaluationState = () Source #
State of evaluation is not needed yet, but it might be in the future
type Atoms = HashMap String (String -> Object -> EvaluationState -> DataizeChain (Object, EvaluationState)) Source #
Context | |
|
type Rule = Context -> Object -> [Object] Source #
A rule tries to apply a transformation to the root object, if possible.
isEmptyBinding :: Binding -> Bool Source #
withSubObject :: (Context -> Object -> [(String, Object)]) -> Context -> Object -> [(String, Object)] Source #
propagateName1 :: (a -> b) -> (name, a) -> (name, b) Source #
Given a unary function that operates only on plain objects, converts it to a function that operates on named objects
propagateName2 :: (a -> b -> c) -> (name, a) -> b -> (name, c) Source #
Given a binary function that operates only on plain objects, converts it to a function that operates on named objects
withSubObjectBindings :: (Context -> Object -> [(String, Object)]) -> Context -> [Binding] -> [(String, [Binding])] Source #
withSubObjectBinding :: (Context -> Object -> [(String, Object)]) -> Context -> Binding -> [(String, Binding)] Source #
data ApplicationLimits Source #
objectSize :: Object -> Int Source #
bindingSize :: Binding -> Int Source #
applyRulesWith :: ApplicationLimits -> Context -> Object -> [Object] Source #
A variant of applyRules
with a maximum application depth.
Chain variants
LogEntry | |
|
type NormalizeChain = Chain Object Source #
incLogLevel :: Chain info a -> Chain info a Source #
transformLogs :: (log1 -> log2) -> Chain log1 a -> Chain log2 a Source #
transformNormLogs :: NormalizeChain a -> DataizeChain a Source #
minimizeObject' :: DataizeChain (Either Object Bytes) -> DataizeChain (Either Object Bytes) Source #
minimizeObject :: DataizeChain (Either Object Bytes) -> DataizeChain (Either Object Bytes) Source #
getContext :: Chain a Context Source #
applyRulesChain :: Object -> NormalizeChain Object Source #
Apply the rules until the object is normalized, preserving the history (chain) of applications.
applyRulesChainWith' :: ApplicationLimits -> Context -> Object -> [([LogEntry Object], Object)] Source #
applyRulesChainWith :: ApplicationLimits -> Object -> NormalizeChain Object Source #
A variant of applyRulesChain
with a maximum application depth.
Helpers
lookupBinding :: Attribute -> [Binding] -> Maybe Object Source #
Lookup a binding by the attribute name.
objectBindings :: Object -> [Binding] Source #
chunksOf :: Int -> [a] -> [[a]] Source #
Split a list into chunks of given size. All lists in the result are guaranteed to have length less than or equal to the given size.
>>>
chunksOf 2 "012345678"
["01","23","45","67","8"]
See paddedLeftChunksOf
for a version with padding to guarantee exact chunk size.
paddedLeftChunksOf :: a -> Int -> [a] -> [[a]] Source #
Split a list into chunks of given size, padding on the left if necessary. All lists in the result are guaranteed to have given size.
>>>
paddedLeftChunksOf '0' 2 "1234567"
["01","23","45","67"]>>>
paddedLeftChunksOf '0' 2 "123456"
["12","34","56"]
n > 0 ==> all (\chunk -> length chunk == n) (paddedLeftChunksOf c n s)
normalizeBytes :: String -> String Source #
Normalize the bytestring representation to fit valid Bytes
token.
>>>
normalizeBytes "238714ABCDEF"
"23-87-14-AB-CD-EF"
>>>
normalizeBytes "0238714ABCDEF"
"00-23-87-14-AB-CD-EF"
>>>
normalizeBytes "4"
"04-"
concatBytes :: Bytes -> Bytes -> Bytes Source #
Concatenate Bytes
.
FIXME: we should really use ByteString
instead of the underlying String
representation.
>>>
concatBytes "00-" "01-02"
Bytes "00-01-02"
>>>
concatBytes "03-04" "01-02"
Bytes "03-04-01-02"
>>>
concatBytes "03-04" "01-"
Bytes "03-04-01"
sliceBytes :: Bytes -> Int -> Int -> Bytes Source #
Select a slice (section) of Bytes
.
>>>
sliceBytes "12-34-56" 1 1
Bytes "34-"
>>>
sliceBytes "12-34-56" 1 0
Bytes "00-"
>>>
sliceBytes "12-34-56" 0 2
Bytes "12-34"
intToBytes :: Int -> Bytes Source #
bytesToInt :: Bytes -> Int Source #
boolToBytes :: Bool -> Bytes Source #
bytesToBool :: Bytes -> Bool Source #
stringToBytes :: String -> Bytes Source #
bytestringToBytes :: ByteString -> Bytes Source #
bytesToByteString :: Bytes -> ByteString Source #
bytesToString :: Bytes -> String Source #
floatToBytes :: Double -> Bytes Source #
Encode Double
as Bytes
following IEEE754.
Note: it is called "float" in EO, but it actually occupies 8 bytes so it corresponds to Double
.
>>>
floatToBytes 0
Bytes "00-00-00-00-00-00-00-00"
>>>
floatToBytes (-0.1)
Bytes "BF-B9-99-99-99-99-99-9A"
>>>
floatToBytes (1/0) -- Infinity
Bytes "7F-F0-00-00-00-00-00-00"
>>>
floatToBytes (asin 2) `elem` ["FF-F8-00-00-00-00-00-00", "7F-F8-00-00-00-00-00-00"] -- sNaN or qNaN
True
bytesToFloat :: Bytes -> Double Source #
isRhoBinding :: Binding -> Bool Source #
hideRhoInBinding :: Binding -> Binding Source #
hideRhoInBinding1 :: Binding -> Binding Source #
Orphan instances
IsString Attribute Source # | |
fromString :: String -> Attribute # | |
IsString Binding Source # | |
fromString :: String -> Binding # | |
IsString MetaId Source # | |
fromString :: String -> MetaId # | |
IsString Object Source # | |
fromString :: String -> Object # | |
IsString ObjectHead Source # | |
fromString :: String -> ObjectHead # | |
IsString PeeledObject Source # | |
fromString :: String -> PeeledObject # | |
IsString Program Source # | |
fromString :: String -> Program # | |
IsString RuleAttribute Source # | |
fromString :: String -> RuleAttribute # |