cryptol-3.1.0: Cryptol: The Language of Cryptography
Copyright(c) 2015-2016 Galois Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cryptol.Utils.Ident

Description

 
Synopsis

Module names

data ModPath Source #

Idnetifies a possibly nested module

Instances

Instances details
Generic ModPath Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep ModPath :: Type -> Type #

Methods

from :: ModPath -> Rep ModPath x #

to :: Rep ModPath x -> ModPath #

Show ModPath Source # 
Instance details

Defined in Cryptol.Utils.Ident

PP ModPath Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> ModPath -> Doc Source #

NFData ModPath Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: ModPath -> () #

Eq ModPath Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

(==) :: ModPath -> ModPath -> Bool #

(/=) :: ModPath -> ModPath -> Bool #

Ord ModPath Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep ModPath Source # 
Instance details

Defined in Cryptol.Utils.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.

data ModName Source #

Top-level Module names are just text.

Instances

Instances details
Generic ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep ModName :: Type -> Type #

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

Show ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

PP ModName Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> ModName -> Doc Source #

PPName ModName Source # 
Instance details

Defined in Cryptol.Utils.PP

NFData ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: ModName -> () #

Eq ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

(==) :: ModName -> ModName -> Bool #

(/=) :: ModName -> ModName -> Bool #

Ord ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep ModName Source # 
Instance details

Defined in Cryptol.Utils.Ident

textToModName :: Text -> ModName Source #

Make a normal module name out of text.

modNameChunks :: ModName -> [String] Source #

Break up a module name on the separators, String version

modNameChunksText :: ModName -> [Text] Source #

Break up a module name on the separators, Text version.

modNameArg :: ModName -> ModName Source #

Change a normal module name to a module name to be used for an anonnymous argument.

modNameIfaceMod :: ModName -> ModName Source #

Change a normal module name to a module name to be used for an anonnymous interface.

modNameToNormalModName :: ModName -> ModName 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

data Ident Source #

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

Instances details
IsString Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

fromString :: String -> Ident #

Generic Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep Ident :: Type -> Type #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

Show Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

ShowParseable Ident Source # 
Instance details

Defined in Cryptol.TypeCheck.Parseable

PP Ident Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> Ident -> Doc Source #

NFData Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: Ident -> () #

Eq Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

(==) :: Ident -> Ident -> Bool #

(/=) :: Ident -> Ident -> Bool #

Ord Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

compare :: Ident -> Ident -> Ordering #

(<) :: Ident -> Ident -> Bool #

(<=) :: Ident -> Ident -> Bool #

(>) :: Ident -> Ident -> Bool #

(>=) :: Ident -> Ident -> Bool #

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

type Rep Ident Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep Ident

packIdent :: String -> Ident Source #

Make a normal (i.e., not anonymous) identifier

packInfix :: String -> Ident Source #

Make a normal (i.e., not anonymous) identifier

mkIdent :: Text -> Ident Source #

Make a normal (i.e., not anonymous) identifier

identAnonArg :: Ident -> Ident Source #

Make an anonymous identifier for the module corresponding to a `where` block in a functor instantiation.

identAnonIfaceMod :: Ident -> Ident Source #

Make an anonymous identifier for the interface corresponding to a parameter declaration.

Namespaces

data Namespace Source #

Namespaces for names

Constructors

NSValue 
NSConstructor

This is for enum and newtype constructors

NSType 
NSModule 

Instances

Instances details
Bounded Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Enum Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Generic Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep Namespace :: Type -> Type #

Show Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

PP Namespace Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> Namespace -> Doc Source #

NFData Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: Namespace -> () #

Eq Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

Ord Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep Namespace Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep Namespace = D1 ('MetaData "Namespace" "Cryptol.Utils.Ident" "cryptol-3.1.0-276efOa9Q2aIFSEzDdp2Mp" 'False) ((C1 ('MetaCons "NSValue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NSConstructor" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NSType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NSModule" 'PrefixI 'False) (U1 :: Type -> Type)))

Original names

data OrigName Source #

Identifies an entitiy

Constructors

OrigName 

Fields

Instances

Instances details
Generic OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep OrigName :: Type -> Type #

Methods

from :: OrigName -> Rep OrigName x #

to :: Rep OrigName x -> OrigName #

Show OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

PP OrigName Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> OrigName -> Doc Source #

NFData OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: OrigName -> () #

Eq OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

Ord OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep OrigName Source # 
Instance details

Defined in Cryptol.Utils.Ident

data OrigSource Source #

Describes where a top-level name came from

Instances

Instances details
Generic OrigSource Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep OrigSource :: Type -> Type #

Show OrigSource Source # 
Instance details

Defined in Cryptol.Utils.Ident

NFData OrigSource Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: OrigSource -> () #

Eq OrigSource Source # 
Instance details

Defined in Cryptol.Utils.Ident

Ord OrigSource Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep OrigSource Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep OrigSource = D1 ('MetaData "OrigSource" "Cryptol.Utils.Ident" "cryptol-3.1.0-276efOa9Q2aIFSEzDdp2Mp" 'False) (C1 ('MetaCons "FromDefinition" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FromFunctorInst" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FromModParam" 'PrefixI 'False) (U1 :: Type -> Type)))

ogIsModParam :: OrigName -> Bool Source #

Returns true iff the ogSource of the given OrigName is FromModParam

Identifiers for primitives

data PrimIdent Source #

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

Constructors

PrimIdent ModName Text 

Instances

Instances details
Generic PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

Associated Types

type Rep PrimIdent :: Type -> Type #

Show PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

PP PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

ppPrec :: Int -> PrimIdent -> Doc Source #

NFData PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

Methods

rnf :: PrimIdent -> () #

Eq PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

Ord PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep PrimIdent Source # 
Instance details

Defined in Cryptol.Utils.Ident

type Rep PrimIdent = D1 ('MetaData "PrimIdent" "Cryptol.Utils.Ident" "cryptol-3.1.0-276efOa9Q2aIFSEzDdp2Mp" '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)))

prelPrim :: Text -> PrimIdent Source #

A shortcut to make (non-infix) primitives in the prelude.