fortran-vars-0.3.0: Fortran memory model and other static analysis tools.
Safe HaskellNone
LanguageHaskell2010

Language.Fortran.Vars.Types

Synopsis

Documentation

data TypeError Source #

Instances

Instances details
Eq TypeError Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Ord TypeError Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Show TypeError Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Generic TypeError Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Associated Types

type Rep TypeError :: Type -> Type #

ToJSON TypeError Source # 
Instance details

Defined in Language.Fortran.Vars.Types

FromJSON TypeError Source # 
Instance details

Defined in Language.Fortran.Vars.Types

type Rep TypeError Source # 
Instance details

Defined in Language.Fortran.Vars.Types

type ProgramStructureTables = Map ProgramUnitName StructureTable Source #

Mapping from name of a program unit to relevant structure table

type ProgramUnitModel = (SymbolTable, StorageTable) Source #

The model to represent an individual ProgramUnit

type StorageTable = Map MemoryBlockName MemoryBlock Source #

Mapping from the name of a memory block to the information about it

data StructureTableEntry Source #

Data structurue for a single field of a structure

Instances

Instances details
Eq StructureTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Data StructureTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StructureTableEntry -> c StructureTableEntry #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StructureTableEntry #

toConstr :: StructureTableEntry -> Constr #

dataTypeOf :: StructureTableEntry -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StructureTableEntry) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StructureTableEntry) #

gmapT :: (forall b. Data b => b -> b) -> StructureTableEntry -> StructureTableEntry #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StructureTableEntry -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StructureTableEntry -> r #

gmapQ :: (forall d. Data d => d -> u) -> StructureTableEntry -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StructureTableEntry -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StructureTableEntry -> m StructureTableEntry #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StructureTableEntry -> m StructureTableEntry #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StructureTableEntry -> m StructureTableEntry #

Show StructureTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

type StructureTable = Map String Structure Source #

Map from a structure name to its internal structure, specifying members and their corresponding type. This can then be used to check the type of a data reference expression.

data MemoryBlock Source #

Structure to hold information about the named blocks of memory in the program

Constructors

MemoryBlock 

Fields

Instances

Instances details
Eq MemoryBlock Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Data MemoryBlock Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MemoryBlock -> c MemoryBlock #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MemoryBlock #

toConstr :: MemoryBlock -> Constr #

dataTypeOf :: MemoryBlock -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MemoryBlock) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MemoryBlock) #

gmapT :: (forall b. Data b => b -> b) -> MemoryBlock -> MemoryBlock #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MemoryBlock -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MemoryBlock -> r #

gmapQ :: (forall d. Data d => d -> u) -> MemoryBlock -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MemoryBlock -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MemoryBlock -> m MemoryBlock #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MemoryBlock -> m MemoryBlock #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MemoryBlock -> m MemoryBlock #

Ord MemoryBlock Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Show MemoryBlock Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Generic MemoryBlock Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Associated Types

type Rep MemoryBlock :: Type -> Type #

ToJSON MemoryBlock Source # 
Instance details

Defined in Language.Fortran.Vars.Types

FromJSON MemoryBlock Source # 
Instance details

Defined in Language.Fortran.Vars.Types

type Rep MemoryBlock Source # 
Instance details

Defined in Language.Fortran.Vars.Types

type Rep MemoryBlock = D1 ('MetaData "MemoryBlock" "Language.Fortran.Vars.Types" "fortran-vars-0.3.0-inplace" 'False) (C1 ('MetaCons "MemoryBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "blockSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "storageClass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StorageClass) :*: S1 ('MetaSel ('Just "variables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]))))

type SymbolTable = Map Name SymbolTableEntry Source #

Symbol table containing all non-intrisic symbols declared in a program

data SymbolTableEntry Source #

An entry in the SymbolTable for some variable

Constructors

SParameter 

Fields

SVariable 

Fields

SDummy 

Fields

SExternal 

Fields

Instances

Instances details
Eq SymbolTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Data SymbolTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SymbolTableEntry -> c SymbolTableEntry #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SymbolTableEntry #

toConstr :: SymbolTableEntry -> Constr #

dataTypeOf :: SymbolTableEntry -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SymbolTableEntry) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SymbolTableEntry) #

gmapT :: (forall b. Data b => b -> b) -> SymbolTableEntry -> SymbolTableEntry #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SymbolTableEntry -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SymbolTableEntry -> r #

gmapQ :: (forall d. Data d => d -> u) -> SymbolTableEntry -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SymbolTableEntry -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SymbolTableEntry -> m SymbolTableEntry #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SymbolTableEntry -> m SymbolTableEntry #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SymbolTableEntry -> m SymbolTableEntry #

Ord SymbolTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Show SymbolTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Generic SymbolTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Associated Types

type Rep SymbolTableEntry :: Type -> Type #

ToJSON SymbolTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

FromJSON SymbolTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

type Rep SymbolTableEntry Source # 
Instance details

Defined in Language.Fortran.Vars.Types

type Dimensions = [(Int, Int)] Source #

The declared dimensions of a staticically typed array variable type is of the form [(dim1_lower, dim1_upper), (dim2_lower, dim2_upper)]

data StorageClass Source #

The declared lifetimes of the variables in memory

Instances

Instances details
Eq StorageClass Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Data StorageClass Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StorageClass -> c StorageClass #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StorageClass #

toConstr :: StorageClass -> Constr #

dataTypeOf :: StorageClass -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StorageClass) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StorageClass) #

gmapT :: (forall b. Data b => b -> b) -> StorageClass -> StorageClass #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StorageClass -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StorageClass -> r #

