fortran-src-0.11.0: Parsers and analyses for Fortran standards 66, 77, 90, 95 and 2003 (partial).
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Fortran.Repr.Type.Scalar.Int

Synopsis

Documentation

data FTInt Source #

Constructors

FTInt1 
FTInt2 
FTInt4 
FTInt8 
FTInt16 

Instances

Instances details
Data FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

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

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

toConstr :: FTInt -> Constr #

dataTypeOf :: FTInt -> DataType #

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

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

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

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

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

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

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

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

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

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

Enum FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Generic FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Associated Types

type Rep FTInt :: Type -> Type #

Methods

from :: FTInt -> Rep FTInt x #

to :: Rep FTInt x -> FTInt #

Show FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

showsPrec :: Int -> FTInt -> ShowS #

show :: FTInt -> String #

showList :: [FTInt] -> ShowS #

Show SomeFIntI Source # 
Instance details

Defined in Language.Fortran.Repr.Value.Scalar.Int.Idealized

Show SomeFInt Source # 
Instance details

Defined in Language.Fortran.Repr.Value.Scalar.Int.Machine

FKinded FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Associated Types

type FKindOf x :: FKindType Source #

type FKindDefault :: a Source #

Eq FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

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

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

Eq SomeFIntI Source # 
Instance details

Defined in Language.Fortran.Repr.Value.Scalar.Int.Idealized

Eq SomeFInt Source # 
Instance details

Defined in Language.Fortran.Repr.Value.Scalar.Int.Machine

Ord FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

compare :: FTInt -> FTInt -> Ordering #

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

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

(>) :: FTInt -> FTInt -> Bool #

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

max :: FTInt -> FTInt -> FTInt #

min :: FTInt -> FTInt -> FTInt #

SingKind FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Associated Types

type Demote FTInt = (r :: Type) #

Methods

fromSing :: forall (a :: FTInt). Sing a -> Demote FTInt #

toSing :: Demote FTInt -> SomeSing FTInt #

SDecide FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

(%~) :: forall (a :: FTInt) (b :: FTInt). Sing a -> Sing b -> Decision (a :~: b) #

PEq FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Associated Types

type arg == arg1 :: Bool #

type arg /= arg1 :: Bool #

SEq FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

