hat-2.9.4: The Haskell tracer, generating and viewing Haskell execution traces

Safe HaskellNone
LanguageHaskell98

Hat.Prelude

Synopsis

Documentation

g_filter :: RefSrcPos -> RefExp -> R (Fun Bool (Fun (Fun (List a) (List a)) (Fun (List a) (List a)))) Source #

h_filter :: R Bool -> R (Fun (List a) (List a)) -> R (List a) -> RefExp -> R (List a) Source #

g_foldr :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun b b)) (Fun (List a) (Fun b b))) Source #

h_foldr :: R (Fun a (Fun b b)) -> R (List a) -> R b -> RefExp -> R b Source #

gmap :: RefSrcPos -> RefExp -> R (Fun (Fun a b) (Fun (List a) (List b))) Source #

hmap :: R (Fun a b) -> R (List a) -> RefExp -> R (List b) Source #

(!++) :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List a) (List a))) Source #

(*++) :: R (List a) -> R (List a) -> RefExp -> R (List a) Source #

gfilter :: RefSrcPos -> RefExp -> R (Fun (Fun a Bool) (Fun (List a) (List a))) Source #

hfilter :: R (Fun a Bool) -> R (List a) -> RefExp -> R (List a) Source #

gconcat :: RefSrcPos -> RefExp -> R (Fun (List (List a)) (List a)) Source #

hconcat :: R (List (List a)) -> RefExp -> R (List a) Source #

ghead :: RefSrcPos -> RefExp -> R (Fun (List a) a) Source #

hhead :: R (List a) -> RefExp -> R a Source #

glast :: RefSrcPos -> RefExp -> R (Fun (List a) a) Source #

hlast :: R (List a) -> RefExp -> R a Source #

gtail :: RefSrcPos -> RefExp -> R (Fun (List a) (List a)) Source #

htail :: R (List a) -> RefExp -> R (List a) Source #

ginit :: RefSrcPos -> RefExp -> R (Fun (List a) (List a)) Source #

hinit :: R (List a) -> RefExp -> R (List a) Source #

hnull :: R (List a) -> RefExp -> R Bool Source #

hlength :: R (List a) -> RefExp -> R Int Source #

(!!!) :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun Int a)) Source #

(*!!) :: R (List a) -> R Int -> RefExp -> R a Source #

gfoldl :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun b a)) (Fun a (Fun (List b) a))) Source #

hfoldl :: R (Fun a (Fun b a)) -> R a -> R (List b) -> RefExp -> R a Source #

gfoldl1 :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun a a)) (Fun (List a) a)) Source #

hfoldl1 :: R (Fun a (Fun a a)) -> R (List a) -> RefExp -> R a Source #

gscanl :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun b a)) (Fun a (Fun (List b) (List a)))) Source #

hscanl :: R (Fun a (Fun b a)) -> R a -> R (List b) -> RefExp -> R (List a) Source #

gscanl1 :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun a a)) (Fun (List a) (List a))) Source #

hscanl1 :: R (Fun a (Fun a a)) -> R (List a) -> RefExp -> R (List a) Source #

gfoldr :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun b b)) (Fun b (Fun (List a) b))) Source #

hfoldr :: R (Fun a (Fun b b)) -> R b -> R (List a) -> RefExp -> R b Source #

gfoldr1 :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun a a)) (Fun (List a) a)) Source #

hfoldr1 :: R (Fun a (Fun a a)) -> R (List a) -> RefExp -> R a Source #

gscanr :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun b b)) (Fun b (Fun (List a) (List b)))) Source #

hscanr :: R (Fun a (Fun b b)) -> R b -> R (List a) -> RefExp -> R (List b) Source #

gscanr1 :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun a a)) (Fun (List a) (List a))) Source #

hscanr1 :: R (Fun a (Fun a a)) -> R (List a) -> RefExp -> R (List a) Source #

giterate :: RefSrcPos -> RefExp -> R (Fun (Fun a a) (Fun a (List a))) Source #

hiterate :: R (Fun a a) -> R a -> RefExp -> R (List a) Source #

hrepeat :: R a -> RefExp -> R (List a) Source #

hreplicate :: R Int -> R a -> RefExp -> R (List a) Source #

gcycle :: RefSrcPos -> RefExp -> R (Fun (List a) (List a)) Source #

hcycle :: R (List a) -> RefExp -> R (List a) Source #

gtake :: RefSrcPos -> RefExp -> R (Fun Int (Fun (List a) (List a))) Source #

htake :: R Int -> R (List a) -> RefExp -> R (List a) Source #

gdrop :: RefSrcPos -> RefExp -> R (Fun Int (Fun (List a) (List a))) Source #

hdrop :: R Int -> R (List a) -> RefExp -> R (List a) Source #

gsplitAt :: RefSrcPos -> RefExp -> R (Fun Int (Fun (List a) (Tuple2 (List a) (List a)))) Source #

hsplitAt :: R Int -> R (List a) -> RefExp -> R (Tuple2 (List a) (List a)) Source #

gtakeWhile :: RefSrcPos -> RefExp -> R (Fun (Fun a Bool) (Fun (List a) (List a))) Source #

htakeWhile :: R (Fun a Bool) -> R (List a) -> RefExp -> R (List a) Source #

gdropWhile :: RefSrcPos -> RefExp -> R (Fun (Fun a Bool) (Fun (List a) (List a))) Source #

hdropWhile :: R (Fun a Bool) -> R (List a) -> RefExp -> R (List a) Source #

gspan :: RefSrcPos -> RefExp -> R (Fun (Fun a Bool) (Fun (List a) (Tuple2 (List a) (List a)))) Source #

hspan :: R (Fun a Bool) -> R (List a) -> RefExp -> R (Tuple2 (List a) (List a)) Source #

gbreak :: RefSrcPos -> RefExp -> R (Fun (Fun a Bool) (Fun (List a) (Tuple2 (List a) (List a)))) Source #

hbreak :: R (Fun a Bool) -> RefExp -> R (Fun (List a) (Tuple2 (List a) (List a))) Source #

gany :: RefSrcPos -> RefExp -> R (Fun (Fun a Bool) (Fun (List a) Bool)) Source #

hany :: R (Fun a Bool) -> RefExp -> R (Fun (List a) Bool) Source #

gall :: RefSrcPos -> RefExp -> R (Fun (Fun a Bool) (Fun (List a) Bool)) Source #

hall :: R (Fun a Bool) -> RefExp -> R (Fun (List a) Bool) Source #

gelem :: Eq a => RefSrcPos -> RefExp -> R (Fun a (Fun (List a) Bool)) Source #

helem :: Eq a => R a -> RefExp -> R (Fun (List a) Bool) Source #

gnotElem :: Eq a => RefSrcPos -> RefExp -> R (Fun a (Fun (List a) Bool)) Source #

hnotElem :: Eq a => R a -> RefExp -> R (Fun (List a) Bool) Source #

glookup :: Eq a => RefSrcPos -> RefExp -> R (Fun a (Fun (List (Tuple2 a b)) (Maybe b))) Source #

hlookup :: Eq a => R a -> R (List (Tuple2 a b)) -> RefExp -> R (Maybe b) Source #

gsum :: Num a => RefSrcPos -> RefExp -> R (Fun (List a) a) Source #

gproduct :: Num a => RefSrcPos -> RefExp -> R (Fun (List a) a) Source #

gmaximum :: Ord a => RefSrcPos -> RefExp -> R (Fun (List a) a) Source #

hmaximum :: Ord a => R (List a) -> RefExp -> R a Source #

gminimum :: Ord a => RefSrcPos -> RefExp -> R (Fun (List a) a) Source #

hminimum :: Ord a => R (List a) -> RefExp -> R a Source #

gconcatMap :: RefSrcPos -> RefExp -> R (Fun (Fun a (List b)) (Fun (List a) (List b))) Source #

hconcatMap :: R (Fun a (List b)) -> RefExp -> R (Fun (List a) (List b)) Source #

gzip :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List b) (List (Tuple2 a b)))) Source #

gzip3 :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List b) (Fun (List c) (List (Tuple3 a b c))))) Source #

gzipWith :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun b c)) (Fun (List a) (Fun (List b) (List c)))) Source #

hzipWith :: R (Fun a (Fun b c)) -> R (List a) -> R (List b) -> RefExp -> R (List c) Source #

gzipWith3 :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun b (Fun c d))) (Fun (List a) (Fun (List b) (Fun (List c) (List d))))) Source #

hzipWith3 :: R (Fun a (Fun b (Fun c d))) -> R (List a) -> R (List b) -> R (List c) -> RefExp -> R (List d) Source #

gunzip :: RefSrcPos -> RefExp -> R (Fun (List (Tuple2 a b)) (Tuple2 (List a) (List b))) Source #

gunzip3 :: RefSrcPos -> RefExp -> R (Fun (List (Tuple3 a b c)) (Tuple3 (List a) (List b) (List c))) Source #

class Read a where Source #

Minimal complete definition

greadsPrec

Instances

Read Bool Source # 
Read Char Source # 
Read Double Source # 
Read Float Source # 
Read Int Source # 
Read Integer Source # 
Read Tuple0 Source # 
Read Ordering Source # 
Read SeekMode Source # 
Read BufferMode Source # 
Read IOMode Source # 
Read ExitCode Source # 
Read TimeDiff Source # 
Read CalendarTime Source # 
Read Day Source # 
Read Month Source # 
Read GeneralCategory Source # 
Read a => Read (List a) Source # 
(Read a, Integral a) => Read (Ratio a) Source # 
Read a => Read (Maybe a) Source # 
Read a => Read (Complex a) Source # 
(Read a, Read b) => Read (Tuple2 a b) Source # 
(Read a, Read b) => Read (Either a b) Source # 
(Ix a, Read a, Read b) => Read (Array a b) Source # 
(Read a, Read b, Read c) => Read (Tuple3 a b c) Source # 
(Read a, Read b, Read c, Read d) => Read (Tuple4 a b c d) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple4 a b c d))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple4 a b c d))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple4 a b c d))) Source #

sreadList :: R (ReadS (List (Tuple4 a b c d))) Source #

(Read a, Read b, Read c, Read d, Read e) => Read (Tuple5 a b c d e) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple5 a b c d e))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple5 a b c d e))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple5 a b c d e))) Source #

sreadList :: R (ReadS (List (Tuple5 a b c d e))) Source #

(Read a, Read b, Read c, Read d, Read e, Read f) => Read (Tuple6 a b c d e f) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple6 a b c d e f))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple6 a b c d e f))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple6 a b c d e f))) Source #

sreadList :: R (ReadS (List (Tuple6 a b c d e f))) Source #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g) => Read (Tuple7 a b c d e f g) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple7 a b c d e f g))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple7 a b c d e f g))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple7 a b c d e f g))) Source #

sreadList :: R (ReadS (List (Tuple7 a b c d e f g))) Source #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) => Read (Tuple8 a b c d e f g h) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple8 a b c d e f g h))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple8 a b c d e f g h))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple8 a b c d e f g h))) Source #

sreadList :: R (ReadS (List (Tuple8 a b c d e f g h))) Source #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i) => Read (Tuple9 a b c d e f g h i) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple9 a b c d e f g h i))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple9 a b c d e f g h i))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple9 a b c d e f g h i))) Source #

sreadList :: R (ReadS (List (Tuple9 a b c d e f g h i))) Source #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j) => Read (Tuple10 a b c d e f g h i j) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple10 a b c d e f g h i j))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple10 a b c d e f g h i j))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple10 a b c d e f g h i j))) Source #