gmapQ :: (forall d. Data d => d -> u) -> StorageClass -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StorageClass -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StorageClass -> m StorageClass #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StorageClass -> m StorageClass #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StorageClass -> m StorageClass #

Ord StorageClass Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Show StorageClass Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Generic StorageClass Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Associated Types

type Rep StorageClass :: Type -> Type #

ToJSON StorageClass Source # 
Instance details

Defined in Language.Fortran.Vars.Types

FromJSON StorageClass Source # 
Instance details

Defined in Language.Fortran.Vars.Types

type Rep StorageClass Source # 
Instance details

Defined in Language.Fortran.Vars.Types

type Rep StorageClass = D1 ('MetaData "StorageClass" "Language.Fortran.Vars.Types" "fortran-vars-0.3.0-inplace" 'False) ((C1 ('MetaCons "Static" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Automatic" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Constant" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Common" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unspecified" 'PrefixI 'False) (U1 :: Type -> Type))))

type Location = (MemoryBlockName, Offset) Source #

The location of a variable, i.e. the MemoryBlockName that contains it as well as the Offset to its location in memory

type MemoryBlockName = Name Source #

The name of block of memory

type Offset = Int Source #

Memory offset given to a variable in memory

data ExpVal Source #

The evaluated value of a FORTRAN expression

Instances

Instances details
Eq ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Methods

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

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

Data ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpVal -> c ExpVal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpVal #

toConstr :: ExpVal -> Constr #

dataTypeOf :: ExpVal -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExpVal) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpVal) #

gmapT :: (forall b. Data b => b -> b) -> ExpVal -> ExpVal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpVal -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpVal -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExpVal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpVal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpVal -> m ExpVal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpVal -> m ExpVal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpVal -> m ExpVal #

Ord ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Show ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Generic ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Associated Types

type Rep ExpVal :: Type -> Type #

Methods

from :: ExpVal -> Rep ExpVal x #

to :: Rep ExpVal x -> ExpVal #

ToJSON ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Types

FromJSON ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Types

NFData ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Types

Methods

rnf :: ExpVal -> () #

type Rep ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Types

typeError :: SrcSpan -> String -> TypeError Source #

Helper method for getting the FilePath out of SrcSpan

data SemType #

Semantic type assigned to variables.

BaseType stores the "type tag" given in syntax. SemTypes add metadata (kind and length), and resolve some "simple" types to a core type with a preset kind (e.g. `DOUBLE PRECISION` -> `REAL(8)`).

Fortran 90 (and beyond) features may not be well supported.

Instances

Instances details
Eq SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

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

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

Data SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SemType -> c SemType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SemType #

toConstr :: SemType -> Constr #

dataTypeOf :: SemType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SemType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SemType) #

gmapT :: (forall b. Data b => b -> b) -> SemType -> SemType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SemType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SemType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SemType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SemType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SemType -> m SemType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SemType -> m SemType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SemType -> m SemType #

Ord SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Show SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Generic SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Associated Types

type Rep SemType :: Type -> Type #

Methods

from :: SemType -> Rep SemType x #

to :: Rep SemType x -> SemType #

Out SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

docPrec :: Int -> SemType -> Doc #

doc :: SemType -> Doc #

docList :: [SemType] -> Doc #

Binary SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

put :: SemType -> Put #

get :: Get SemType #

putList :: [SemType] -> Put #

Pretty SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep SemType = D1 ('MetaData "SemType" "Language.Fortran.Analysis.SemanticTypes" "fortran-src-0.8.0-58cee80cdc027fa3d4e093713bdbc453ef13b1cb991712a110c942406e8ab709" 'False) (((C1 ('MetaCons "TInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "TReal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind))) :+: (C1 ('MetaCons "TComplex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "TLogical" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)))) :+: ((C1 ('MetaCons "TByte" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "TCharacter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CharacterLen) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind))) :+: (C1 ('MetaCons "TArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SemType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Dimensions))) :+: C1 ('MetaCons "TCustom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

data CharacterLen #

Constructors

CharLenStar

specified with a *

CharLenColon

specified with a : (Fortran2003) FIXME, possibly, with a more robust const-exp:

CharLenExp

specified with a non-trivial expression

CharLenInt Int

specified with a constant integer

Instances

Instances details
Eq CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Data CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CharacterLen -> c CharacterLen #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CharacterLen #

toConstr :: CharacterLen -> Constr #

dataTypeOf :: CharacterLen -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CharacterLen) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CharacterLen) #

gmapT :: (forall b. Data b => b -> b) -> CharacterLen -> CharacterLen #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CharacterLen -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CharacterLen -> r #

gmapQ :: (forall d. Data d => d -> u) -> CharacterLen -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CharacterLen -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CharacterLen -> m CharacterLen #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CharacterLen -> m CharacterLen #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CharacterLen -> m CharacterLen #

Ord CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Show CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Generic CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Associated Types

type Rep CharacterLen :: Type -> Type #

Out CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Binary CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

NFData CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

rnf :: CharacterLen -> () #

type Rep CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep CharacterLen = D1 ('MetaData "CharacterLen" "Language.Fortran.Analysis.SemanticTypes" "fortran-src-0.8.0-58cee80cdc027fa3d4e093713bdbc453ef13b1cb991712a110c942406e8ab709" 'False) ((C1 ('MetaCons "CharLenStar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CharLenColon" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CharLenExp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CharLenInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

type Kind = Int #

Orphan instances