Copyright | (c) 2015-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data ModName
- modNameToText :: ModName -> Text
- textToModName :: Text -> ModName
- modNameChunks :: ModName -> [String]
- packModName :: [Text] -> ModName
- preludeName :: ModName
- preludeReferenceName :: ModName
- floatName :: ModName
- suiteBName :: ModName
- arrayName :: ModName
- primeECName :: ModName
- interactiveName :: ModName
- noModuleName :: ModName
- exprModName :: ModName
- isParamInstModName :: ModName -> Bool
- paramInstModName :: ModName -> ModName
- notParamInstModName :: ModName -> ModName
- data Ident
- packIdent :: String -> Ident
- packInfix :: String -> Ident
- unpackIdent :: Ident -> String
- mkIdent :: Text -> Ident
- mkInfix :: Text -> Ident
- isInfixIdent :: Ident -> Bool
- nullIdent :: Ident -> Bool
- identText :: Ident -> Text
- modParamIdent :: Ident -> Ident
- data PrimIdent = PrimIdent ModName Text
- prelPrim :: Text -> PrimIdent
- floatPrim :: Text -> PrimIdent
- arrayPrim :: Text -> PrimIdent
- suiteBPrim :: Text -> PrimIdent
- primeECPrim :: Text -> PrimIdent
Module names
Module names are just text.
modNameToText :: ModName -> Text Source #
textToModName :: Text -> ModName Source #
modNameChunks :: ModName -> [String] Source #
packModName :: [Text] -> ModName Source #
suiteBName :: ModName Source #
isParamInstModName :: ModName -> Bool Source #
paramInstModName :: ModName -> ModName Source #
Convert a parameterized module's name to the name of the module containing the same definitions but with explicit parameters on each definition.
notParamInstModName :: ModName -> ModName Source #
Identifiers
Identifiers, along with a flag that indicates whether or not they're infix operators. The boolean is present just as cached information from the lexer, and never used during comparisons.
Instances
Eq Ident Source # | |
Ord Ident Source # | |
Show Ident Source # | |
IsString Ident Source # | |
Defined in Cryptol.Utils.Ident fromString :: String -> Ident # | |
Generic Ident Source # | |
NFData Ident Source # | |
Defined in Cryptol.Utils.Ident | |
PP Ident Source # | |
ShowParseable Ident Source # | |
Defined in Cryptol.TypeCheck.Parseable showParseable :: Ident -> Doc Source # | |
type Rep Ident Source # | |
Defined in Cryptol.Utils.Ident type Rep Ident = D1 ('MetaData "Ident" "Cryptol.Utils.Ident" "cryptol-2.10.0-Bsi6VMfJ6GCFlOdda30jWW" 'False) (C1 ('MetaCons "Ident" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
unpackIdent :: Ident -> String Source #
isInfixIdent :: Ident -> Bool Source #
modParamIdent :: Ident -> Ident Source #
Identifiers for primitives
A way to identify primitives: we used to use just Ident
, but this
isn't good anymore as now we have primitives in multiple modules.
This is used as a key when we need to lookup details about a specific
primitive. Also, this is intended to mostly be used internally, so
we don't store the fixity flag of the Ident
Instances
Eq PrimIdent Source # | |
Ord PrimIdent Source # | |
Defined in Cryptol.Utils.Ident | |
Show PrimIdent Source # | |
Generic PrimIdent Source # | |
NFData PrimIdent Source # | |
Defined in Cryptol.Utils.Ident | |
type Rep PrimIdent Source # | |
Defined in Cryptol.Utils.Ident type Rep PrimIdent = D1 ('MetaData "PrimIdent" "Cryptol.Utils.Ident" "cryptol-2.10.0-Bsi6VMfJ6GCFlOdda30jWW" 'False) (C1 ('MetaCons "PrimIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
suiteBPrim :: Text -> PrimIdent Source #
primeECPrim :: Text -> PrimIdent Source #