(%==) :: forall (t1 :: FTInt) (t2 :: FTInt). Sing t1 -> Sing t2 -> Sing (Apply (Apply (==@#@$) t1) t2) #

(%/=) :: forall (t1 :: FTInt) (t2 :: FTInt). Sing t1 -> Sing t2 -> Sing (Apply (Apply (/=@#@$) t1) t2) #

POrd FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

SOrd FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

sCompare :: forall (t1 :: FTInt) (t2 :: FTInt). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: forall (t1 :: FTInt) (t2 :: FTInt). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: forall (t1 :: FTInt) (t2 :: FTInt). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: forall (t1 :: FTInt) (t2 :: FTInt). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: forall (t1 :: FTInt) (t2 :: FTInt). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: forall (t1 :: FTInt) (t2 :: FTInt). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

sMin :: forall (t1 :: FTInt) (t2 :: FTInt). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) #

PShow FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: FTInt) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: FTInt). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [FTInt]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

TestCoercion SFTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

testCoercion :: forall (a :: k) (b :: k). SFTInt a -> SFTInt b -> Maybe (Coercion a b) #

TestEquality SFTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

testEquality :: forall (a :: k) (b :: k). SFTInt a -> SFTInt b -> Maybe (a :~: b) #

SingI 'FTInt1 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

sing :: Sing 'FTInt1 #

SingI 'FTInt16 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

sing :: Sing 'FTInt16 #

SingI 'FTInt2 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

sing :: Sing 'FTInt2 #

SingI 'FTInt4 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

sing :: Sing 'FTInt4 #

SingI 'FTInt8 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

sing :: Sing 'FTInt8 #

Show (SomeFVA FTInt FInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Value.Array.Machine

SuppressUnusedWarnings Compare_6989586621679161570Sym0 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

SuppressUnusedWarnings TFHelper_6989586621679161561Sym0 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

SuppressUnusedWarnings ShowsPrec_6989586621679161580Sym0 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

SuppressUnusedWarnings (Compare_6989586621679161570Sym1 a6989586621679161575 :: TyFun FTInt Ordering -> Type) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

SuppressUnusedWarnings (ShowsPrec_6989586621679161580Sym1 a6989586621679161596 :: TyFun FTInt (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

SuppressUnusedWarnings (TFHelper_6989586621679161561Sym1 a6989586621679161566 :: TyFun FTInt Bool -> Type) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Rep FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Rep FTInt = D1 ('MetaData "FTInt" "Language.Fortran.Repr.Type.Scalar.Int" "fortran-src-0.11.0-inplace" 'False) ((C1 ('MetaCons "FTInt1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FTInt2" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FTInt4" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FTInt8" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FTInt16" 'PrefixI 'False) (U1 :: Type -> Type))))
type FKindDefault Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Demote FTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Sing Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Sing = SFTInt
type FKindOf 'FTInt1 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type FKindOf 'FTInt1 = 1
type FKindOf 'FTInt16 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type FKindOf 'FTInt16 = 16
type FKindOf 'FTInt2 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type FKindOf 'FTInt2 = 2
type FKindOf 'FTInt4 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type FKindOf 'FTInt4 = 4
type FKindOf 'FTInt8 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type FKindOf 'FTInt8 = 8
type Show_ (arg :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Show_ (arg :: FTInt) = Apply (Show__6989586621680059119Sym0 :: TyFun FTInt Symbol -> Type) arg
type (arg :: FTInt) /= (arg1 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type (arg :: FTInt) /= (arg1 :: FTInt) = Apply (Apply (TFHelper_6989586621679129971Sym0 :: TyFun FTInt (FTInt ~> Bool) -> Type) arg) arg1
type (a1 :: FTInt) == (a2 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type (a1 :: FTInt) == (a2 :: FTInt) = Apply (Apply TFHelper_6989586621679161561Sym0 a1) a2
type (arg :: FTInt) < (arg1 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type (arg :: FTInt) < (arg1 :: FTInt) = Apply (Apply (TFHelper_6989586621679167373Sym0 :: TyFun FTInt (FTInt ~> Bool) -> Type) arg) arg1
type (arg :: FTInt) <= (arg1 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type (arg :: FTInt) <= (arg1 :: FTInt) = Apply (Apply (TFHelper_6989586621679167389Sym0 :: TyFun FTInt (FTInt ~> Bool) -> Type) arg) arg1
type (arg :: FTInt) > (arg1 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type (arg :: FTInt) > (arg1 :: FTInt) = Apply (Apply (TFHelper_6989586621679167405Sym0 :: TyFun FTInt (FTInt ~> Bool) -> Type) arg) arg1
type (arg :: FTInt) >= (arg1 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type (arg :: FTInt) >= (arg1 :: FTInt) = Apply (Apply (TFHelper_6989586621679167421Sym0 :: TyFun FTInt (FTInt ~> Bool) -> Type) arg) arg1
type Compare (a1 :: FTInt) (a2 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Max (arg :: FTInt) (arg1 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Max (arg :: FTInt) (arg1 :: FTInt) = Apply (Apply (Max_6989586621679167437Sym0 :: TyFun FTInt (FTInt ~> FTInt) -> Type) arg) arg1
type Min (arg :: FTInt) (arg1 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Min (arg :: FTInt) (arg1 :: FTInt) = Apply (Apply (Min_6989586621679167453Sym0 :: TyFun FTInt (FTInt ~> FTInt) -> Type) arg) arg1
type ShowList (arg :: [FTInt]) arg1 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type ShowList (arg :: [FTInt]) arg1 = Apply (Apply (ShowList_6989586621680059127Sym0 :: TyFun [FTInt] (Symbol ~> Symbol) -> Type) arg) arg1
type ShowsPrec a1 (a2 :: FTInt) a3 Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (Compare_6989586621679161570Sym1 a6989586621679161575 :: TyFun FTInt Ordering -> Type) (a6989586621679161576 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (Compare_6989586621679161570Sym1 a6989586621679161575 :: TyFun FTInt Ordering -> Type) (a6989586621679161576 :: FTInt) = Compare_6989586621679161570 a6989586621679161575 a6989586621679161576
type Apply (TFHelper_6989586621679161561Sym1 a6989586621679161566 :: TyFun FTInt Bool -> Type) (a6989586621679161567 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (TFHelper_6989586621679161561Sym1 a6989586621679161566 :: TyFun FTInt Bool -> Type) (a6989586621679161567 :: FTInt) = TFHelper_6989586621679161561 a6989586621679161566 a6989586621679161567
type Apply Compare_6989586621679161570Sym0 (a6989586621679161575 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply Compare_6989586621679161570Sym0 (a6989586621679161575 :: FTInt) = Compare_6989586621679161570Sym1 a6989586621679161575
type Apply TFHelper_6989586621679161561Sym0 (a6989586621679161566 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply TFHelper_6989586621679161561Sym0 (a6989586621679161566 :: FTInt) = TFHelper_6989586621679161561Sym1 a6989586621679161566
type Apply ShowsPrec_6989586621679161580Sym0 (a6989586621679161596 :: Natural) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply ShowsPrec_6989586621679161580Sym0 (a6989586621679161596 :: Natural) = ShowsPrec_6989586621679161580Sym1 a6989586621679161596
type Apply (ShowsPrec_6989586621679161580Sym1 a6989586621679161596 :: TyFun FTInt (Symbol ~> Symbol) -> Type) (a6989586621679161597 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (ShowsPrec_6989586621679161580Sym1 a6989586621679161596 :: TyFun FTInt (Symbol ~> Symbol) -> Type) (a6989586621679161597 :: FTInt) = ShowsPrec_6989586621679161580Sym2 a6989586621679161596 a6989586621679161597

type family FTInt1Sym0 :: FTInt where ... Source #

Equations

FTInt1Sym0 = FTInt1 

type family FTInt2Sym0 :: FTInt where ... Source #

Equations

FTInt2Sym0 = FTInt2 

type family FTInt4Sym0 :: FTInt where ... Source #

Equations

FTInt4Sym0 = FTInt4 

type family FTInt8Sym0 :: FTInt where ... Source #

Equations

FTInt8Sym0 = FTInt8 

type family FTInt16Sym0 :: FTInt where ... Source #

Equations

FTInt16Sym0 = FTInt16 

type family TFHelper_6989586621679161561 (a :: FTInt) (a :: FTInt) :: Bool where ... Source #

type family TFHelper_6989586621679161561Sym2 (a6989586621679161566 :: FTInt) (a6989586621679161567 :: FTInt) :: Bool where ... Source #

Equations

TFHelper_6989586621679161561Sym2 a6989586621679161566 a6989586621679161567 = TFHelper_6989586621679161561 a6989586621679161566 a6989586621679161567 

data TFHelper_6989586621679161561Sym1 (a6989586621679161566 :: FTInt) :: (~>) FTInt Bool where Source #

Constructors

TFHelper_6989586621679161561Sym1KindInference :: SameKind (Apply (TFHelper_6989586621679161561Sym1 a6989586621679161566) arg) (TFHelper_6989586621679161561Sym2 a6989586621679161566 arg) => TFHelper_6989586621679161561Sym1 a6989586621679161566 a6989586621679161567 

Instances

Instances details
SuppressUnusedWarnings (TFHelper_6989586621679161561Sym1 a6989586621679161566 :: TyFun FTInt Bool -> Type) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (TFHelper_6989586621679161561Sym1 a6989586621679161566 :: TyFun FTInt Bool -> Type) (a6989586621679161567 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (TFHelper_6989586621679161561Sym1 a6989586621679161566 :: TyFun FTInt Bool -> Type) (a6989586621679161567 :: FTInt) = TFHelper_6989586621679161561 a6989586621679161566 a6989586621679161567

type family Compare_6989586621679161570 (a :: FTInt) (a :: FTInt) :: Ordering where ... Source #

Equations

Compare_6989586621679161570 FTInt1 FTInt1 = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) NilSym0 
Compare_6989586621679161570 FTInt2 FTInt2 = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) NilSym0 
Compare_6989586621679161570 FTInt4 FTInt4 = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) NilSym0 
Compare_6989586621679161570 FTInt8 FTInt8 = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) NilSym0 
Compare_6989586621679161570 FTInt16 FTInt16 = Apply (Apply (Apply FoldlSym0 ThenCmpSym0) EQSym0) NilSym0 
Compare_6989586621679161570 FTInt1 FTInt2 = LTSym0 
Compare_6989586621679161570 FTInt1 FTInt4 = LTSym0 
Compare_6989586621679161570 FTInt1 FTInt8 = LTSym0 
Compare_6989586621679161570 FTInt1 FTInt16 = LTSym0 
Compare_6989586621679161570 FTInt2 FTInt1 = GTSym0 
Compare_6989586621679161570 FTInt2 FTInt4 = LTSym0 
Compare_6989586621679161570 FTInt2 FTInt8 = LTSym0 
Compare_6989586621679161570 FTInt2 FTInt16 = LTSym0 
Compare_6989586621679161570 FTInt4 FTInt1 = GTSym0 
Compare_6989586621679161570 FTInt4 FTInt2 = GTSym0 
Compare_6989586621679161570 FTInt4 FTInt8 = LTSym0 
Compare_6989586621679161570 FTInt4 FTInt16 = LTSym0 
Compare_6989586621679161570 FTInt8 FTInt1 = GTSym0 
Compare_6989586621679161570 FTInt8 FTInt2 = GTSym0 
Compare_6989586621679161570 FTInt8 FTInt4 = GTSym0 
Compare_6989586621679161570 FTInt8 FTInt16 = LTSym0 
Compare_6989586621679161570 FTInt16 FTInt1 = GTSym0 
Compare_6989586621679161570 FTInt16 FTInt2 = GTSym0 
Compare_6989586621679161570 FTInt16 FTInt4 = GTSym0 
Compare_6989586621679161570 FTInt16 FTInt8 = GTSym0 

type family Compare_6989586621679161570Sym2 (a6989586621679161575 :: FTInt) (a6989586621679161576 :: FTInt) :: Ordering where ... Source #

Equations

Compare_6989586621679161570Sym2 a6989586621679161575 a6989586621679161576 = Compare_6989586621679161570 a6989586621679161575 a6989586621679161576 

data Compare_6989586621679161570Sym1 (a6989586621679161575 :: FTInt) :: (~>) FTInt Ordering where Source #

Constructors

Compare_6989586621679161570Sym1KindInference :: SameKind (Apply (Compare_6989586621679161570Sym1 a6989586621679161575) arg) (Compare_6989586621679161570Sym2 a6989586621679161575 arg) => Compare_6989586621679161570Sym1 a6989586621679161575 a6989586621679161576 

Instances

Instances details
SuppressUnusedWarnings (Compare_6989586621679161570Sym1 a6989586621679161575 :: TyFun FTInt Ordering -> Type) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (Compare_6989586621679161570Sym1 a6989586621679161575 :: TyFun FTInt Ordering -> Type) (a6989586621679161576 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (Compare_6989586621679161570Sym1 a6989586621679161575 :: TyFun FTInt Ordering -> Type) (a6989586621679161576 :: FTInt) = Compare_6989586621679161570 a6989586621679161575 a6989586621679161576

type family ShowsPrec_6989586621679161580 (a :: Natural) (a :: FTInt) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrec_6989586621679161580 _ FTInt1 a_6989586621679161582 = Apply (Apply ShowStringSym0 "FTInt1") a_6989586621679161582 
ShowsPrec_6989586621679161580 _ FTInt2 a_6989586621679161584 = Apply (Apply ShowStringSym0 "FTInt2") a_6989586621679161584 
ShowsPrec_6989586621679161580 _ FTInt4 a_6989586621679161586 = Apply (Apply ShowStringSym0 "FTInt4") a_6989586621679161586 
ShowsPrec_6989586621679161580 _ FTInt8 a_6989586621679161588 = Apply (Apply ShowStringSym0 "FTInt8") a_6989586621679161588 
ShowsPrec_6989586621679161580 _ FTInt16 a_6989586621679161590 = Apply (Apply ShowStringSym0 "FTInt16") a_6989586621679161590 

type family ShowsPrec_6989586621679161580Sym3 (a6989586621679161596 :: Natural) (a6989586621679161597 :: FTInt) (a6989586621679161598 :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrec_6989586621679161580Sym3 a6989586621679161596 a6989586621679161597 a6989586621679161598 = ShowsPrec_6989586621679161580 a6989586621679161596 a6989586621679161597 a6989586621679161598 

data ShowsPrec_6989586621679161580Sym2 (a6989586621679161596 :: Natural) (a6989586621679161597 :: FTInt) :: (~>) Symbol Symbol where Source #

Constructors

ShowsPrec_6989586621679161580Sym2KindInference :: SameKind (Apply (ShowsPrec_6989586621679161580Sym2 a6989586621679161596 a6989586621679161597) arg) (ShowsPrec_6989586621679161580Sym3 a6989586621679161596 a6989586621679161597 arg) => ShowsPrec_6989586621679161580Sym2 a6989586621679161596 a6989586621679161597 a6989586621679161598 

Instances

Instances details
SuppressUnusedWarnings (ShowsPrec_6989586621679161580Sym2 a6989586621679161596 a6989586621679161597 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (ShowsPrec_6989586621679161580Sym2 a6989586621679161596 a6989586621679161597 :: TyFun Symbol Symbol -> Type) (a6989586621679161598 :: Symbol) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (ShowsPrec_6989586621679161580Sym2 a6989586621679161596 a6989586621679161597 :: TyFun Symbol Symbol -> Type) (a6989586621679161598 :: Symbol) = ShowsPrec_6989586621679161580 a6989586621679161596 a6989586621679161597 a6989586621679161598

data ShowsPrec_6989586621679161580Sym1 (a6989586621679161596 :: Natural) :: (~>) FTInt ((~>) Symbol Symbol) where Source #

Constructors

ShowsPrec_6989586621679161580Sym1KindInference :: SameKind (Apply (ShowsPrec_6989586621679161580Sym1 a6989586621679161596) arg) (ShowsPrec_6989586621679161580Sym2 a6989586621679161596 arg) => ShowsPrec_6989586621679161580Sym1 a6989586621679161596 a6989586621679161597 

Instances

Instances details
SuppressUnusedWarnings (ShowsPrec_6989586621679161580Sym1 a6989586621679161596 :: TyFun FTInt (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (ShowsPrec_6989586621679161580Sym1 a6989586621679161596 :: TyFun FTInt (Symbol ~> Symbol) -> Type) (a6989586621679161597 :: FTInt) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

type Apply (ShowsPrec_6989586621679161580Sym1 a6989586621679161596 :: TyFun FTInt (Symbol ~> Symbol) -> Type) (a6989586621679161597 :: FTInt) = ShowsPrec_6989586621679161580Sym2 a6989586621679161596 a6989586621679161597

data SFTInt :: FTInt -> Type where Source #

Instances

Instances details
TestCoercion SFTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

testCoercion :: forall (a :: k) (b :: k). SFTInt a -> SFTInt b -> Maybe (Coercion a b) #

TestEquality SFTInt Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

testEquality :: forall (a :: k) (b :: k). SFTInt a -> SFTInt b -> Maybe (a :~: b) #

Show (SFTInt z) Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Scalar.Int

Methods

showsPrec :: Int -> SFTInt z -> ShowS #

show :: SFTInt z -> String #

showList :: [SFTInt z] -> ShowS #

type family FTIntCombine k1 k2 where ... Source #

Get the output type from combining two integer values of arbitrary kinds (for example, adding an INTEGER(1) and an INTEGER(4)).

TODO is this OK?? the k k = k equation at top???

type family FTIntMax k where ... Source #

max k = 2^(8k-1) - 1

Equations

FTIntMax 'FTInt1 = (2 ^ ((8 * 1) - 1)) - 1 
FTIntMax 'FTInt2 = (2 ^ ((8 * 2) - 1)) - 1 
FTIntMax 'FTInt4 = (2 ^ ((8 * 4) - 1)) - 1 
FTIntMax 'FTInt8 = (2 ^ ((8 * 8) - 1)) - 1 
FTIntMax 'FTInt16 = (2 ^ ((8 * 16) - 1)) - 1 

type family FTIntMin k where ... Source #

min k = - (2^(8k-1)) (make sure you negate when reifying etc!)

Equations

FTIntMin 'FTInt1 = 2 ^ ((8 * 1) - 1) 
FTIntMin 'FTInt2 = 2 ^ ((8 * 2) - 1) 
FTIntMin 'FTInt4 = 2 ^ ((8 * 4) - 1) 
FTIntMin 'FTInt8 = 2 ^ ((8 * 8) - 1) 
FTIntMin 'FTInt16 = 2 ^ ((8 * 16) - 1)