Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data kinds and corresponding singletons (via the singletons
library) for kinds
used in various places in Language.Fortran.Model.
As documentation in Template Haskell is not yet supported, documentation for each data type is given here.
Precision
The precision, in bits, of an intrinsic Fortran data type.
BasicType
The basic type of an intrinsic Fortran data type.
OpKind
TODO
precMax
Finds the maximum of two precisions. Use PrecMax
at the type level and sPrecMax
for singletons.
basicTypeMax
Finds the 'largest' (with respect to the size of the set it semantically
represents) of numeric basic types. Also works with non-numeric basic types, but
the result in that case is unspecified. Use BasicTypeMax
at the type level and
sBasicTypeMax
for singletons.
Documentation
Instances
Instances
Instances
Eq OpKind Source # | |
Ord OpKind Source # | |
Show OpKind Source # | |
SingKind OpKind Source # | |
SingI 'OKLit Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKNum Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKEq Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKRel Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKLogical Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKLookup Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKDeref Source # | |
Defined in Language.Fortran.Model.Singletons | |
SingI 'OKWriteArr Source # | |
Defined in Language.Fortran.Model.Singletons sing :: Sing 'OKWriteArr | |
SingI 'OKWriteData Source # | |
Defined in Language.Fortran.Model.Singletons sing :: Sing 'OKWriteData | |
type Demote OpKind Source # | |
Defined in Language.Fortran.Model.Singletons | |
type Sing Source # | |
Defined in Language.Fortran.Model.Singletons type Sing = SOpKind |
type BTRealSym0 = BTReal :: BasicType Source #
type BTLogicalSym0 = BTLogical :: BasicType Source #
type BTCharSym0 = BTChar :: BasicType Source #
type OKLogicalSym0 = OKLogical :: OpKind Source #
type OKLookupSym0 = OKLookup :: OpKind Source #
type OKDerefSym0 = OKDeref :: OpKind Source #
type OKWriteArrSym0 = OKWriteArr :: OpKind Source #
type OKWriteDataSym0 = OKWriteData :: OpKind Source #
type family BasicTypeMax a a where ... Source #
BasicTypeMax a_6989586621679387412 a_6989586621679387414 = Apply (Apply MaxSym0 a_6989586621679387412) a_6989586621679387414 |
type BasicTypeMaxSym2 (a6989586621679387419 :: BasicType) (a6989586621679387420 :: BasicType) = BasicTypeMax a6989586621679387419 a6989586621679387420 :: BasicType Source #
data BasicTypeMaxSym1 a6989586621679387419 a6989586621679387420 where Source #
BasicTypeMaxSym1KindInference :: SameKind (Apply (BasicTypeMaxSym1 a6989586621679387419) arg) (BasicTypeMaxSym2 a6989586621679387419 arg) => BasicTypeMaxSym1 a6989586621679387419 a6989586621679387420 |
Instances
SingI d => SingI (BasicTypeMaxSym1 d :: TyFun BasicType BasicType -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons sing :: Sing (BasicTypeMaxSym1 d) | |
SuppressUnusedWarnings (BasicTypeMaxSym1 a6989586621679387419 :: TyFun BasicType BasicType -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons suppressUnusedWarnings :: () | |
type Apply (BasicTypeMaxSym1 a6989586621679387419 :: TyFun BasicType BasicType -> Type) (a6989586621679387420 :: BasicType) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply (BasicTypeMaxSym1 a6989586621679387419 :: TyFun BasicType BasicType -> Type) (a6989586621679387420 :: BasicType) = BasicTypeMaxSym2 a6989586621679387419 a6989586621679387420 |
data BasicTypeMaxSym0 a6989586621679387419 where Source #
BasicTypeMaxSym0KindInference :: SameKind (Apply BasicTypeMaxSym0 arg) (BasicTypeMaxSym1 arg) => BasicTypeMaxSym0 a6989586621679387419 |
Instances
SingI BasicTypeMaxSym0 Source # | |
Defined in Language.Fortran.Model.Singletons sing :: Sing BasicTypeMaxSym0 | |
SuppressUnusedWarnings BasicTypeMaxSym0 Source # | |
Defined in Language.Fortran.Model.Singletons suppressUnusedWarnings :: () | |
type Apply BasicTypeMaxSym0 (a6989586621679387419 :: BasicType) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply BasicTypeMaxSym0 (a6989586621679387419 :: BasicType) = BasicTypeMaxSym1 a6989586621679387419 |
type family PrecMax a a where ... Source #
PrecMax a_6989586621679387423 a_6989586621679387425 = Apply (Apply MaxSym0 a_6989586621679387423) a_6989586621679387425 |
type PrecMaxSym2 (a6989586621679387430 :: Precision) (a6989586621679387431 :: Precision) = PrecMax a6989586621679387430 a6989586621679387431 :: Precision Source #
data PrecMaxSym1 a6989586621679387430 a6989586621679387431 where Source #
PrecMaxSym1KindInference :: SameKind (Apply (PrecMaxSym1 a6989586621679387430) arg) (PrecMaxSym2 a6989586621679387430 arg) => PrecMaxSym1 a6989586621679387430 a6989586621679387431 |
Instances
SingI d => SingI (PrecMaxSym1 d :: TyFun Precision Precision -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons sing :: Sing (PrecMaxSym1 d) | |
SuppressUnusedWarnings (PrecMaxSym1 a6989586621679387430 :: TyFun Precision Precision -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons suppressUnusedWarnings :: () | |
type Apply (PrecMaxSym1 a6989586621679387430 :: TyFun Precision Precision -> Type) (a6989586621679387431 :: Precision) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply (PrecMaxSym1 a6989586621679387430 :: TyFun Precision Precision -> Type) (a6989586621679387431 :: Precision) = PrecMaxSym2 a6989586621679387430 a6989586621679387431 |
data PrecMaxSym0 a6989586621679387430 where Source #
PrecMaxSym0KindInference :: SameKind (Apply PrecMaxSym0 arg) (PrecMaxSym1 arg) => PrecMaxSym0 a6989586621679387430 |
Instances
SingI PrecMaxSym0 Source # | |
Defined in Language.Fortran.Model.Singletons sing :: Sing PrecMaxSym0 | |
SuppressUnusedWarnings PrecMaxSym0 Source # | |
Defined in Language.Fortran.Model.Singletons suppressUnusedWarnings :: () | |
type Apply PrecMaxSym0 (a6989586621679387430 :: Precision) Source # | |
Defined in Language.Fortran.Model.Singletons |
type family Compare_6989586621679388653 a a where ... Source #
type Compare_6989586621679388653Sym2 (a6989586621679388658 :: Precision) (a6989586621679388659 :: Precision) = Compare_6989586621679388653 a6989586621679388658 a6989586621679388659 :: Ordering Source #
data Compare_6989586621679388653Sym1 a6989586621679388658 a6989586621679388659 where Source #
Compare_6989586621679388653Sym1KindInference :: SameKind (Apply (Compare_6989586621679388653Sym1 a6989586621679388658) arg) (Compare_6989586621679388653Sym2 a6989586621679388658 arg) => Compare_6989586621679388653Sym1 a6989586621679388658 a6989586621679388659 |
Instances
SuppressUnusedWarnings (Compare_6989586621679388653Sym1 a6989586621679388658 :: TyFun Precision Ordering -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons suppressUnusedWarnings :: () | |
type Apply (Compare_6989586621679388653Sym1 a6989586621679388658 :: TyFun Precision Ordering -> Type) (a6989586621679388659 :: Precision) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply (Compare_6989586621679388653Sym1 a6989586621679388658 :: TyFun Precision Ordering -> Type) (a6989586621679388659 :: Precision) = Compare_6989586621679388653Sym2 a6989586621679388658 a6989586621679388659 |
data Compare_6989586621679388653Sym0 a6989586621679388658 where Source #
Compare_6989586621679388653Sym0KindInference :: SameKind (Apply Compare_6989586621679388653Sym0 arg) (Compare_6989586621679388653Sym1 arg) => Compare_6989586621679388653Sym0 a6989586621679388658 |
Instances
SuppressUnusedWarnings Compare_6989586621679388653Sym0 Source # | |
Defined in Language.Fortran.Model.Singletons suppressUnusedWarnings :: () | |
type Apply Compare_6989586621679388653Sym0 (a6989586621679388658 :: Precision) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply Compare_6989586621679388653Sym0 (a6989586621679388658 :: Precision) = Compare_6989586621679388653Sym1 a6989586621679388658 |
type family Compare_6989586621679388662 a a where ... Source #
type Compare_6989586621679388662Sym2 (a6989586621679388667 :: BasicType) (a6989586621679388668 :: BasicType) = Compare_6989586621679388662 a6989586621679388667 a6989586621679388668 :: Ordering Source #
data Compare_6989586621679388662Sym1 a6989586621679388667 a6989586621679388668 where Source #
Compare_6989586621679388662Sym1KindInference :: SameKind (Apply (Compare_6989586621679388662Sym1 a6989586621679388667) arg) (Compare_6989586621679388662Sym2 a6989586621679388667 arg) => Compare_6989586621679388662Sym1 a6989586621679388667 a6989586621679388668 |
Instances
SuppressUnusedWarnings (Compare_6989586621679388662Sym1 a6989586621679388667 :: TyFun BasicType Ordering -> Type) Source # | |
Defined in Language.Fortran.Model.Singletons suppressUnusedWarnings :: () | |
type Apply (Compare_6989586621679388662Sym1 a6989586621679388667 :: TyFun BasicType Ordering -> Type) (a6989586621679388668 :: BasicType) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply (Compare_6989586621679388662Sym1 a6989586621679388667 :: TyFun BasicType Ordering -> Type) (a6989586621679388668 :: BasicType) = Compare_6989586621679388662Sym2 a6989586621679388667 a6989586621679388668 |
data Compare_6989586621679388662Sym0 a6989586621679388667 where Source #
Compare_6989586621679388662Sym0KindInference :: SameKind (Apply Compare_6989586621679388662Sym0 arg) (Compare_6989586621679388662Sym1 arg) => Compare_6989586621679388662Sym0 a6989586621679388667 |
Instances
SuppressUnusedWarnings Compare_6989586621679388662Sym0 Source # | |
Defined in Language.Fortran.Model.Singletons suppressUnusedWarnings :: () | |
type Apply Compare_6989586621679388662Sym0 (a6989586621679388667 :: BasicType) Source # | |
Defined in Language.Fortran.Model.Singletons type Apply Compare_6989586621679388662Sym0 (a6989586621679388667 :: BasicType) = Compare_6989586621679388662Sym1 a6989586621679388667 |
type family Equals_6989586621679388669 a b where ... Source #
Equals_6989586621679388669 P8 P8 = TrueSym0 | |
Equals_6989586621679388669 P16 P16 = TrueSym0 | |
Equals_6989586621679388669 P32 P32 = TrueSym0 | |
Equals_6989586621679388669 P64 P64 = TrueSym0 | |
Equals_6989586621679388669 P128 P128 = TrueSym0 | |
Equals_6989586621679388669 (_ :: Precision) (_ :: Precision) = FalseSym0 |
type family Equals_6989586621679388673 a b where ... Source #
Equals_6989586621679388673 BTInt BTInt = TrueSym0 | |
Equals_6989586621679388673 BTReal BTReal = TrueSym0 | |
Equals_6989586621679388673 BTLogical BTLogical = TrueSym0 | |
Equals_6989586621679388673 BTChar BTChar = TrueSym0 | |
Equals_6989586621679388673 (_ :: BasicType) (_ :: BasicType) = FalseSym0 |
data SPrecision :: Precision -> Type where Source #
SP8 :: SPrecision (P8 :: Precision) | |
SP16 :: SPrecision (P16 :: Precision) | |
SP32 :: SPrecision (P32 :: Precision) | |
SP64 :: SPrecision (P64 :: Precision) | |
SP128 :: SPrecision (P128 :: Precision) |
Instances
TestCoercion SPrecision Source # | |
Defined in Language.Fortran.Model.Singletons testCoercion :: forall (a :: k) (b :: k). SPrecision a -> SPrecision b -> Maybe (Coercion a b) # | |
TestEquality SPrecision Source # | |
Defined in Language.Fortran.Model.Singletons testEquality :: forall (a :: k) (b :: k). SPrecision a -> SPrecision b -> Maybe (a :~: b) # |
data SBasicType :: BasicType -> Type where Source #
SBTInt :: SBasicType (BTInt :: BasicType) | |
SBTReal :: SBasicType (BTReal :: BasicType) | |
SBTLogical :: SBasicType (BTLogical :: BasicType) | |
SBTChar :: SBasicType (BTChar :: BasicType) |
Instances
TestCoercion SBasicType Source # | |
Defined in Language.Fortran.Model.Singletons testCoercion :: forall (a :: k) (b :: k). SBasicType a -> SBasicType b -> Maybe (Coercion a b) # | |
TestEquality SBasicType Source # | |
Defined in Language.Fortran.Model.Singletons testEquality :: forall (a :: k) (b :: k). SBasicType a -> SBasicType b -> Maybe (a :~: b) # |
data SOpKind :: OpKind -> Type where Source #
SOKLit :: SOpKind (OKLit :: OpKind) | |
SOKNum :: SOpKind (OKNum :: OpKind) | |
SOKEq :: SOpKind (OKEq :: OpKind) | |
SOKRel :: SOpKind (OKRel :: OpKind) | |
SOKLogical :: SOpKind (OKLogical :: OpKind) | |
SOKLookup :: SOpKind (OKLookup :: OpKind) | |
SOKDeref :: SOpKind (OKDeref :: OpKind) | |
SOKWriteArr :: SOpKind (OKWriteArr :: OpKind) | |
SOKWriteData :: SOpKind (OKWriteData :: OpKind) |
sPrecMax :: forall (t :: Precision) (t :: Precision). Sing t -> Sing t -> Sing (Apply (Apply PrecMaxSym0 t) t :: Precision) Source #
sBasicTypeMax :: forall (t :: BasicType) (t :: BasicType). Sing t -> Sing t -> Sing (Apply (Apply BasicTypeMaxSym0 t) t :: BasicType) Source #