sreadList :: R (ReadS (List (Tuple10 a b c d e f g h i j))) Source #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k) => Read (Tuple11 a b c d e f g h i j k) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple11 a b c d e f g h i j k))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple11 a b c d e f g h i j k))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple11 a b c d e f g h i j k))) Source #

sreadList :: R (ReadS (List (Tuple11 a b c d e f g h i j k))) Source #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l) => Read (Tuple12 a b c d e f g h i j k l) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple12 a b c d e f g h i j k l))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple12 a b c d e f g h i j k l))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple12 a b c d e f g h i j k l))) Source #

sreadList :: R (ReadS (List (Tuple12 a b c d e f g h i j k l))) Source #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m) => Read (Tuple13 a b c d e f g h i j k l m) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple13 a b c d e f g h i j k l m))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple13 a b c d e f g h i j k l m))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple13 a b c d e f g h i j k l m))) Source #

sreadList :: R (ReadS (List (Tuple13 a b c d e f g h i j k l m))) Source #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n) => Read (Tuple14 a b c d e f g h i j k l m n) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple14 a b c d e f g h i j k l m n))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple14 a b c d e f g h i j k l m n))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple14 a b c d e f g h i j k l m n))) Source #

sreadList :: R (ReadS (List (Tuple14 a b c d e f g h i j k l m n))) Source #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n, Read o) => Read (Tuple15 a b c d e f g h i j k l m n o) Source # 

Methods

greadsPrec :: RefSrcPos -> RefExp -> R (Fun Int (ReadS (Tuple15 a b c d e f g h i j k l m n o))) Source #

sreadsPrec :: R (Fun Int (ReadS (Tuple15 a b c d e f g h i j k l m n o))) Source #

greadList :: RefSrcPos -> RefExp -> R (ReadS (List (Tuple15 a b c d e f g h i j k l m n o))) Source #

sreadList :: R (ReadS (List (Tuple15 a b c d e f g h i j k l m n o))) Source #

class Show a where Source #

Minimal complete definition

sshowsPrec, sshow, sshowList

Instances

Show Bool Source # 
Show Char Source # 
Show Double Source # 
Show Float Source # 
Show Int Source # 
Show Integer Source # 
Show Tuple0 Source # 
Show Ordering Source # 
Show SeekMode Source # 
Show BufferMode Source # 
Show IOMode Source # 
Show TimeLocale Source # 
Show ExitCode Source # 
Show TimeDiff Source # 
Show CalendarTime Source # 
Show Day Source # 
Show Month Source # 
Show GeneralCategory Source # 
Show a => Show (List a) Source # 
Integral a => Show (Ratio a) Source # 
Show a => Show (Maybe a) Source # 
Show a => Show (Complex a) Source # 
(Show a, Show b) => Show (Tuple2 a b) Source # 
(Show a, Show b) => Show (Either a b) Source # 
(Ix a, Show a, Show b) => Show (Array a b) Source # 
(Show a, Show b, Show c) => Show (Tuple3 a b c) Source # 
(Show a, Show b, Show c, Show d) => Show (Tuple4 a b c d) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple4 a b c d) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple4 a b c d) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple4 a b c d) String) Source #

sshow :: R (Fun (Tuple4 a b c d) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple4 a b c d)) ShowS) Source #

sshowList :: R (Fun (List (Tuple4 a b c d)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e) => Show (Tuple5 a b c d e) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple5 a b c d e) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple5 a b c d e) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple5 a b c d e) String) Source #

sshow :: R (Fun (Tuple5 a b c d e) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple5 a b c d e)) ShowS) Source #

sshowList :: R (Fun (List (Tuple5 a b c d e)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e, Show f) => Show (Tuple6 a b c d e f) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple6 a b c d e f) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple6 a b c d e f) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple6 a b c d e f) String) Source #

sshow :: R (Fun (Tuple6 a b c d e f) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple6 a b c d e f)) ShowS) Source #

sshowList :: R (Fun (List (Tuple6 a b c d e f)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (Tuple7 a b c d e f g) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple7 a b c d e f g) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple7 a b c d e f g) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple7 a b c d e f g) String) Source #

sshow :: R (Fun (Tuple7 a b c d e f g) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple7 a b c d e f g)) ShowS) Source #

sshowList :: R (Fun (List (Tuple7 a b c d e f g)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (Tuple8 a b c d e f g h) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple8 a b c d e f g h) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple8 a b c d e f g h) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple8 a b c d e f g h) String) Source #

sshow :: R (Fun (Tuple8 a b c d e f g h) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple8 a b c d e f g h)) ShowS) Source #

sshowList :: R (Fun (List (Tuple8 a b c d e f g h)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (Tuple9 a b c d e f g h i) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple9 a b c d e f g h i) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple9 a b c d e f g h i) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple9 a b c d e f g h i) String) Source #

sshow :: R (Fun (Tuple9 a b c d e f g h i) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple9 a b c d e f g h i)) ShowS) Source #

sshowList :: R (Fun (List (Tuple9 a b c d e f g h i)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (Tuple10 a b c d e f g h i j) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple10 a b c d e f g h i j) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple10 a b c d e f g h i j) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple10 a b c d e f g h i j) String) Source #

sshow :: R (Fun (Tuple10 a b c d e f g h i j) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple10 a b c d e f g h i j)) ShowS) Source #

sshowList :: R (Fun (List (Tuple10 a b c d e f g h i j)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (Tuple11 a b c d e f g h i j k) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple11 a b c d e f g h i j k) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple11 a b c d e f g h i j k) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple11 a b c d e f g h i j k) String) Source #

sshow :: R (Fun (Tuple11 a b c d e f g h i j k) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple11 a b c d e f g h i j k)) ShowS) Source #

sshowList :: R (Fun (List (Tuple11 a b c d e f g h i j k)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (Tuple12 a b c d e f g h i j k l) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple12 a b c d e f g h i j k l) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple12 a b c d e f g h i j k l) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple12 a b c d e f g h i j k l) String) Source #

sshow :: R (Fun (Tuple12 a b c d e f g h i j k l) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple12 a b c d e f g h i j k l)) ShowS) Source #

sshowList :: R (Fun (List (Tuple12 a b c d e f g h i j k l)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (Tuple13 a b c d e f g h i j k l m) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple13 a b c d e f g h i j k l m) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple13 a b c d e f g h i j k l m) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple13 a b c d e f g h i j k l m) String) Source #

sshow :: R (Fun (Tuple13 a b c d e f g h i j k l m) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple13 a b c d e f g h i j k l m)) ShowS) Source #

sshowList :: R (Fun (List (Tuple13 a b c d e f g h i j k l m)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (Tuple14 a b c d e f g h i j k l m n) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple14 a b c d e f g h i j k l m n) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple14 a b c d e f g h i j k l m n) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple14 a b c d e f g h i j k l m n) String) Source #

sshow :: R (Fun (Tuple14 a b c d e f g h i j k l m n) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple14 a b c d e f g h i j k l m n)) ShowS) Source #

sshowList :: R (Fun (List (Tuple14 a b c d e f g h i j k l m n)) ShowS) Source #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (Tuple15 a b c d e f g h i j k l m n o) Source # 

Methods

gshowsPrec :: RefSrcPos -> RefExp -> R (Fun Int (Fun (Tuple15 a b c d e f g h i j k l m n o) ShowS)) Source #

sshowsPrec :: R (Fun Int (Fun (Tuple15 a b c d e f g h i j k l m n o) ShowS)) Source #

gshow :: RefSrcPos -> RefExp -> R (Fun (Tuple15 a b c d e f g h i j k l m n o) String) Source #

sshow :: R (Fun (Tuple15 a b c d e f g h i j k l m n o) String) Source #

gshowList :: RefSrcPos -> RefExp -> R (Fun (List (Tuple15 a b c d e f g h i j k l m n o)) ShowS) Source #

sshowList :: R (Fun (List (Tuple15 a b c d e f g h i j k l m n o)) ShowS) Source #

hread :: Read a => R String -> RefExp -> R a Source #

hreadParen :: R Bool -> R (ReadS a) -> RefExp -> R (ReadS a) Source #

type IOError = IOException #

The Haskell 2010 type for exceptions in the IO monad. Any I/O operation may raise an IOError instead of returning a result. For a more general type of exception, including also those that arise in pure code, see Exception.

In Haskell 2010, this is an opaque type.

gcatch :: RefSrcPos -> RefExp -> R (Fun (IO a) (Fun (Fun IOError (IO a)) (IO a))) Source #

hcatch :: R (IO b) -> R (Fun IOError (IO b)) -> RefExp -> R (IO b) Source #

hprint :: Show a => R a -> RefExp -> R (IO Tuple0) Source #

hreadIO :: Read a => R String -> RefExp -> R (IO a) Source #

greadLn :: Read a => RefSrcPos -> RefExp -> R (IO a) Source #

data Bool :: * #

Constructors

False 
True 

Instances

Bounded Bool 
Enum Bool 

Methods

succ :: Bool -> Bool #

pred :: Bool -> Bool #

toEnum :: Int -> Bool #

fromEnum :: Bool -> Int #

enumFrom :: Bool -> [Bool] #

enumFromThen :: Bool -> Bool -> [Bool] #

enumFromTo :: Bool -> Bool -> [Bool] #

enumFromThenTo :: Bool -> Bool -> Bool -> [Bool] #

Eq Bool 

Methods

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

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

Ord Bool 

Methods

compare :: Bool -> Bool -> Ordering #

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

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

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

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

max :: Bool -> Bool -> Bool #

min :: Bool -> Bool -> Bool #

Read Bool 
Show Bool 

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Storable Bool 

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Random Bool 

Methods

randomR :: RandomGen g => (Bool, Bool) -> g -> (Bool, g) #

random :: RandomGen g => g -> (Bool, g) #

randomRs :: RandomGen g => (Bool, Bool) -> g -> [Bool] #

randoms :: RandomGen g => g -> [Bool] #

randomRIO :: (Bool, Bool) -> IO Bool #

randomIO :: IO Bool #

Show Bool Source # 
Read Bool Source # 
Bounded Bool Source # 
Enum Bool Source # 
Ord Bool Source # 
Eq Bool Source # 
Ix Bool Source # 
Random Bool Source # 
SingI Bool False 

Methods

sing :: Sing False a

SingI Bool True 

Methods

sing :: Sing True a

SingKind Bool (KProxy Bool) 

Associated Types

type DemoteRep (KProxy Bool) (kparam :: KProxy (KProxy Bool)) :: *

Methods

fromSing :: Sing (KProxy Bool) a -> DemoteRep (KProxy Bool) kparam

type Rep Bool 
type Rep Bool = D1 (MetaData "Bool" "GHC.Types" "ghc-prim" False) ((:+:) (C1 (MetaCons "False" PrefixI False) U1) (C1 (MetaCons "True" PrefixI False) U1))
data Sing Bool 
data Sing Bool where
type (==) Bool a b 
type (==) Bool a b = EqBool a b
type DemoteRep Bool (KProxy Bool) 
type DemoteRep Bool (KProxy Bool) = Bool

data Maybe a Source #

Constructors

Nothing 
Just (R a) 

Instances

Monad Maybe Source # 

Methods

(!>>=) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Fun a (Maybe b)) (Maybe b))) Source #

(|>>=) :: R (Fun (Maybe a) (Fun (Fun a (Maybe b)) (Maybe b))) Source #

(!>>) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe b) (Maybe b))) Source #

