fluid-idl-0.0.1: Fluid | The Programmatic IDL

Safe HaskellNone
LanguageHaskell2010

Fluid.Types

Documentation

newtype Major Source #

Constructors

Major Int 

Instances

Enum Major Source # 
Eq Major Source # 

Methods

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

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

Integral Major Source # 
Num Major Source # 
Ord Major Source # 

Methods

compare :: Major -> Major -> Ordering #

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

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

(>) :: Major -> Major -> Bool #

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

max :: Major -> Major -> Major #

min :: Major -> Major -> Major #

Real Major Source # 

Methods

toRational :: Major -> Rational #

Show Major Source # 

Methods

showsPrec :: Int -> Major -> ShowS #

show :: Major -> String #

showList :: [Major] -> ShowS #

Generic Major Source # 

Associated Types

type Rep Major :: * -> * #

Methods

from :: Major -> Rep Major x #

to :: Rep Major x -> Major #

ToJSON Major Source # 
FromJSON Major Source # 
type Rep Major Source # 
type Rep Major = D1 (MetaData "Major" "Fluid.Types" "fluid-idl-0.0.1-IRQIjxVZhGMH5OstGCnN5O" True) (C1 (MetaCons "Major" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype Minor Source #

Constructors

Minor Int 

Instances

Enum Minor Source # 
Eq Minor Source # 

Methods

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

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

Integral Minor Source # 
Num Minor Source # 
Ord Minor Source # 

Methods

compare :: Minor -> Minor -> Ordering #

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

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

(>) :: Minor -> Minor -> Bool #

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

max :: Minor -> Minor -> Minor #

min :: Minor -> Minor -> Minor #

Real Minor Source # 

Methods

toRational :: Minor -> Rational #

Show Minor Source # 

Methods

showsPrec :: Int -> Minor -> ShowS #

show :: Minor -> String #

showList :: [Minor] -> ShowS #

Generic Minor Source # 

Associated Types

type Rep Minor :: * -> * #

Methods

from :: Minor -> Rep Minor x #

to :: Rep Minor x -> Minor #

ToJSON Minor Source # 
FromJSON Minor Source # 
type Rep Minor Source # 
type Rep Minor = D1 (MetaData "Minor" "Fluid.Types" "fluid-idl-0.0.1-IRQIjxVZhGMH5OstGCnN5O" True) (C1 (MetaCons "Minor" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data Pull Source #

Constructors

Pull Text Text Text Int 

Instances

Eq Pull Source # 

Methods

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

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

Show Pull Source # 

Methods

showsPrec :: Int -> Pull -> ShowS #

show :: Pull -> String #

showList :: [Pull] -> ShowS #

data Hooks m meta meta' Source #

Constructors

Hooks (meta -> m meta') (meta' -> m Limits) 

defHooks :: Monad m => Hooks m meta meta Source #

class HasType a where Source #

Minimal complete definition

getType

Methods

getType :: Proxy a -> Type Source #

Instances

HasType Bool Source # 

Methods

getType :: Proxy * Bool -> Type Source #

HasType Double Source # 
HasType Float Source # 
HasType Int8 Source # 

Methods

getType :: Proxy * Int8 -> Type Source #

HasType Int16 Source # 
HasType Int32 Source # 
HasType Int64 Source # 
HasType Word8 Source # 
HasType Word16 Source # 
HasType Word32 Source # 
HasType Word64 Source # 
HasType () Source # 

Methods

getType :: Proxy * () -> Type Source #

HasType Text Source # 

Methods

getType :: Proxy * Text -> Type Source #

HasType a => HasType [a] Source # 

Methods

getType :: Proxy * [a] -> Type Source #

HasType a => HasType (Maybe a) Source # 

Methods

getType :: Proxy * (Maybe a) -> Type Source #

(HasType t1, HasType t2, HasType t3) => HasType (Fn ((Expr t1, Expr t2) -> t3)) Source # 

Methods

getType :: Proxy * (Fn ((Expr t1, Expr t2) -> t3)) -> Type Source #

(HasType t1, HasType t2) => HasType (Fn (Expr t1 -> t2)) Source # 

Methods

getType :: Proxy * (Fn (Expr t1 -> t2)) -> Type Source #

HasType a => HasType (Expr a) Source # 

Methods

getType :: Proxy * (Expr a) -> Type Source #

(HasType e, HasType a) => HasType (Either e a) Source # 

Methods

getType :: Proxy * (Either e a) -> Type Source #

(HasType t1, HasType t2) => HasType (t1, t2) Source # 

Methods

getType :: Proxy * (t1, t2) -> Type Source #

(HasType t1, HasType t2, HasType t3) => HasType (t1, t2, t3) Source # 

Methods

getType :: Proxy * (t1, t2, t3) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4) => HasType (t1, t2, t3, t4) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5) => HasType (t1, t2, t3, t4, t5) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6) => HasType (t1, t2, t3, t4, t5, t6) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7) => HasType (t1, t2, t3, t4, t5, t6, t7) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8) => HasType (t1, t2, t3, t4, t5, t6, t7, t8) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22, HasType t23) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22, HasType t23, HasType t24) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22, HasType t23, HasType t24, HasType t25) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22, HasType t23, HasType t24, HasType t25, HasType t26) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22, HasType t23, HasType t24, HasType t25, HasType t26, HasType t27) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22, HasType t23, HasType t24, HasType t25, HasType t26, HasType t27, HasType t28) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27, t28) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27, t28) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22, HasType t23, HasType t24, HasType t25, HasType t26, HasType t27, HasType t28, HasType t29) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27, t28, t29) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27, t28, t29) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22, HasType t23, HasType t24, HasType t25, HasType t26, HasType t27, HasType t28, HasType t29, HasType t30) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27, t28, t29, t30) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27, t28, t29, t30) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22, HasType t23, HasType t24, HasType t25, HasType t26, HasType t27, HasType t28, HasType t29, HasType t30, HasType t31) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27, t28, t29, t30, t31) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27, t28, t29, t30, t31) -> Type Source #

(HasType t1, HasType t2, HasType t3, HasType t4, HasType t5, HasType t6, HasType t7, HasType t8, HasType t9, HasType t10, HasType t11, HasType t12, HasType t13, HasType t14, HasType t15, HasType t16, HasType t17, HasType t18, HasType t19, HasType t20, HasType t21, HasType t22, HasType t23, HasType t24, HasType t25, HasType t26, HasType t27, HasType t28, HasType t29, HasType t30, HasType t31, HasType t32) => HasType (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32) Source # 

Methods

getType :: Proxy * (t1, t2, t3, t4, t5, t6, t7, t8, t9, t10, t11, t12, t13, t14, t15, t16, t17, t18, t19, t20, t21, t22, t23, t24, t25, t26, t27, t28, t29, t30, t31, t32) -> Type Source #