Copyright | (c) 2015-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Cryptol.Utils.Ident
Description
Synopsis
- data ModPath
- apPathRoot :: (ModName -> ModName) -> ModPath -> ModPath
- modPathCommon :: ModPath -> ModPath -> Maybe (ModPath, [Ident], [Ident])
- modPathIsOrContains :: ModPath -> ModPath -> Bool
- topModuleFor :: ModPath -> ModName
- modPathSplit :: ModPath -> (ModName, [Ident])
- modPathIsNormal :: ModPath -> Bool
- data ModName
- modNameToText :: ModName -> Text
- textToModName :: Text -> ModName
- mainModName :: FilePath -> ModName
- modNameChunks :: ModName -> [String]
- modNameChunksText :: ModName -> [Text]
- packModName :: [Text] -> ModName
- identToModName :: Ident -> ModName
- preludeName :: ModName
- preludeReferenceName :: ModName
- undefinedModName :: ModName
- floatName :: ModName
- suiteBName :: ModName
- arrayName :: ModName
- primeECName :: ModName
- interactiveName :: ModName
- noModuleName :: ModName
- exprModName :: ModName
- modNameArg :: Int -> Int -> ModName -> ModName
- modNameIfaceMod :: ModName -> ModName
- modNameToNormalModName :: ModName -> ModName
- modNamesMatch :: ModName -> ModName -> Bool
- modNameIsNormal :: ModName -> Bool
- data Ident
- packIdent :: String -> Ident
- packInfix :: String -> Ident
- unpackIdent :: Ident -> String
- mkIdent :: Text -> Ident
- mkInfix :: Text -> Ident
- isInfixIdent :: Ident -> Bool
- isUpperIdent :: Ident -> Bool
- isAnonIfaceModIdnet :: Ident -> Bool
- nullIdent :: Ident -> Bool
- identText :: Ident -> Text
- identAnonArg :: Int -> Int -> Ident
- identAnonIfaceMod :: Ident -> Ident
- identAnonInstImport :: Int -> Int -> Ident
- identIsNormal :: Ident -> Bool
- data Namespace
- allNamespaces :: [Namespace]
- data OrigName = OrigName {
- ogNamespace :: Namespace
- ogModule :: ModPath
- ogSource :: OrigSource
- ogName :: Ident
- ogFromParam :: !(Maybe Ident)
- data OrigSource
- ogIsModParam :: OrigName -> Bool
- data PrimIdent = PrimIdent ModName Text
- prelPrim :: Text -> PrimIdent
- floatPrim :: Text -> PrimIdent
- arrayPrim :: Text -> PrimIdent
- suiteBPrim :: Text -> PrimIdent
- primeECPrim :: Text -> PrimIdent
Module names
Identifies a possibly nested module
Instances
Generic ModPath Source # | |
Show ModPath Source # | |
PP ModPath Source # | |
NFData ModPath Source # | |
Defined in Cryptol.Utils.Ident | |
Eq ModPath Source # | |
Ord ModPath Source # | |
type Rep ModPath Source # | |
Defined in Cryptol.Utils.Ident type Rep ModPath = D1 ('MetaData "ModPath" "Cryptol.Utils.Ident" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "TopModule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModName)) :+: C1 ('MetaCons "Nested" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModPath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) |
modPathCommon :: ModPath -> ModPath -> Maybe (ModPath, [Ident], [Ident]) Source #
Compute a common prefix between two module paths, if any. This is basically "anti-unification" of the two paths, where we compute the longest common prefix, and the remaining differences for each module.
modPathIsOrContains :: ModPath -> ModPath -> Bool Source #
Does the first module path contain the second? This returns true if the paths are the same.
topModuleFor :: ModPath -> ModName Source #
modPathIsNormal :: ModPath -> Bool Source #
Top-level Module names are just text.
modNameToText :: ModName -> Text Source #
textToModName :: Text -> ModName Source #
Make a normal module name out of text. This function should not
be used to build a Main
module name. See mainModName
.
mainModName :: FilePath -> ModName Source #
modNameChunks :: ModName -> [String] Source #
Break up a module name on the separators, String
version
modNameChunksText :: ModName -> [Text] Source #
packModName :: [Text] -> ModName Source #
identToModName :: Ident -> ModName Source #
suiteBName :: ModName Source #
modNameArg :: Int -> Int -> ModName -> ModName Source #
Change a normal module name to a module name to be used for an anonnymous argument. The first two ints are the line and column of the name, which are used for name disambiguation.
modNameIfaceMod :: ModName -> ModName Source #
Change a normal module name to a module name to be used for an anonnymous interface.
modNamesMatch :: ModName -> ModName -> Bool Source #
This is used when we check that the name of a module matches the file where it is defined.
modNameIsNormal :: ModName -> Bool Source #
This is useful when we want to hide anonymous modules.
Identifiers
The type of identifiers. * The boolean flag indicates whether or not they're infix operators. The boolean is present just as cached information from the lexer, and never used during comparisons. * The MaybeAnon indicates if this is an anonymous name
Instances
IsString Ident Source # | |
Defined in Cryptol.Utils.Ident Methods fromString :: String -> Ident # | |
Generic Ident Source # | |
Show Ident Source # | |
ShowParseable Ident Source # | |
Defined in Cryptol.TypeCheck.Parseable | |
PP Ident Source # | |
NFData Ident Source # | |
Defined in Cryptol.Utils.Ident | |
Eq Ident Source # | |
Ord Ident Source # | |
type Rep Ident Source # | |
Defined in Cryptol.Utils.Ident |
unpackIdent :: Ident -> String Source #
isInfixIdent :: Ident -> Bool Source #
isUpperIdent :: Ident -> Bool Source #
isAnonIfaceModIdnet :: Ident -> Bool Source #
Is this an ident for an anonymous module interface
(i.e., a parameter
block)?
identAnonArg :: Int -> Int -> Ident Source #
Make an anonymous identifier for the module corresponding to a `where` block in a functor instantiation. The two ints are the line and column of the definition site.
identAnonIfaceMod :: Ident -> Ident Source #
Make an anonymous identifier for the interface corresponding to
a parameter
declaration.
identAnonInstImport :: Int -> Int -> Ident Source #
Make an anonymous identifier for an instantiation in an import. The two ints are the line and column of the definition site.
identIsNormal :: Ident -> Bool Source #
Namespaces
Namespaces for names
Constructors
NSValue | |
NSConstructor | This is for enum and newtype constructors |
NSType | |
NSModule |
Instances
allNamespaces :: [Namespace] Source #
Original names
Identifies an entitiy
Constructors
OrigName | |
Fields
|
Instances
Generic OrigName Source # | |
Show OrigName Source # | |
PP OrigName Source # | |
NFData OrigName Source # | |
Defined in Cryptol.Utils.Ident | |
Eq OrigName Source # | |
Ord OrigName Source # | |
Defined in Cryptol.Utils.Ident | |
type Rep OrigName Source # | |
Defined in Cryptol.Utils.Ident type Rep OrigName = D1 ('MetaData "OrigName" "Cryptol.Utils.Ident" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "OrigName" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ogNamespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Namespace) :*: S1 ('MetaSel ('Just "ogModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModPath)) :*: (S1 ('MetaSel ('Just "ogSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OrigSource) :*: (S1 ('MetaSel ('Just "ogName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Just "ogFromParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Ident)))))) |
data OrigSource Source #
Describes where a top-level name came from
Constructors
FromDefinition | |
FromFunctorInst | |
FromModParam |
Instances
ogIsModParam :: OrigName -> Bool Source #
Returns true iff the ogSource
of the given OrigName
is FromModParam
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
Generic PrimIdent Source # | |
Show PrimIdent Source # | |
PP PrimIdent Source # | |
NFData PrimIdent Source # | |
Defined in Cryptol.Utils.Ident | |
Eq PrimIdent Source # | |
Ord PrimIdent Source # | |
type Rep PrimIdent Source # | |
Defined in Cryptol.Utils.Ident type Rep PrimIdent = D1 ('MetaData "PrimIdent" "Cryptol.Utils.Ident" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" '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 #