(|>>) :: R (Fun (Maybe a) (Fun (Maybe b) (Maybe b))) Source #

greturn :: RefSrcPos -> RefExp -> R (Fun a (Maybe a)) Source #

sreturn :: R (Fun a (Maybe a)) Source #

gfail :: RefSrcPos -> RefExp -> R (Fun String (Maybe a)) Source #

sfail :: R (Fun String (Maybe a)) Source #

Functor Maybe Source # 

Methods

gfmap :: RefSrcPos -> RefExp -> R (Fun (Fun a b) (Fun (Maybe a) (Maybe b))) Source #

sfmap :: R (Fun (Fun a b) (Fun (Maybe a) (Maybe b))) Source #

MonadPlus Maybe Source # 

Methods

gmzero :: RefSrcPos -> RefExp -> R (Maybe a) Source #

smzero :: R (Maybe a) Source #

gmplus :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) (Maybe a))) Source #

smplus :: R (Fun (Maybe a) (Fun (Maybe a) (Maybe a))) Source #

WrapVal (Maybe a) Source # 

Methods

wrapVal :: RefSrcPos -> Maybe a -> RefExp -> R (Maybe a) Source #

Show a => Show (Maybe a) Source # 
Read a => Read (Maybe a) Source # 
Ord a => Ord (Maybe a) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Ordering)) Source #

scompare :: R (Fun (Maybe a) (Fun (Maybe a) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|<) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|<=) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|>=) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|>) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) (Maybe a))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) (Maybe a))) Source #

smax :: R (Fun (Maybe a) (Fun (Maybe a) (Maybe a))) Source #

smin :: R (Fun (Maybe a) (Fun (Maybe a) (Maybe a))) Source #

Eq a => Eq (Maybe a) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|==) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|/=) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

data Either a b Source #

Constructors

Left (R a) 
Right (R b) 

Instances

WrapVal (Either a b) Source # 

Methods

wrapVal :: RefSrcPos -> Either a b -> RefExp -> R (Either a b) Source #

(Show a, Show b) => Show (Either a b) Source # 
(Read a, Read b) => Read (Either a b) Source # 
(Ord a, Ord b) => Ord (Either a b) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Ordering)) Source #

scompare :: R (Fun (Either a b) (Fun (Either a b) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|<) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|<=) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|>=) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|>) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) (Either a b))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) (Either a b))) Source #

smax :: R (Fun (Either a b) (Fun (Either a b) (Either a b))) Source #

smin :: R (Fun (Either a b) (Fun (Either a b) (Either a b))) Source #

(Eq a, Eq b) => Eq (Either a b) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|==) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|/=) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

data Ordering Source #

Constructors

LT 
EQ 
GT 

Instances

WrapVal Ordering Source # 
Show Ordering Source # 
Read Ordering Source # 
Bounded Ordering Source # 
Enum Ordering Source # 
Ord Ordering Source # 
Eq Ordering Source # 
Ix Ordering Source # 

data Char :: * #

