Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data ExprNode s a
- type Expression s a = Free (ExprNode s) a
- class (Ord s, Show s, NFData s) => Identifier s where
- class HasIdents s s' t t' | t t' -> s s' where
- data Builtin
- = B_Undefined
- | B_Seq
- | B_Unit
- | B_Number Int
- | B_AddInt
- | B_SubInt
- | B_MulInt
- | B_DivInt
- | B_CmpInt_LT
- | B_CmpInt_EQ
- | B_String String
- | B_StringLength
- | B_AddString
- | B_ShowInt
- | B_Bytes Bytes
- | B_MkArray
- | B_ArrayLength
- | B_ArrayAt
- | B_ArraySet
- | B_SyntaxNode
- | B_SyntaxSym
- | B_SyntaxExpr
- | B_SyntaxInd
- | B_ExprLambda
- | B_ExprApply
- | B_ExprSym
- | B_ExprInd
- | B_FileDesc Int
- | B_Open
- | B_Read
- | B_Write
- | B_Close
- | B_Foreign (Map String GlobalID) GlobalID
- | B_Relocatable Bool Hash [(Bytes, BinaryRelocation)] Bytes
- | B_RawIndex Int
- | B_ShowExpr
- | B_ShowSyntax
- data BinaryRelocation = BinaryRelocation {
- _br_PCRelative :: Bool
- _br_size :: RelocationSize
- _br_symhash :: Hash
- _br_symoffset :: Int
- data SemanticT e i o
- = SemApply e e
- | SemAbstract i e
- | SemSymbol o
- class Semantic e i o | e -> i o where
- mkAbstract :: Semantic e i o => i -> e -> e
- mkSymbol :: Semantic e i o => o -> e
- mkApply :: Semantic e i o => e -> e -> e
- sem :: Semantic e i o => e -> SemanticT e i o
- newtype Hash = Hash Chunk
- hashData :: Bytes -> Hash
- newtype LibraryID = LibraryID Chunk
- data GlobalID = GlobalID String (Maybe (String, LibraryID))
- pattern PatSymbol :: forall e i o. Semantic e i o => o -> e
- pattern PatAbstract :: forall e i o. Semantic e i o => i -> e -> e
- pattern PatApply :: forall e i o. Semantic e i o => e -> e -> e
- pattern PatApply2 :: forall e i o. Semantic e i o => e -> e -> e -> e
- t'Symbol :: Semantic e i o => Traversal' e o
- t'Apply :: Semantic e i o => Traversal' e (e, e)
- t'Abstract :: Semantic e i o => Traversal' e (i, e)
- c'Expression :: Constraint (Expression a b)
- syntax :: (Semantic e i o, Semantic e' i o'', Ord i) => (o -> o' -> o'') -> (o -> o') -> (o -> i) -> (Int -> o') -> e -> e'
- semantic :: (Semantic e i o, Semantic e' i o) => e -> e'
- mapParams :: (Semantic e i o, Semantic e' i' o) => (i -> i') -> e -> e'
- envVar :: String -> String -> String
- curlyDataRoot :: FilePath
- curlyConfigRoot :: FilePath
- curlyCacheRoot :: FilePath
- curlyKeysFile :: FilePath
- curlyCacheDir :: FilePath
- curlyCommitDir :: FilePath
- curlyPort :: PortNumber
- data LogLevel
- data LogMessage
- serialWriteHBytes :: Handle -> Bytes -> IO ()
- addLogCallback :: (LogMessage -> IO ()) -> IO LogCallbackID
- removeLogCallback :: LogCallbackID -> IO ()
- withLogCallback :: (LogMessage -> IO ()) -> IO a -> IO a
- envLogLevel :: LogLevel
- logLine :: MonadIO m => LogLevel -> String -> m ()
- logMessage :: MonadIO m => LogMessage -> m ()
- logAction :: MonadIO m => String -> IO a -> m a
- trylogLevel :: LogLevel -> IO a -> IO a -> IO a
- trylog :: IO a -> IO a -> IO a
- liftIOLog :: MonadIO m => IO () -> m ()
- cyDebug :: Show a => a -> a
- newtype B64Chunk = B64Chunk Chunk
- data PortNumber :: *
- watchFile :: FilePath -> IO () -> IO (IO ())
- connectTo :: String -> PortNumber -> IO Handle
- (*+) :: (Ord k, Semigroup m) => Map k m -> Map k m -> Map k m
- cacheFileName :: FilePath -> String -> String -> FilePath
- createFileDirectory :: FilePath -> IO ()
- newtype Compressed a = Compressed {
- unCompressed :: a
- noCurlySuf :: FilePath -> Maybe FilePath
- (</>) :: FilePath -> FilePath -> FilePath
- format :: FormatType r => String -> r
Expressions
The type of an expression node
This type is used in combination with others within Free functors to model expressions with different attributes.
HasIdents s s' (ExprNode s a) (ExprNode s' a) Source # | |
(Serializable Bytes a, Serializable Bytes s) => Serializable Bytes (Free (ExprNode s) a) Source # | |
(Serializable Bytes a, Serializable Bytes s) => Serializable Bytes (ExprNode s a) Source # | |
(Format Bytes a, Format Bytes s) => Format Bytes (Free (ExprNode s) a) Source # | |
(Format Bytes a, Format Bytes s) => Format Bytes (ExprNode s a) Source # | |
Functor (ExprNode s) Source # | |
Foldable (ExprNode s) Source # | |
Traversable (ExprNode s) Source # | |
(Eq s, Eq a) => Eq (ExprNode s a) Source # | |
(Ord s, Ord a) => Ord (ExprNode s a) Source # | |
(Show s, Show a) => Show (ExprNode s a) Source # | |
Generic (ExprNode s a) Source # | |
(NFData s, NFData a) => NFData (ExprNode s a) Source # | |
(Documented s, Documented a) => Documented (Expression s a) Source # | |
Semantic (Free (ExprNode s) a) s a Source # | |
type Rep (ExprNode s a) Source # | |
type Expression s a = Free (ExprNode s) a Source #
The type of a simple Curly expression
class (Ord s, Show s, NFData s) => Identifier s where Source #
The class of Curly identifiers, used mainly to simplify type signatures.
class HasIdents s s' t t' | t t' -> s s' where Source #
A useful class for identifier-filled types
The type of all Curly builtins
data BinaryRelocation Source #
BinaryRelocation | |
|
class Semantic e i o | e -> i o where Source #
The class of all lambda-like expressions.
This class provides an abstraction of the different types used to represent expressions at the different stages of compilation.
This class provides three constructors and a destructor for its target type, allowing abstract pattern-matching to take place.
mkAbstract :: Semantic e i o => i -> e -> e Source #
pattern PatAbstract :: forall e i o. Semantic e i o => i -> e -> e Source #
t'Symbol :: Semantic e i o => Traversal' e o Source #
t'Apply :: Semantic e i o => Traversal' e (e, e) Source #
t'Abstract :: Semantic e i o => Traversal' e (i, e) Source #
Utilities
c'Expression :: Constraint (Expression a b) Source #
syntax :: (Semantic e i o, Semantic e' i o'', Ord i) => (o -> o' -> o'') -> (o -> o') -> (o -> i) -> (Int -> o') -> e -> e' Source #
Tranform an expression into another, annotating it with contextual information.
semantic :: (Semantic e i o, Semantic e' i o) => e -> e' Source #
Transform a lambda-like expression into another
mapParams :: (Semantic e i o, Semantic e' i' o) => (i -> i') -> e -> e' Source #
Maps a function over lambda parameters in an expression
Environment
envVar :: String -> String -> String Source #
`envVar def var` retrieves a var
from the environment, or returns def
if the former doesn't exist
curlyKeysFile :: FilePath Source #
The path of the Curly key wallet
curlyCacheDir :: FilePath Source #
The path to the user's cache directory
curlyPort :: PortNumber Source #
The default Curly port for library proxies and the portmapper
Logging facilities
A Curly log level
data LogMessage Source #
addLogCallback :: (LogMessage -> IO ()) -> IO LogCallbackID Source #
removeLogCallback :: LogCallbackID -> IO () Source #
withLogCallback :: (LogMessage -> IO ()) -> IO a -> IO a Source #
logLine :: MonadIO m => LogLevel -> String -> m () Source #
Logs a line to stderr if the environment log level is greater than the given threshold
logMessage :: MonadIO m => LogMessage -> m () Source #
trylogLevel :: LogLevel -> IO a -> IO a -> IO a Source #
Runs an IO action, logging its errors if the given log level is lower than the environment
liftIOLog :: MonadIO m => IO () -> m () Source #
A utility function that lifts its argument while logging its errors
Misc
data PortNumber :: * #
Use the Num
instance (i.e. use a literal) to create a
PortNumber
value with the correct network-byte-ordering. You
should not use the PortNum constructor. It will be removed in the
next release.
>>>
1 :: PortNumber
1>>>
read "1" :: PortNumber
1
watchFile :: FilePath -> IO () -> IO (IO ()) Source #
Sets a watch on the given file, on the usual signals
connectTo :: String -> PortNumber -> IO Handle Source #
A utility function that opens a client socket to the given server and port
createFileDirectory :: FilePath -> IO () Source #
newtype Compressed a Source #
Compressed | |
|
Serializable Bytes a => Serializable Bytes (Compressed a) Source # | |
Format Bytes a => Format Bytes (Compressed a) Source # | |
Eq a => Eq (Compressed a) Source # | |
Ord a => Ord (Compressed a) Source # | |
Show a => Show (Compressed a) Source # | |
format :: FormatType r => String -> r Source #
A function that mimics sprintf-style formatting for Haskell