express-1.0.2: Dynamically-typed expressions involving function application and variables.
Copyright(c) 2016-2021 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Express.Utils.Typeable

Description

This module is part of Express.

Utilities to manipulate TypeReps (of Typeable values).

Synopsis

Documentation

tyArity :: TypeRep -> Int Source #

Returns the functional arity of the given TypeRep.

> tyArity $ typeOf (undefined :: Int)
0
> tyArity $ typeOf (undefined :: Int -> Int)
1
> tyArity $ typeOf (undefined :: (Int,Int))
0

unFunTy :: TypeRep -> (TypeRep, TypeRep) Source #

Deconstructs a functional TypeRep into a pair of TypeReps.

> unFunTy $ typeOf (undefined :: Int -> Char -> Bool)
(Int,Char -> Bool)

This function raises an error on non-functional types.

(cf. argumentTy and resultTy)

isFunTy :: TypeRep -> Bool Source #

Returns whether a TypeRep is functional.

> isFunTy $ typeOf (undefined :: Int -> Int)
True
> isFunTy $ typeOf (undefined :: Int)
False

argumentTy :: TypeRep -> TypeRep Source #

Returns the argument TypeRep of a given functional TypeRep.

argumentTy $ typeOf (undefined :: Int -> Char)
Int

This function raises an error on non-functional types.

(cf. resultTy)

resultTy :: TypeRep -> TypeRep Source #

Returns the result TypeRep of a given functional TypeRep.

> resultTy $ typeOf (undefined :: Int -> Char)
Char
> resultTy $ typeOf (undefined :: Int -> Char -> Bool)
Char -> Bool

This function raises an error on non-functional types.

(cf. argumentTy and finalResultTy)

finalResultTy :: TypeRep -> TypeRep Source #

Returns the ultimate result type of the given TypeRep.

> finalResultTy (typeOf (undefined :: Int))
Int
> finalResultTy (typeOf (undefined :: Int -> Char))
Char
> finalResultTy (typeOf (undefined :: Int -> Char -> Bool))
Bool

boolTy :: TypeRep Source #

The Bool type encoded as a TypeRep.

intTy :: TypeRep Source #

The Int type encoded as a TypeRep.

orderingTy :: TypeRep Source #

The Ordering type encoded as a TypeRep.

mkComparisonTy :: TypeRep -> TypeRep Source #

Constructs a comparison type ( a -> a -> Bool ) from the given argument type.

> mkComparisonTy $ typeOf (undefined :: Int)
Int -> Int -> Bool
> mkComparisonTy $ typeOf (undefined :: ())
() -> () -> Bool

mkCompareTy :: TypeRep -> TypeRep Source #

Constructs a "compare" type ( a -> a -> Ordering ) from the given argument type.

> mkCompareTy $ typeOf (undefined :: Int)
Int -> Int -> Ordering
> mkCompareTy $ typeOf (undefined :: ())
() -> () -> Ordering

funTyCon :: TyCon Source #

The function type constructor as a TyCon

compareTy :: TypeRep -> TypeRep -> Ordering Source #

Compares two TypeReps.

Different versions of Typeable/GHC provide different orderings for TypeReps. The following is a version independent ordering, with the following properties:

  • functional types with more arguments are larger;
  • type constructors with more arguments are larger.
> typeOf (undefined :: Int -> Int) `compareTy` typeOf (undefined :: () -> () -> ())
LT
> typeOf (undefined :: Int) `compareTy` typeOf (undefined :: ())
GT

elementTy :: TypeRep -> TypeRep Source #

This function returns the type of the element of a list. It will throw an error when not given the list type.

> > elementTy $ typeOf (undefined :: [Int])
Int
> > elementTy $ typeOf (undefined :: [[Int]])
[Int]
> > elementTy $ typeOf (undefined :: [Bool])
Bool
> > elementTy $ typeOf (undefined :: Bool)
*** Exception: error (elementTy): `Bool' is not a list type

typesIn :: TypeRep -> [TypeRep] Source #

O(n). Return all sub types of a given type including itself.

> typesIn $ typeOf (undefined :: Int)
[Int]
> typesIn $ typeOf (undefined :: Bool)
[Bool]
> typesIn $ typeOf (undefined :: [Int])
[ Int
, [Int]
]
> typesIn $ typeOf (undefined :: Int -> Int -> Int)
[ Int
, Int -> Int
, Int -> Int -> Int
]
> typesIn $ typeOf (undefined :: Int -> [Int] -> [Int])
[ Int
, [Int]
, [Int] -> [Int]
, Int -> [Int] -> [Int]
]
> typesIn $ typeOf (undefined :: Maybe Bool)
[ Bool
, Maybe Bool
]

typesInList :: [TypeRep] -> [TypeRep] Source #

Returns types and subtypes from the given list of TypeReps.

> typesInList [typeOf (undefined :: () -> Int), typeOf (undefined :: String -> String -> Bool)]
[(),Bool,Char,Int,[Char],() -> Int,[Char] -> Bool,[Char] -> [Char] -> Bool]
> typesInList [typeOf (undefined :: (Char,Int))]
[Char,Int,(Char,Int)]

countListTy :: TypeRep -> Int Source #

Return the number of outer list nestings in a TypeRep

> countListTy $ typeOf (undefined :: Int)
0
> countListTy $ typeOf (undefined :: [Bool])
1
> countListTy $ typeOf (undefined :: [[()]])
2
> countListTy $ typeOf (undefined :: String)
1
> countListTy $ typeOf (undefined :: ([Int],[Bool]))
0

(->::) :: TypeRep -> TypeRep -> TypeRep infixr 9 Source #

An infix alias for mkFunTy. It is right associative.