The character type Char is an enumeration whose values represent Unicode (or equivalently ISO/IEC 10646) characters (see http://www.unicode.org/ for details). This set extends the ISO 8859-1 (Latin-1) character set (the first 256 characters), which is itself an extension of the ASCII character set (the first 128 characters). A character literal in Haskell has type Char.

To convert a Char to or from the corresponding Int value defined by Unicode, use toEnum and fromEnum from the Enum class respectively (or equivalently ord and chr).

Instances

Bounded Char 
Enum Char 

Methods

succ :: Char -> Char #

pred :: Char -> Char #

toEnum :: Int -> Char #

fromEnum :: Char -> Int #

enumFrom :: Char -> [Char] #

enumFromThen :: Char -> Char -> [Char] #

enumFromTo :: Char -> Char -> [Char] #

enumFromThenTo :: Char -> Char -> Char -> [Char] #

Eq Char 

Methods

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

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

Ord Char 

Methods

compare :: Char -> Char -> Ordering #

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

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

(>) :: Char -> Char -> Bool #

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

max :: Char -> Char -> Char #

min :: Char -> Char -> Char #

Read Char 
Show Char 

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Storable Char 

Methods

sizeOf :: Char -> Int #

alignment :: Char -> Int #

peekElemOff :: Ptr Char -> Int -> IO Char #

pokeElemOff :: Ptr Char -> Int -> Char -> IO () #

peekByteOff :: Ptr b -> Int -> IO Char #

pokeByteOff :: Ptr b -> Int -> Char -> IO () #

peek :: Ptr Char -> IO Char #

poke :: Ptr Char -> Char -> IO () #

Random Char 

Methods

randomR :: RandomGen g => (Char, Char) -> g -> (Char, g) #

random :: RandomGen g => g -> (Char, g) #

randomRs :: RandomGen g => (Char, Char) -> g -> [Char] #

randoms :: RandomGen g => g -> [Char] #

randomRIO :: (Char, Char) -> IO Char #

randomIO :: IO Char #

Show Char Source # 
Read Char Source # 
Bounded Char Source # 
Enum Char Source # 
Ord Char Source # 
Eq Char Source # 
Ix Char Source # 
Random Char Source # 
Functor (URec Char) 

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b #

(<$) :: a -> URec Char b -> URec Char a #

Foldable (URec Char) 

Methods

fold :: Monoid m => URec Char m -> m #

foldMap :: Monoid m => (a -> m) -> URec Char a -> m #

foldr :: (a -> b -> b) -> b -> URec Char a -> b #

foldr' :: (a -> b -> b) -> b -> URec Char a -> b #

foldl :: (b -> a -> b) -> b -> URec Char a -> b #

foldl' :: (b -> a -> b) -> b -> URec Char a -> b #

foldr1 :: (a -> a -> a) -> URec Char a -> a #

foldl1 :: (a -> a -> a) -> URec Char a -> a #

toList :: URec Char a -> [a] #

null :: URec Char a -> Bool #

length :: URec Char a -> Int #

elem :: Eq a => a -> URec Char a -> Bool #

maximum :: Ord a => URec Char a -> a #

minimum :: Ord a => URec Char a -> a #

sum :: Num a => URec Char a -> a #

product :: Num a => URec Char a -> a #

Generic1 (URec Char) 

Associated Types

type Rep1 (URec Char :: * -> *) :: * -> * #

Methods

from1 :: URec Char a -> Rep1 (URec Char) a #

to1 :: Rep1 (URec Char) a -> URec Char a #

Eq (URec Char p) 

Methods

(==) :: URec Char p -> URec Char p -> Bool #

(/=) :: URec Char p -> URec Char p -> Bool #

Ord (URec Char p) 

Methods

compare :: URec Char p -> URec Char p -> Ordering #

(<) :: URec Char p -> URec Char p -> Bool #

(<=) :: URec Char p -> URec Char p -> Bool #

(>) :: URec Char p -> URec Char p -> Bool #

(>=) :: URec Char p -> URec Char p -> Bool #

max :: URec Char p -> URec Char p -> URec Char p #

min :: URec Char p -> URec Char p -> URec Char p #

Show (URec Char p) 

Methods

showsPrec :: Int -> URec Char p -> ShowS #

show :: URec Char p -> String #

showList :: [URec Char p] -> ShowS #

Generic (URec Char p) 

Associated Types

type Rep (URec Char p) :: * -> * #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

data URec Char

Used for marking occurrences of Char#

data URec Char = UChar {}
type Rep1 (URec Char) 
type Rep1 (URec Char) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UChar" PrefixI True) (S1 (MetaSel (Just Symbol "uChar#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UChar))
type Rep (URec Char p) 
type Rep (URec Char p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UChar" PrefixI True) (S1 (MetaSel (Just Symbol "uChar#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UChar))

data Int :: * #

A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. The exact range for a given implementation can be determined by using minBound and maxBound from the Bounded class.

Instances

Bounded Int 

Methods

minBound :: Int #

maxBound :: Int #

Enum Int 

Methods

succ :: Int -> Int #

pred :: Int -> Int #

toEnum :: Int -> Int #

fromEnum :: Int -> Int #

enumFrom :: Int -> [Int] #

enumFromThen :: Int -> Int -> [Int] #

enumFromTo :: Int -> Int -> [Int] #

enumFromThenTo :: Int -> Int -> Int -> [Int] #

Eq Int 

Methods

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

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

Integral Int 

Methods

quot :: Int -> Int -> Int #

rem :: Int -> Int -> Int #

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

quotRem :: Int -> Int -> (Int, Int) #

divMod :: Int -> Int -> (Int, Int) #

toInteger :: Int -> Integer #

Num Int 

Methods

(+) :: Int -> Int -> Int #

(-) :: Int -> Int -> Int #

(*) :: Int -> Int -> Int #

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

Ord Int 

Methods

compare :: Int -> Int -> Ordering #

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

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

(>) :: Int -> Int -> Bool #

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

max :: Int -> Int -> Int #

min :: Int -> Int -> Int #

Read Int 
Real Int 

Methods

toRational :: Int -> Rational #

Show Int 

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Storable Int 

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

peekElemOff :: Ptr Int -> Int -> IO Int #

pokeElemOff :: Ptr Int -> Int -> Int -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int #

pokeByteOff :: Ptr b -> Int -> Int -> IO () #

peek :: Ptr Int -> IO Int #

poke :: Ptr Int -> Int -> IO () #

Random Int 

Methods

randomR :: RandomGen g => (Int, Int) -> g -> (Int, g) #

random :: RandomGen g => g -> (Int, g) #

randomRs :: RandomGen g => (Int, Int) -> g -> [Int] #

randoms :: RandomGen g => g -> [Int] #

randomRIO :: (Int, Int) -> IO Int #

randomIO :: IO Int #

Show Int Source # 
Read Int Source # 
Integral Int Source # 
Real Int Source # 
Num Int Source # 
Bounded Int Source # 
Enum Int Source # 
Ord Int Source # 
Eq Int Source # 
Ix Int Source # 
Random Int Source # 
Functor (URec Int) 

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b #

(<$) :: a -> URec Int b -> URec Int a #

Foldable (URec Int) 

Methods

fold :: Monoid m => URec Int m -> m #

foldMap :: Monoid m => (a -> m) -> URec Int a -> m #

foldr :: (a -> b -> b) -> b -> URec Int a -> b #

foldr' :: (a -> b -> b) -> b -> URec Int a -> b #

foldl :: (b -> a -> b) -> b -> URec Int a -> b #

foldl' :: (b -> a -> b) -> b -> URec Int a -> b #

foldr1 :: (a -> a -> a) -> URec Int a -> a #

foldl1 :: (a -> a -> a) -> URec Int a -> a #

toList :: URec Int a -> [a] #

null :: URec Int a -> Bool #

length :: URec Int a -> Int #

elem :: Eq a => a -> URec Int a -> Bool #

maximum :: Ord a => URec Int a -> a #

minimum :: Ord a => URec Int a -> a #

sum :: Num a => URec Int a -> a #

product :: Num a => URec Int a -> a #

Generic1 (URec Int) 

Associated Types

type Rep1 (URec Int :: * -> *) :: * -> * #

Methods

from1 :: URec Int a -> Rep1 (URec Int) a #

to1 :: Rep1 (URec Int) a -> URec Int a #

Eq (URec Int p) 

Methods

(==) :: URec Int p -> URec Int p -> Bool #

(/=) :: URec Int p -> URec Int p -> Bool #

Ord (URec Int p) 

Methods

compare :: URec Int p -> URec Int p -> Ordering #

(<) :: URec Int p -> URec Int p -> Bool #

(<=) :: URec Int p -> URec Int p -> Bool #

(>) :: URec Int p -> URec Int p -> Bool #

(>=) :: URec Int p -> URec Int p -> Bool #

max :: URec Int p -> URec Int p -> URec Int p #

min :: URec Int p -> URec Int p -> URec Int p #

Show (URec Int p) 

Methods

showsPrec :: Int -> URec Int p -> ShowS #

show :: URec Int p -> String #

showList :: [URec Int p] -> ShowS #

Generic (URec Int p) 

Associated Types

type Rep (URec Int p) :: * -> * #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

data URec Int

Used for marking occurrences of Int#

data URec Int = UInt {}
type Rep1 (URec Int) 
type Rep1 (URec Int) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UInt" PrefixI True) (S1 (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UInt))
type Rep (URec Int p) 
type Rep (URec Int p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UInt" PrefixI True) (S1 (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UInt))

data Integer :: * #

Invariant: Jn# and Jp# are used iff value doesn't fit in S#

Useful properties resulting from the invariants:

Instances

Enum Integer 
Eq Integer 

Methods

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

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

Integral Integer 
Num Integer 
Ord Integer 
Read Integer 
Real Integer 
Show Integer 
Random Integer 

Methods

randomR :: RandomGen g => (Integer, Integer) -> g -> (Integer, g) #

random :: RandomGen g => g -> (Integer, g) #

randomRs :: RandomGen g => (Integer, Integer) -> g -> [Integer] #

randoms :: RandomGen g => g -> [Integer] #

randomRIO :: (Integer, Integer) -> IO Integer #

randomIO :: IO Integer #

Show Integer Source # 
Read Integer Source # 
Integral Integer Source # 
Real Integer Source # 
Num Integer Source # 
Enum Integer Source # 
Ord Integer Source # 
Eq Integer Source # 
Ix Integer Source # 
Random Integer Source # 

data Float :: * #

Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.

Instances

Eq Float 

Methods

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

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

Floating Float 
Ord Float 

Methods

compare :: Float -> Float -> Ordering #

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

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

(>) :: Float -> Float -> Bool #

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

max :: Float -> Float -> Float #

min :: Float -> Float -> Float #

Read Float 
RealFloat Float 
Storable Float 

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

pokeElemOff :: Ptr Float -> Int -> Float -> IO () #

peekByteOff :: Ptr b -> Int -> IO Float #

pokeByteOff :: Ptr b -> Int -> Float -> IO () #

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

Random Float 

Methods

randomR :: RandomGen g => (Float, Float) -> g -> (Float, g) #

random :: RandomGen g => g -> (Float, g) #

randomRs :: RandomGen g => (Float, Float) -> g -> [Float] #

randoms :: RandomGen g => g -> [Float] #

randomRIO :: (Float, Float) -> IO Float #

randomIO :: IO Float #

Show Float Source # 
Read Float Source # 
RealFloat Float Source # 

Methods

gfloatRadix :: RefSrcPos -> RefExp -> R (Fun Float Integer) Source #

sfloatRadix :: R (Fun Float Integer) Source #

gfloatDigits :: RefSrcPos -> RefExp -> R (Fun Float Int) Source #

sfloatDigits :: R (Fun Float Int) Source #

gfloatRange :: RefSrcPos -> RefExp -> R (Fun Float (Tuple2 Int Int)) Source #

sfloatRange :: R (Fun Float (Tuple2 Int Int)) Source #

gdecodeFloat :: RefSrcPos -> RefExp -> R (Fun Float (Tuple2 Integer Int)) Source #

sdecodeFloat :: R (Fun Float (Tuple2 Integer Int)) Source #

gencodeFloat :: RefSrcPos -> RefExp -> R (Fun Integer (Fun Int Float)) Source #

sencodeFloat :: R (Fun Integer (Fun Int Float)) Source #

gexponent :: RefSrcPos -> RefExp -> R (Fun Float Int) Source #

sexponent :: R (Fun Float Int) Source #

gsignificand :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

ssignificand :: R (Fun Float Float) Source #

gscaleFloat :: RefSrcPos -> RefExp -> R (Fun Int (Fun Float Float)) Source #

sscaleFloat :: R (Fun Int (Fun Float Float)) Source #

gisNaN :: RefSrcPos -> RefExp -> R (Fun Float Bool) Source #

gisInfinite :: RefSrcPos -> RefExp -> R (Fun Float Bool) Source #

gisDenormalized :: RefSrcPos -> RefExp -> R (Fun Float Bool) Source #

gisNegativeZero :: RefSrcPos -> RefExp -> R (Fun Float Bool) Source #

gisIEEE :: RefSrcPos -> RefExp -> R (Fun Float Bool) Source #

sisNaN :: R (Fun Float Bool) Source #

sisInfinite :: R (Fun Float Bool) Source #

sisDenormalized :: R (Fun Float Bool) Source #

sisNegativeZero :: R (Fun Float Bool) Source #

sisIEEE :: R (Fun Float Bool) Source #

gatan2 :: RefSrcPos -> RefExp -> R (Fun Float (Fun Float Float)) Source #

satan2 :: R (Fun Float (Fun Float Float)) Source #

RealFrac Float Source # 
Floating Float Source # 

Methods

gpi :: RefSrcPos -> RefExp -> R Float Source #

spi :: R Float Source #

gexp :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

glog :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gsqrt :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

sexp :: R (Fun Float Float) Source #

slog :: R (Fun Float Float) Source #

ssqrt :: R (Fun Float Float) Source #

(!**) :: RefSrcPos -> RefExp -> R (Fun Float (Fun Float Float)) Source #

glogBase :: RefSrcPos -> RefExp -> R (Fun Float (Fun Float Float)) Source #

(|**) :: R (Fun Float (Fun Float Float)) Source #

slogBase :: R (Fun Float (Fun Float Float)) Source #

gsin :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gcos :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gtan :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

ssin :: R (Fun Float Float) Source #

scos :: R (Fun Float Float) Source #

stan :: R (Fun Float Float) Source #

gasin :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gacos :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gatan :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

sasin :: R (Fun Float Float) Source #

sacos :: R (Fun Float Float) Source #

satan :: R (Fun Float Float) Source #

gsinh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gcosh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gtanh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

ssinh :: R (Fun Float Float) Source #

scosh :: R (Fun Float Float) Source #

stanh :: R (Fun Float Float) Source #

gasinh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gacosh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gatanh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

sasinh :: R (Fun Float Float) Source #

sacosh :: R (Fun Float Float) Source #

satanh :: R (Fun Float Float) Source #

Fractional Float Source # 
Real Float Source # 
Num Float Source # 
Enum Float Source # 
Ord Float Source # 
Eq Float Source # 
Random Float Source # 
Functor (URec Float) 

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b #

(<$) :: a -> URec Float b -> URec Float a #

Foldable (URec Float) 

Methods

fold :: Monoid m => URec Float m -> m #

foldMap :: Monoid m => (a -> m) -> URec Float a -> m #

foldr :: (a -> b -> b) -> b -> URec Float a -> b #

foldr' :: (a -> b -> b) -> b -> URec Float a -> b #

foldl :: (b -> a -> b) -> b -> URec Float a -> b #

foldl' :: (b -> a -> b) -> b -> URec Float a -> b #

foldr1 :: (a -> a -> a) -> URec Float a -> a #

foldl1 :: (a -> a -> a) -> URec Float a -> a #

toList :: URec Float a -> [a] #

null :: URec Float a -> Bool #

length :: URec Float a -> Int #

elem :: Eq a => a -> URec Float a -> Bool #

maximum :: Ord a => URec Float a -> a #

minimum :: Ord a => URec Float a -> a #

sum :: Num a => URec Float a -> a #

product :: Num a => URec Float a -> a #

Generic1 (URec Float) 

Associated Types

type Rep1 (URec Float :: * -> *) :: * -> * #

Methods

from1 :: URec Float a -> Rep1 (URec Float) a #

to1 :: Rep1 (URec Float) a -> URec Float a #

Eq (URec Float p) 

Methods

(==) :: URec Float p -> URec Float p -> Bool #

(/=) :: URec Float p -> URec Float p -> Bool #

Ord (URec Float p) 

Methods

compare :: URec Float p -> URec Float p -> Ordering #

(<) :: URec Float p -> URec Float p -> Bool #

(<=) :: URec Float p -> URec Float p -> Bool #

(>) :: URec Float p -> URec Float p -> Bool #

(>=) :: URec Float p -> URec Float p -> Bool #

max :: URec Float p -> URec Float p -> URec Float p #

min :: URec Float p -> URec Float p -> URec Float p #

Show (URec Float p) 

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Generic (URec Float p) 

Associated Types

type Rep (URec Float p) :: * -> * #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

data URec Float

Used for marking occurrences of Float#

type Rep1 (URec Float) 
type Rep1 (URec Float) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UFloat" PrefixI True) (S1 (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UFloat))
type Rep (URec Float p) 
type Rep (URec Float p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UFloat" PrefixI True) (S1 (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UFloat))

data Double :: * #

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

Instances

Eq Double 

Methods

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

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

Floating Double 
Ord Double 
Read Double 
RealFloat Double 
Storable Double 
Random Double 

Methods

randomR :: RandomGen g => (Double, Double) -> g -> (Double, g) #

random :: RandomGen g => g -> (Double, g) #

randomRs :: RandomGen g => (Double, Double) -> g -> [Double] #

randoms :: RandomGen g => g -> [Double] #

randomRIO :: (Double, Double) -> IO Double #

randomIO :: IO Double #

Show Double Source # 
Read Double Source # 
RealFloat Double Source # 

Methods

gfloatRadix :: RefSrcPos -> RefExp -> R (Fun Double Integer) Source #

sfloatRadix :: R (Fun Double Integer) Source #

gfloatDigits :: RefSrcPos -> RefExp -> R (Fun Double Int) Source #

sfloatDigits :: R (Fun Double Int) Source #

gfloatRange :: RefSrcPos -> RefExp -> R (Fun Double (Tuple2 Int Int)) Source #

sfloatRange :: R (Fun Double (Tuple2 Int Int)) Source #

gdecodeFloat :: RefSrcPos -> RefExp -> R (Fun Double (Tuple2 Integer Int)) Source #

sdecodeFloat :: R (Fun Double (Tuple2 Integer Int)) Source #

gencodeFloat :: RefSrcPos -> RefExp -> R (Fun Integer (Fun Int Double)) Source #

sencodeFloat :: R (Fun Integer (Fun Int Double)) Source #

gexponent :: RefSrcPos -> RefExp -> R (Fun Double Int) Source #

sexponent :: R (Fun Double Int) Source #

gsignificand :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

ssignificand :: R (Fun Double Double) Source #

gscaleFloat :: RefSrcPos -> RefExp -> R (Fun Int (Fun Double Double)) Source #

sscaleFloat :: R (Fun Int (Fun Double Double)) Source #

gisNaN :: RefSrcPos -> RefExp -> R (Fun Double Bool) Source #

gisInfinite :: RefSrcPos -> RefExp -> R (Fun Double Bool) Source #

gisDenormalized :: RefSrcPos -> RefExp -> R (Fun Double Bool) Source #

gisNegativeZero :: RefSrcPos -> RefExp -> R (Fun Double Bool) Source #

gisIEEE :: RefSrcPos -> RefExp -> R (Fun Double Bool) Source #

sisNaN :: R (Fun Double Bool) Source #

sisInfinite :: R (Fun Double Bool) Source #

sisDenormalized :: R (Fun Double Bool) Source #

sisNegativeZero :: R (Fun Double Bool) Source #

sisIEEE :: R (Fun Double Bool) Source #

gatan2 :: RefSrcPos -> RefExp -> R (Fun Double (Fun Double Double)) Source #

satan2 :: R (Fun Double (Fun Double Double)) Source #

RealFrac Double Source # 
Floating Double Source # 

Methods

gpi :: RefSrcPos -> RefExp -> R Double Source #

spi :: R Double Source #

gexp :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

glog :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gsqrt :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

sexp :: R (Fun Double Double) Source #

slog :: R (Fun Double Double) Source #

ssqrt :: R (Fun Double Double) Source #

(!**) :: RefSrcPos -> RefExp -> R (Fun Double (Fun Double Double)) Source #

glogBase :: RefSrcPos -> RefExp -> R (Fun Double (Fun Double Double)) Source #

(|**) :: R (Fun Double (Fun Double Double)) Source #

slogBase :: R (Fun Double (Fun Double Double)) Source #

gsin :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gcos :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gtan :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

ssin :: R (Fun Double Double) Source #

scos :: R (Fun Double Double) Source #

stan :: R (Fun Double Double) Source #

gasin :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gacos :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gatan :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

sasin :: R (Fun Double Double) Source #

sacos :: R (Fun Double Double) Source #

satan :: R (Fun Double Double) Source #

gsinh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gcosh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gtanh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

ssinh :: R (Fun Double Double) Source #

scosh :: R (Fun Double Double) Source #

stanh :: R (Fun Double Double) Source #

gasinh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gacosh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gatanh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

sasinh :: R (Fun Double Double) Source #

sacosh :: R (Fun Double Double) Source #

satanh :: R (Fun Double Double) Source #

Fractional Double Source # 
Real Double Source # 
Num Double Source # 
Enum Double Source # 
Ord Double Source # 
Eq Double Source # 
Random Double Source # 
Functor (URec Double) 

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b #

(<$) :: a -> URec Double b -> URec Double a #

Foldable (URec Double) 

Methods

fold :: Monoid m => URec Double m -> m #

foldMap :: Monoid m => (a -> m) -> URec Double a -> m #

foldr :: (a -> b -> b) -> b -> URec Double a -> b #

foldr' :: (a -> b -> b) -> b -> URec Double a -> b #

foldl :: (b -> a -> b) -> b -> URec Double a -> b #

foldl' :: (b -> a -> b) -> b -> URec Double a -> b #

foldr1 :: (a -> a -> a) -> URec Double a -> a #

foldl1 :: (a -> a -> a) -> URec Double a -> a #

toList :: URec Double a -> [a] #

null :: URec Double a -> Bool #

length :: URec Double a -> Int #

elem :: Eq a => a -> URec Double a -> Bool #

maximum :: Ord a => URec Double a -> a #

minimum :: Ord a => URec Double a -> a #

sum :: Num a => URec Double a -> a #

product :: Num a => URec Double a -> a #

Generic1 (URec Double) 

Associated Types

type Rep1 (URec Double :: * -> *) :: * -> * #

Methods

from1 :: URec Double a -> Rep1 (URec Double) a #

to1 :: Rep1 (URec Double) a -> URec Double a #

Eq (URec Double p) 

Methods

(==) :: URec Double p -> URec Double p -> Bool #

(/=) :: URec Double p -> URec Double p -> Bool #

Ord (URec Double p) 

Methods

compare :: URec Double p -> URec Double p -> Ordering #

(<) :: URec Double p -> URec Double p -> Bool #

(<=) :: URec Double p -> URec Double p -> Bool #

(>) :: URec Double p -> URec Double p -> Bool #

(>=) :: URec Double p -> URec Double p -> Bool #

max :: URec Double p -> URec Double p -> URec Double p #

min :: URec Double p -> URec Double p -> URec Double p #

Show (URec Double p) 

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Generic (URec Double p) 

Associated Types

type Rep (URec Double p) :: * -> * #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

data URec Double

Used for marking occurrences of Double#

type Rep1 (URec Double) 
type Rep1 (URec Double) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UDouble" PrefixI True) (S1 (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UDouble))
type Rep (URec Double p) 
type Rep (URec Double p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UDouble" PrefixI True) (S1 (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UDouble))

data IO a Source #

Instances

Monad IO Source # 

Methods

(!>>=) :: RefSrcPos -> RefExp -> R (Fun (IO a) (Fun (Fun a (IO b)) (IO b))) Source #

(|>>=) :: R (Fun (IO a) (Fun (Fun a (IO b)) (IO b))) Source #

(!>>) :: RefSrcPos -> RefExp -> R (Fun (IO a) (Fun (IO b) (IO b))) Source #

(|>>) :: R (Fun (IO a) (Fun (IO b) (IO b))) Source #

greturn :: RefSrcPos -> RefExp -> R (Fun a (IO a)) Source #

sreturn :: R (Fun a (IO a)) Source #

gfail :: RefSrcPos -> RefExp -> R (Fun String (IO a)) Source #

sfail :: R (Fun String (IO a)) Source #

Functor IO Source # 

Methods

gfmap :: RefSrcPos -> RefExp -> R (Fun (Fun a b) (Fun (IO a) (IO b))) Source #

sfmap :: R (Fun (Fun a b) (Fun (IO a) (IO b))) Source #

class Eq a where Source #

Minimal complete definition

(|==), (|/=)

Methods

(!==), (!/=) :: RefSrcPos -> RefExp -> R (Fun a (Fun a Bool)) Source #

(|==), (|/=) :: R (Fun a (Fun a Bool)) Source #

Instances

Eq Bool Source # 
Eq Char Source # 
Eq Double Source # 
Eq Float Source # 
Eq Int Source # 
Eq Integer Source # 
Eq Tuple0 Source # 
Eq Ordering Source # 
Eq SeekMode Source # 
Eq BufferMode Source # 
Eq IOMode Source # 
Eq TimeLocale Source # 
Eq ExitCode Source # 
Eq TimeDiff Source # 
Eq CalendarTime Source # 
Eq Day Source # 
Eq Month Source # 
Eq GeneralCategory Source # 
Eq a => Eq (List a) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List a) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List a) Bool)) Source #

(|==) :: R (Fun (List a) (Fun (List a) Bool)) Source #

(|/=) :: R (Fun (List a) (Fun (List a) Bool)) Source #

Eq a => Eq (Ratio a) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

(|==) :: R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

(|/=) :: R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

Eq a => Eq (Maybe a) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|==) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|/=) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

Eq a => Eq (Complex a) Source # 
(Eq a, Eq b) => Eq (Tuple2 a b) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(|==) :: R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(|/=) :: R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(Eq a, Eq b) => Eq (Either a b) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|==) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|/=) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(Ix a, Eq b) => Eq (Array a b) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(|==) :: R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(|/=) :: R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(Eq a, Eq b, Eq c) => Eq (Tuple3 a b c) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(|==) :: R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(|/=) :: R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d) => Eq (Tuple4 a b c d) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(|==) :: R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(|/=) :: R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (Tuple5 a b c d e) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(|==) :: R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(|/=) :: R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (Tuple6 a b c d e f) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(|==) :: R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(|/=) :: R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (Tuple7 a b c d e f g) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(|==) :: R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(|/=) :: R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (Tuple8 a b c d e f g h) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(|==) :: R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(|/=) :: R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (Tuple9 a b c d e f g h i) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(|==) :: R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(|/=) :: R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (Tuple10 a b c d e f g h i j) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(|==) :: R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(|/=) :: R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (Tuple11 a b c d e f g h i j k) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(|==) :: R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(|/=) :: R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (Tuple12 a b c d e f g h i j k l) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(|==) :: R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(|/=) :: R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (Tuple13 a b c d e f g h i j k l m) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(|==) :: R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(|/=) :: R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (Tuple14 a b c d e f g h i j k l m n) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(|==) :: R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(|/=) :: R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (Tuple15 a b c d e f g h i j k l m n o) Source # 

Methods

(!==) :: RefSrcPos -> RefExp -> R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

(!/=) :: RefSrcPos -> RefExp -> R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

(|==) :: R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

(|/=) :: R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

class Eq a => Ord a where Source #

Minimal complete definition

scompare, (|<), (|<=), (|>=), (|>), smax, smin

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun a (Fun a Ordering)) Source #

scompare :: R (Fun a (Fun a Ordering)) Source #

(!<), (!<=), (!>=), (!>) :: RefSrcPos -> RefExp -> R (Fun a (Fun a Bool)) Source #

(|<), (|<=), (|>=), (|>) :: R (Fun a (Fun a Bool)) Source #

gmax, gmin :: RefSrcPos -> RefExp -> R (Fun a (Fun a a)) Source #

smax, smin :: R (Fun a (Fun a a)) Source #

Instances

Ord Bool Source # 
Ord Char Source # 
Ord Double Source # 
Ord Float Source # 
Ord Int Source # 
Ord Integer Source # 
Ord Tuple0 Source # 
Ord Ordering Source # 
Ord SeekMode Source # 
Ord BufferMode Source # 
Ord IOMode Source # 
Ord TimeLocale Source # 
Ord ExitCode Source # 
Ord TimeDiff Source # 
Ord CalendarTime Source # 
Ord Day Source # 
Ord Month Source # 
Ord GeneralCategory Source # 
Ord a => Ord (List a) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List a) Ordering)) Source #

scompare :: R (Fun (List a) (Fun (List a) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List a) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List a) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List a) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List a) Bool)) Source #

(|<) :: R (Fun (List a) (Fun (List a) Bool)) Source #

(|<=) :: R (Fun (List a) (Fun (List a) Bool)) Source #

(|>=) :: R (Fun (List a) (Fun (List a) Bool)) Source #

(|>) :: R (Fun (List a) (Fun (List a) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List a) (List a))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List a) (List a))) Source #

smax :: R (Fun (List a) (Fun (List a) (List a))) Source #

smin :: R (Fun (List a) (Fun (List a) (List a))) Source #

Integral a => Ord (Ratio a) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) Ordering)) Source #

scompare :: R (Fun (Ratio a) (Fun (Ratio a) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

(|<) :: R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

(|<=) :: R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

(|>=) :: R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

(|>) :: R (Fun (Ratio a) (Fun (Ratio a) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) (Ratio a))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) (Ratio a))) Source #

smax :: R (Fun (Ratio a) (Fun (Ratio a) (Ratio a))) Source #

smin :: R (Fun (Ratio a) (Fun (Ratio a) (Ratio a))) Source #

Ord a => Ord (Maybe a) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Ordering)) Source #

scompare :: R (Fun (Maybe a) (Fun (Maybe a) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|<) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|<=) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|>=) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

(|>) :: R (Fun (Maybe a) (Fun (Maybe a) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) (Maybe a))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe a) (Maybe a))) Source #

smax :: R (Fun (Maybe a) (Fun (Maybe a) (Maybe a))) Source #

smin :: R (Fun (Maybe a) (Fun (Maybe a) (Maybe a))) Source #

(Ord a, Ord b) => Ord (Tuple2 a b) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Ordering)) Source #

scompare :: R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(|<) :: R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(|<=) :: R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(|>=) :: R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

(|>) :: R (Fun (Tuple2 a b) (Fun (Tuple2 a b) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) (Fun (Tuple2 a b) (Tuple2 a b))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) (Fun (Tuple2 a b) (Tuple2 a b))) Source #

smax :: R (Fun (Tuple2 a b) (Fun (Tuple2 a b) (Tuple2 a b))) Source #

smin :: R (Fun (Tuple2 a b) (Fun (Tuple2 a b) (Tuple2 a b))) Source #

(Ord a, Ord b) => Ord (Either a b) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Ordering)) Source #

scompare :: R (Fun (Either a b) (Fun (Either a b) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|<) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|<=) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|>=) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

(|>) :: R (Fun (Either a b) (Fun (Either a b) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) (Either a b))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Either a b) (Fun (Either a b) (Either a b))) Source #

smax :: R (Fun (Either a b) (Fun (Either a b) (Either a b))) Source #

smin :: R (Fun (Either a b) (Fun (Either a b) (Either a b))) Source #

(Ix a, Ord b) => Ord (Array a b) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Array a b) (Fun (Array a b) Ordering)) Source #

scompare :: R (Fun (Array a b) (Fun (Array a b) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(|<) :: R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(|<=) :: R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(|>=) :: R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

(|>) :: R (Fun (Array a b) (Fun (Array a b) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Array a b) (Fun (Array a b) (Array a b))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Array a b) (Fun (Array a b) (Array a b))) Source #

smax :: R (Fun (Array a b) (Fun (Array a b) (Array a b))) Source #

smin :: R (Fun (Array a b) (Fun (Array a b) (Array a b))) Source #

(Ord a, Ord b, Ord c) => Ord (Tuple3 a b c) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Ordering)) Source #

scompare :: R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(|<) :: R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(|<=) :: R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(|>=) :: R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

(|>) :: R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) (Tuple3 a b c))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) (Tuple3 a b c))) Source #

smax :: R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) (Tuple3 a b c))) Source #

smin :: R (Fun (Tuple3 a b c) (Fun (Tuple3 a b c) (Tuple3 a b c))) Source #

(Ord a, Ord b, Ord c, Ord d) => Ord (Tuple4 a b c d) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Ordering)) Source #

scompare :: R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(|<) :: R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(|<=) :: R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(|>=) :: R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

(|>) :: R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) (Tuple4 a b c d))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) (Tuple4 a b c d))) Source #

smax :: R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) (Tuple4 a b c d))) Source #

smin :: R (Fun (Tuple4 a b c d) (Fun (Tuple4 a b c d) (Tuple4 a b c d))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (Tuple5 a b c d e) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Ordering)) Source #

scompare :: R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(|<) :: R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(|<=) :: R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(|>=) :: R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

(|>) :: R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) (Tuple5 a b c d e))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) (Tuple5 a b c d e))) Source #

smax :: R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) (Tuple5 a b c d e))) Source #

smin :: R (Fun (Tuple5 a b c d e) (Fun (Tuple5 a b c d e) (Tuple5 a b c d e))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (Tuple6 a b c d e f) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Ordering)) Source #

scompare :: R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(|<) :: R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(|<=) :: R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(|>=) :: R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

(|>) :: R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) (Tuple6 a b c d e f))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) (Tuple6 a b c d e f))) Source #

smax :: R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) (Tuple6 a b c d e f))) Source #

smin :: R (Fun (Tuple6 a b c d e f) (Fun (Tuple6 a b c d e f) (Tuple6 a b c d e f))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (Tuple7 a b c d e f g) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Ordering)) Source #

scompare :: R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(|<) :: R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(|<=) :: R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(|>=) :: R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

(|>) :: R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) (Tuple7 a b c d e f g))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) (Tuple7 a b c d e f g))) Source #

smax :: R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) (Tuple7 a b c d e f g))) Source #

smin :: R (Fun (Tuple7 a b c d e f g) (Fun (Tuple7 a b c d e f g) (Tuple7 a b c d e f g))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (Tuple8 a b c d e f g h) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Ordering)) Source #

scompare :: R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(|<) :: R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(|<=) :: R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(|>=) :: R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

(|>) :: R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) (Tuple8 a b c d e f g h))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) (Tuple8 a b c d e f g h))) Source #

smax :: R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) (Tuple8 a b c d e f g h))) Source #

smin :: R (Fun (Tuple8 a b c d e f g h) (Fun (Tuple8 a b c d e f g h) (Tuple8 a b c d e f g h))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (Tuple9 a b c d e f g h i) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Ordering)) Source #

scompare :: R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(|<) :: R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(|<=) :: R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(|>=) :: R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

(|>) :: R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) (Tuple9 a b c d e f g h i))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) (Tuple9 a b c d e f g h i))) Source #

smax :: R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) (Tuple9 a b c d e f g h i))) Source #

smin :: R (Fun (Tuple9 a b c d e f g h i) (Fun (Tuple9 a b c d e f g h i) (Tuple9 a b c d e f g h i))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (Tuple10 a b c d e f g h i j) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Ordering)) Source #

scompare :: R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(|<) :: R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(|<=) :: R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(|>=) :: R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

(|>) :: R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) (Tuple10 a b c d e f g h i j))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) (Tuple10 a b c d e f g h i j))) Source #

smax :: R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) (Tuple10 a b c d e f g h i j))) Source #

smin :: R (Fun (Tuple10 a b c d e f g h i j) (Fun (Tuple10 a b c d e f g h i j) (Tuple10 a b c d e f g h i j))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (Tuple11 a b c d e f g h i j k) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Ordering)) Source #

scompare :: R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(|<) :: R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(|<=) :: R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(|>=) :: R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

(|>) :: R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) (Tuple11 a b c d e f g h i j k))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) (Tuple11 a b c d e f g h i j k))) Source #

smax :: R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) (Tuple11 a b c d e f g h i j k))) Source #

smin :: R (Fun (Tuple11 a b c d e f g h i j k) (Fun (Tuple11 a b c d e f g h i j k) (Tuple11 a b c d e f g h i j k))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (Tuple12 a b c d e f g h i j k l) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Ordering)) Source #

scompare :: R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(|<) :: R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(|<=) :: R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(|>=) :: R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

(|>) :: R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) (Tuple12 a b c d e f g h i j k l))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) (Tuple12 a b c d e f g h i j k l))) Source #

smax :: R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) (Tuple12 a b c d e f g h i j k l))) Source #

smin :: R (Fun (Tuple12 a b c d e f g h i j k l) (Fun (Tuple12 a b c d e f g h i j k l) (Tuple12 a b c d e f g h i j k l))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (Tuple13 a b c d e f g h i j k l m) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Ordering)) Source #

scompare :: R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(|<) :: R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(|<=) :: R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(|>=) :: R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

(|>) :: R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) (Tuple13 a b c d e f g h i j k l m))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) (Tuple13 a b c d e f g h i j k l m))) Source #

smax :: R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) (Tuple13 a b c d e f g h i j k l m))) Source #

smin :: R (Fun (Tuple13 a b c d e f g h i j k l m) (Fun (Tuple13 a b c d e f g h i j k l m) (Tuple13 a b c d e f g h i j k l m))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (Tuple14 a b c d e f g h i j k l m n) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Ordering)) Source #

scompare :: R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(|<) :: R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(|<=) :: R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(|>=) :: R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

(|>) :: R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) (Tuple14 a b c d e f g h i j k l m n))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) (Tuple14 a b c d e f g h i j k l m n))) Source #

smax :: R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) (Tuple14 a b c d e f g h i j k l m n))) Source #

smin :: R (Fun (Tuple14 a b c d e f g h i j k l m n) (Fun (Tuple14 a b c d e f g h i j k l m n) (Tuple14 a b c d e f g h i j k l m n))) Source #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (Tuple15 a b c d e f g h i j k l m n o) Source # 

Methods

gcompare :: RefSrcPos -> RefExp -> R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Ordering)) Source #

scompare :: R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Ordering)) Source #

(!<) :: RefSrcPos -> RefExp -> R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

(!<=) :: RefSrcPos -> RefExp -> R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

(!>=) :: RefSrcPos -> RefExp -> R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

(!>) :: RefSrcPos -> RefExp -> R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

(|<) :: R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

(|<=) :: R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

(|>=) :: R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

(|>) :: R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) Bool)) Source #

gmax :: RefSrcPos -> RefExp -> R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) (Tuple15 a b c d e f g h i j k l m n o))) Source #

gmin :: RefSrcPos -> RefExp -> R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) (Tuple15 a b c d e f g h i j k l m n o))) Source #

smax :: R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) (Tuple15 a b c d e f g h i j k l m n o))) Source #

smin :: R (Fun (Tuple15 a b c d e f g h i j k l m n o) (Fun (Tuple15 a b c d e f g h i j k l m n o) (Tuple15 a b c d e f g h i j k l m n o))) Source #

class Enum a where Source #

Instances

Enum Bool Source # 
Enum Char Source # 
Enum Double Source # 
Enum Float Source # 
Enum Int Source # 
Enum Integer Source # 
Enum Tuple0 Source # 
Enum Ordering Source # 
Enum SeekMode Source # 
Enum IOMode Source # 
Enum Day Source # 
Enum Month Source # 
Enum GeneralCategory Source # 
Integral a => Enum (Ratio a) Source # 

class Bounded a where Source #

Minimal complete definition

gminBound, gmaxBound

Instances

Bounded Bool Source # 
Bounded Char Source # 
Bounded Int Source # 
Bounded Tuple0 Source # 
Bounded Ordering Source # 
Bounded SeekMode Source # 
Bounded IOMode Source # 
Bounded Day Source # 
Bounded Month Source # 
Bounded GeneralCategory Source # 
(Bounded a, Bounded b) => Bounded (Tuple2 a b) Source # 
(Bounded a, Bounded b, Bounded c) => Bounded (Tuple3 a b c) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple3 a b c) Source #

sminBound :: R (Tuple3 a b c) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple3 a b c) Source #

smaxBound :: R (Tuple3 a b c) Source #

(Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (Tuple4 a b c d) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple4 a b c d) Source #

sminBound :: R (Tuple4 a b c d) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple4 a b c d) Source #

smaxBound :: R (Tuple4 a b c d) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (Tuple5 a b c d e) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple5 a b c d e) Source #

sminBound :: R (Tuple5 a b c d e) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple5 a b c d e) Source #

smaxBound :: R (Tuple5 a b c d e) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f) => Bounded (Tuple6 a b c d e f) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple6 a b c d e f) Source #

sminBound :: R (Tuple6 a b c d e f) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple6 a b c d e f) Source #

smaxBound :: R (Tuple6 a b c d e f) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g) => Bounded (Tuple7 a b c d e f g) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple7 a b c d e f g) Source #

sminBound :: R (Tuple7 a b c d e f g) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple7 a b c d e f g) Source #

smaxBound :: R (Tuple7 a b c d e f g) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h) => Bounded (Tuple8 a b c d e f g h) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple8 a b c d e f g h) Source #

sminBound :: R (Tuple8 a b c d e f g h) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple8 a b c d e f g h) Source #

smaxBound :: R (Tuple8 a b c d e f g h) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i) => Bounded (Tuple9 a b c d e f g h i) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple9 a b c d e f g h i) Source #

sminBound :: R (Tuple9 a b c d e f g h i) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple9 a b c d e f g h i) Source #

smaxBound :: R (Tuple9 a b c d e f g h i) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j) => Bounded (Tuple10 a b c d e f g h i j) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple10 a b c d e f g h i j) Source #

sminBound :: R (Tuple10 a b c d e f g h i j) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple10 a b c d e f g h i j) Source #

smaxBound :: R (Tuple10 a b c d e f g h i j) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k) => Bounded (Tuple11 a b c d e f g h i j k) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple11 a b c d e f g h i j k) Source #

sminBound :: R (Tuple11 a b c d e f g h i j k) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple11 a b c d e f g h i j k) Source #

smaxBound :: R (Tuple11 a b c d e f g h i j k) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l) => Bounded (Tuple12 a b c d e f g h i j k l) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple12 a b c d e f g h i j k l) Source #

sminBound :: R (Tuple12 a b c d e f g h i j k l) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple12 a b c d e f g h i j k l) Source #

smaxBound :: R (Tuple12 a b c d e f g h i j k l) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m) => Bounded (Tuple13 a b c d e f g h i j k l m) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple13 a b c d e f g h i j k l m) Source #

sminBound :: R (Tuple13 a b c d e f g h i j k l m) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple13 a b c d e f g h i j k l m) Source #

smaxBound :: R (Tuple13 a b c d e f g h i j k l m) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n) => Bounded (Tuple14 a b c d e f g h i j k l m n) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple14 a b c d e f g h i j k l m n) Source #

sminBound :: R (Tuple14 a b c d e f g h i j k l m n) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple14 a b c d e f g h i j k l m n) Source #

smaxBound :: R (Tuple14 a b c d e f g h i j k l m n) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n, Bounded o) => Bounded (Tuple15 a b c d e f g h i j k l m n o) Source # 

Methods

gminBound :: RefSrcPos -> RefExp -> R (Tuple15 a b c d e f g h i j k l m n o) Source #

sminBound :: R (Tuple15 a b c d e f g h i j k l m n o) Source #

gmaxBound :: RefSrcPos -> RefExp -> R (Tuple15 a b c d e f g h i j k l m n o) Source #

smaxBound :: R (Tuple15 a b c d e f g h i j k l m n o) Source #

class (Eq a, Show a) => Num a where Source #

Minimal complete definition

(!+), (!*), (|-), snegate, gabs, gsignum, gfromInteger

Instances

Num Double Source # 
Num Float Source # 
Num Int Source # 
Num Integer Source # 
Integral a => Num (Ratio a) Source # 

Methods

(!+) :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) (Ratio a))) Source #

(!-) :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) (Ratio a))) Source #

(!*) :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Fun (Ratio a) (Ratio a))) Source #

(|+) :: R (Fun (Ratio a) (Fun (Ratio a) (Ratio a))) Source #

(|-) :: R (Fun (Ratio a) (Fun (Ratio a) (Ratio a))) Source #

(|*) :: R (Fun (Ratio a) (Fun (Ratio a) (Ratio a))) Source #

gnegate :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Ratio a)) Source #

snegate :: R (Fun (Ratio a) (Ratio a)) Source #

gabs :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Ratio a)) Source #

gsignum :: RefSrcPos -> RefExp -> R (Fun (Ratio a) (Ratio a)) Source #

sabs :: R (Fun (Ratio a) (Ratio a)) Source #

ssignum :: R (Fun (Ratio a) (Ratio a)) Source #

gfromInteger :: RefSrcPos -> RefExp -> R (Fun Integer (Ratio a)) Source #

sfromInteger :: R (Fun Integer (Ratio a)) Source #

RealFloat a => Num (Complex a) Source # 

class (Real a, Enum a) => Integral a where Source #

Minimal complete definition

squot, srem, sdiv, smod, gquotRem, sdivMod, gtoInteger

Methods

gquot, grem :: RefSrcPos -> RefExp -> R (Fun a (Fun a a)) Source #

squot, srem :: R (Fun a (Fun a a)) Source #

gdiv, gmod :: RefSrcPos -> RefExp -> R (Fun a (Fun a a)) Source #

sdiv, smod :: R (Fun a (Fun a a)) Source #

gquotRem, gdivMod :: RefSrcPos -> RefExp -> R (Fun a (Fun a (Tuple2 a a))) Source #

squotRem, sdivMod :: R (Fun a (Fun a (Tuple2 a a))) Source #

gtoInteger :: RefSrcPos -> RefExp -> R (Fun a Integer) Source #

stoInteger :: R (Fun a Integer) Source #

Instances

Integral Int Source # 
Integral Integer Source # 

class Num a => Fractional a where Source #

Minimal complete definition

(|/), srecip, gfromRational

Instances

Fractional Double Source # 
Fractional Float Source # 
Integral a => Fractional (Ratio a) Source # 
RealFloat a => Fractional (Complex a) Source # 

class Fractional a => Floating a where Source #

Minimal complete definition

gpi, gexp, glog, ssqrt, (|**), slogBase, gsin, gcos, stan, gasin, gacos, gatan, gsinh, gcosh, stanh, gasinh, gacosh, gatanh

Instances

Floating Double Source # 

Methods

gpi :: RefSrcPos -> RefExp -> R Double Source #

spi :: R Double Source #

gexp :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

glog :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gsqrt :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

sexp :: R (Fun Double Double) Source #

slog :: R (Fun Double Double) Source #

ssqrt :: R (Fun Double Double) Source #

(!**) :: RefSrcPos -> RefExp -> R (Fun Double (Fun Double Double)) Source #

glogBase :: RefSrcPos -> RefExp -> R (Fun Double (Fun Double Double)) Source #

(|**) :: R (Fun Double (Fun Double Double)) Source #

slogBase :: R (Fun Double (Fun Double Double)) Source #

gsin :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gcos :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gtan :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

ssin :: R (Fun Double Double) Source #

scos :: R (Fun Double Double) Source #

stan :: R (Fun Double Double) Source #

gasin :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gacos :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gatan :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

sasin :: R (Fun Double Double) Source #

sacos :: R (Fun Double Double) Source #

satan :: R (Fun Double Double) Source #

gsinh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gcosh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gtanh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

ssinh :: R (Fun Double Double) Source #

scosh :: R (Fun Double Double) Source #

stanh :: R (Fun Double Double) Source #

gasinh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gacosh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

gatanh :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

sasinh :: R (Fun Double Double) Source #

sacosh :: R (Fun Double Double) Source #

satanh :: R (Fun Double Double) Source #

Floating Float Source # 

Methods

gpi :: RefSrcPos -> RefExp -> R Float Source #

spi :: R Float Source #

gexp :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

glog :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gsqrt :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

sexp :: R (Fun Float Float) Source #

slog :: R (Fun Float Float) Source #

ssqrt :: R (Fun Float Float) Source #

(!**) :: RefSrcPos -> RefExp -> R (Fun Float (Fun Float Float)) Source #

glogBase :: RefSrcPos -> RefExp -> R (Fun Float (Fun Float Float)) Source #

(|**) :: R (Fun Float (Fun Float Float)) Source #

slogBase :: R (Fun Float (Fun Float Float)) Source #

gsin :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gcos :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gtan :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

ssin :: R (Fun Float Float) Source #

scos :: R (Fun Float Float) Source #

stan :: R (Fun Float Float) Source #

gasin :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gacos :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gatan :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

sasin :: R (Fun Float Float) Source #

sacos :: R (Fun Float Float) Source #

satan :: R (Fun Float Float) Source #

gsinh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gcosh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gtanh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

ssinh :: R (Fun Float Float) Source #

scosh :: R (Fun Float Float) Source #

stanh :: R (Fun Float Float) Source #

gasinh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gacosh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

gatanh :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

sasinh :: R (Fun Float Float) Source #

sacosh :: R (Fun Float Float) Source #

satanh :: R (Fun Float Float) Source #

RealFloat a => Floating (Complex a) Source # 

Methods

gpi :: RefSrcPos -> RefExp -> R (Complex a) Source #

spi :: R (Complex a) Source #

gexp :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

glog :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

gsqrt :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

sexp :: R (Fun (Complex a) (Complex a)) Source #

slog :: R (Fun (Complex a) (Complex a)) Source #

ssqrt :: R (Fun (Complex a) (Complex a)) Source #

(!**) :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Fun (Complex a) (Complex a))) Source #

glogBase :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Fun (Complex a) (Complex a))) Source #

(|**) :: R (Fun (Complex a) (Fun (Complex a) (Complex a))) Source #

slogBase :: R (Fun (Complex a) (Fun (Complex a) (Complex a))) Source #

gsin :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

gcos :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

gtan :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

ssin :: R (Fun (Complex a) (Complex a)) Source #

scos :: R (Fun (Complex a) (Complex a)) Source #

stan :: R (Fun (Complex a) (Complex a)) Source #

gasin :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

gacos :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

gatan :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

sasin :: R (Fun (Complex a) (Complex a)) Source #

sacos :: R (Fun (Complex a) (Complex a)) Source #

satan :: R (Fun (Complex a) (Complex a)) Source #

gsinh :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

gcosh :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

gtanh :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

ssinh :: R (Fun (Complex a) (Complex a)) Source #

scosh :: R (Fun (Complex a) (Complex a)) Source #

stanh :: R (Fun (Complex a) (Complex a)) Source #

gasinh :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

gacosh :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

gatanh :: RefSrcPos -> RefExp -> R (Fun (Complex a) (Complex a)) Source #

sasinh :: R (Fun (Complex a) (Complex a)) Source #

sacosh :: R (Fun (Complex a) (Complex a)) Source #

satanh :: R (Fun (Complex a) (Complex a)) Source #

class (Real a, Fractional a) => RealFrac a where Source #

Minimal complete definition

gproperFraction, struncate, sround, sceiling, sfloor

Instances

RealFrac Double Source # 
RealFrac Float Source # 
Integral a => RealFrac (Ratio a) Source # 

class (RealFrac a, Floating a) => RealFloat a where Source #

Instances

RealFloat Double Source # 

Methods

gfloatRadix :: RefSrcPos -> RefExp -> R (Fun Double Integer) Source #

sfloatRadix :: R (Fun Double Integer) Source #

gfloatDigits :: RefSrcPos -> RefExp -> R (Fun Double Int) Source #

sfloatDigits :: R (Fun Double Int) Source #

gfloatRange :: RefSrcPos -> RefExp -> R (Fun Double (Tuple2 Int Int)) Source #

sfloatRange :: R (Fun Double (Tuple2 Int Int)) Source #

gdecodeFloat :: RefSrcPos -> RefExp -> R (Fun Double (Tuple2 Integer Int)) Source #

sdecodeFloat :: R (Fun Double (Tuple2 Integer Int)) Source #

gencodeFloat :: RefSrcPos -> RefExp -> R (Fun Integer (Fun Int Double)) Source #

sencodeFloat :: R (Fun Integer (Fun Int Double)) Source #

gexponent :: RefSrcPos -> RefExp -> R (Fun Double Int) Source #

sexponent :: R (Fun Double Int) Source #

gsignificand :: RefSrcPos -> RefExp -> R (Fun Double Double) Source #

ssignificand :: R (Fun Double Double) Source #

gscaleFloat :: RefSrcPos -> RefExp -> R (Fun Int (Fun Double Double)) Source #

sscaleFloat :: R (Fun Int (Fun Double Double)) Source #

gisNaN :: RefSrcPos -> RefExp -> R (Fun Double Bool) Source #

gisInfinite :: RefSrcPos -> RefExp -> R (Fun Double Bool) Source #

gisDenormalized :: RefSrcPos -> RefExp -> R (Fun Double Bool) Source #

gisNegativeZero :: RefSrcPos -> RefExp -> R (Fun Double Bool) Source #

gisIEEE :: RefSrcPos -> RefExp -> R (Fun Double Bool) Source #

sisNaN :: R (Fun Double Bool) Source #

sisInfinite :: R (Fun Double Bool) Source #

sisDenormalized :: R (Fun Double Bool) Source #

sisNegativeZero :: R (Fun Double Bool) Source #

sisIEEE :: R (Fun Double Bool) Source #

gatan2 :: RefSrcPos -> RefExp -> R (Fun Double (Fun Double Double)) Source #

satan2 :: R (Fun Double (Fun Double Double)) Source #

RealFloat Float Source # 

Methods

gfloatRadix :: RefSrcPos -> RefExp -> R (Fun Float Integer) Source #

sfloatRadix :: R (Fun Float Integer) Source #

gfloatDigits :: RefSrcPos -> RefExp -> R (Fun Float Int) Source #

sfloatDigits :: R (Fun Float Int) Source #

gfloatRange :: RefSrcPos -> RefExp -> R (Fun Float (Tuple2 Int Int)) Source #

sfloatRange :: R (Fun Float (Tuple2 Int Int)) Source #

gdecodeFloat :: RefSrcPos -> RefExp -> R (Fun Float (Tuple2 Integer Int)) Source #

sdecodeFloat :: R (Fun Float (Tuple2 Integer Int)) Source #

gencodeFloat :: RefSrcPos -> RefExp -> R (Fun Integer (Fun Int Float)) Source #

sencodeFloat :: R (Fun Integer (Fun Int Float)) Source #

gexponent :: RefSrcPos -> RefExp -> R (Fun Float Int) Source #

sexponent :: R (Fun Float Int) Source #

gsignificand :: RefSrcPos -> RefExp -> R (Fun Float Float) Source #

ssignificand :: R (Fun Float Float) Source #

gscaleFloat :: RefSrcPos -> RefExp -> R (Fun Int (Fun Float Float)) Source #

sscaleFloat :: R (Fun Int (Fun Float Float)) Source #

gisNaN :: RefSrcPos -> RefExp -> R (Fun Float Bool) Source #

gisInfinite :: RefSrcPos -> RefExp -> R (Fun Float Bool) Source #

gisDenormalized :: RefSrcPos -> RefExp -> R (Fun Float Bool) Source #

gisNegativeZero :: RefSrcPos -> RefExp -> R (Fun Float Bool) Source #

gisIEEE :: RefSrcPos -> RefExp -> R (Fun Float Bool) Source #

sisNaN :: R (Fun Float Bool) Source #

sisInfinite :: R (Fun Float Bool) Source #

sisDenormalized :: R (Fun Float Bool) Source #

sisNegativeZero :: R (Fun Float Bool) Source #

sisIEEE :: R (Fun Float Bool) Source #

gatan2 :: RefSrcPos -> RefExp -> R (Fun Float (Fun Float Float)) Source #

satan2 :: R (Fun Float (Fun Float Float)) Source #

class Monad m where Source #

Minimal complete definition

(!>>=), (|>>), greturn, sfail

Methods

(!>>=) :: RefSrcPos -> RefExp -> R (Fun (m a) (Fun (Fun a (m b)) (m b))) Source #

(|>>=) :: R (Fun (m a) (Fun (Fun a (m b)) (m b))) Source #

(!>>) :: RefSrcPos -> RefExp -> R (Fun (m a) (Fun (m b) (m b))) Source #

(|>>) :: R (Fun (m a) (Fun (m b) (m b))) Source #

greturn :: RefSrcPos -> RefExp -> R (Fun a (m a)) Source #

sreturn :: R (Fun a (m a)) Source #

gfail :: RefSrcPos -> RefExp -> R (Fun String (m a)) Source #

sfail :: R (Fun String (m a)) Source #

Instances

Monad List Source # 

Methods

(!>>=) :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (Fun a (List b)) (List b))) Source #

(|>>=) :: R (Fun (List a) (Fun (Fun a (List b)) (List b))) Source #

(!>>) :: RefSrcPos -> RefExp -> R (Fun (List a) (Fun (List b) (List b))) Source #

(|>>) :: R (Fun (List a) (Fun (List b) (List b))) Source #

greturn :: RefSrcPos -> RefExp -> R (Fun a (List a)) Source #

sreturn :: R (Fun a (List a)) Source #

gfail :: RefSrcPos -> RefExp -> R (Fun String (List a)) Source #

sfail :: R (Fun String (List a)) Source #

Monad IO Source # 

Methods

(!>>=) :: RefSrcPos -> RefExp -> R (Fun (IO a) (Fun (Fun a (IO b)) (IO b))) Source #

(|>>=) :: R (Fun (IO a) (Fun (Fun a (IO b)) (IO b))) Source #

(!>>) :: RefSrcPos -> RefExp -> R (Fun (IO a) (Fun (IO b) (IO b))) Source #

(|>>) :: R (Fun (IO a) (Fun (IO b) (IO b))) Source #

greturn :: RefSrcPos -> RefExp -> R (Fun a (IO a)) Source #

sreturn :: R (Fun a (IO a)) Source #

gfail :: RefSrcPos -> RefExp -> R (Fun String (IO a)) Source #

sfail :: R (Fun String (IO a)) Source #

Monad Maybe Source # 

Methods

(!>>=) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Fun a (Maybe b)) (Maybe b))) Source #

(|>>=) :: R (Fun (Maybe a) (Fun (Fun a (Maybe b)) (Maybe b))) Source #

(!>>) :: RefSrcPos -> RefExp -> R (Fun (Maybe a) (Fun (Maybe b) (Maybe b))) Source #

(|>>) :: R (Fun (Maybe a) (Fun (Maybe b) (Maybe b))) Source #

greturn :: RefSrcPos -> RefExp -> R (Fun a (Maybe a)) Source #

sreturn :: R (Fun a (Maybe a)) Source #

gfail :: RefSrcPos -> RefExp -> R (Fun String (Maybe a)) Source #

sfail :: R (Fun String (Maybe a)) Source #

class Functor f where Source #

Minimal complete definition

gfmap

Methods

gfmap :: RefSrcPos -> RefExp -> R (Fun (Fun a b) (Fun (f a) (f b))) Source #

sfmap :: R (Fun (Fun a b) (Fun (f a) (f b))) Source #

Instances

Functor List Source # 

Methods

gfmap :: RefSrcPos -> RefExp -> R (Fun (Fun a b) (Fun (List a) (List b))) Source #

sfmap :: R (Fun (Fun a b) (Fun (List a) (List b))) Source #

Functor IO Source # 

Methods

gfmap :: RefSrcPos -> RefExp -> R (Fun (Fun a b) (Fun (IO a) (IO b))) Source #

sfmap :: R (Fun (Fun a b) (Fun (IO a) (IO b))) Source #

Functor Maybe Source # 

Methods

gfmap :: RefSrcPos -> RefExp -> R (Fun (Fun a b) (Fun (Maybe a) (Maybe b))) Source #

sfmap :: R (Fun (Fun a b) (Fun (Maybe a) (Maybe b))) Source #

Ix a => Functor (Array a) Source # 

Methods

gfmap :: RefSrcPos -> RefExp -> R (Fun (Fun a b) (Fun (Array a a) (Array a b))) Source #

sfmap :: R (Fun (Fun a b) (Fun (Array a a) (Array a b))) Source #

gmapM :: Monad m => RefSrcPos -> RefExp -> R (Fun (Fun a (m b)) (Fun (List a) (m (List b)))) Source #

hmapM :: Monad m => R (Fun a (m b)) -> R (List a) -> RefExp -> R (m (List b)) Source #

gmapM_ :: Monad m => RefSrcPos -> RefExp -> R (Fun (Fun a (m b)) (Fun (List a) (m Tuple0))) Source #

hmapM_ :: Monad m => R (Fun a (m b)) -> R (List a) -> RefExp -> R (m Tuple0) Source #

gsequence :: Monad m => RefSrcPos -> RefExp -> R (Fun (List (m a)) (m (List a))) Source #

gsequence_ :: Monad m => RefSrcPos -> RefExp -> R (Fun (List (m a)) (m Tuple0)) Source #

(!=<<) :: Monad m => RefSrcPos -> RefExp -> R (Fun (Fun a (m b)) (Fun (m a) (m b))) Source #

(*=<<) :: Monad m => R (Fun a (m b)) -> R (m a) -> RefExp -> R (m b) Source #

gmaybe :: RefSrcPos -> RefExp -> R (Fun b (Fun (Fun a b) (Fun (Maybe a) b))) Source #

hmaybe :: R b -> R (Fun a b) -> R (Maybe a) -> RefExp -> R b Source #

geither :: RefSrcPos -> RefExp -> R (Fun (Fun a c) (Fun (Fun b c) (Fun (Either a b) c))) Source #

heither :: R (Fun a c) -> R (Fun b c) -> R (Either a b) -> RefExp -> R c Source #

gsubtract :: Num a => RefSrcPos -> RefExp -> R (Fun a (Fun a a)) Source #

heven :: Integral a => R a -> RefExp -> R Bool Source #

ggcd :: Integral a => RefSrcPos -> RefExp -> R (Fun a (Fun a a)) Source #

hgcd :: Integral a => R a -> R a -> RefExp -> R a Source #

glcm :: Integral a => RefSrcPos -> RefExp -> R (Fun a (Fun a a)) Source #

hlcm :: Integral a => R a -> R a -> RefExp -> R a Source #

(!^) :: (Num a, Integral b) => RefSrcPos -> RefExp -> R (Fun a (Fun b a)) Source #

(*^) :: (Num a, Integral b) => R a -> R b -> RefExp -> R a Source #

(!^^) :: (Fractional a, Integral b) => RefSrcPos -> RefExp -> R (Fun a (Fun b a)) Source #

(*^^) :: (Fractional a, Integral b) => R a -> R b -> RefExp -> R a Source #

gfst :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) a) Source #

hfst :: R (Tuple2 a b) -> RefExp -> R a Source #

gsnd :: RefSrcPos -> RefExp -> R (Fun (Tuple2 a b) b) Source #

hsnd :: R (Tuple2 a b) -> RefExp -> R b Source #

gcurry :: RefSrcPos -> RefExp -> R (Fun (Fun (Tuple2 a b) c) (Fun a (Fun b c))) Source #

hcurry :: R (Fun (Tuple2 a b) c) -> R a -> R b -> RefExp -> R c Source #

guncurry :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun b c)) (Fun (Tuple2 a b) c)) Source #

huncurry :: R (Fun a (Fun b c)) -> R (Tuple2 a b) -> RefExp -> R c Source #

gid :: RefSrcPos -> RefExp -> R (Fun a a) Source #

hid :: R a -> RefExp -> R a Source #

gconst :: RefSrcPos -> RefExp -> R (Fun a (Fun b a)) Source #

hconst :: R a -> R b -> RefExp -> R a Source #

(!.) :: RefSrcPos -> RefExp -> R (Fun (Fun b c) (Fun (Fun a b) (Fun a c))) Source #

(*.) :: R (Fun b c) -> R (Fun a b) -> R a -> RefExp -> R c Source #

gflip :: RefSrcPos -> RefExp -> R (Fun (Fun a (Fun b c)) (Fun b (Fun a c))) Source #

hflip :: R (Fun a (Fun b c)) -> R b -> R a -> RefExp -> R c Source #

(!$) :: RefSrcPos -> RefExp -> R (Fun (Fun a b) (Fun a b)) Source #

(*$) :: R (Fun a b) -> R a -> RefExp -> R b Source #

guntil :: RefSrcPos -> RefExp -> R (Fun (Fun a Bool) (Fun (Fun a a) (Fun a a))) Source #

huntil :: R (Fun a Bool) -> R (Fun a a) -> R a -> RefExp -> R a Source #

gasTypeOf :: RefSrcPos -> RefExp -> R (Fun a (Fun a a)) Source #

gseq :: RefSrcPos -> RefExp -> R (Fun a (Fun b b)) Source #

hseq :: R a1 -> R a -> RefExp -> R a Source #

(!$!) :: RefSrcPos -> RefExp -> R (Fun (Fun a b) (Fun a b)) Source #

(*$!) :: R (Fun a b) -> R a -> RefExp -> R b Source #