1
1
module Prelude where
2
+ import Prim ()
2
3
infixr 9 >>>
3
4
infixr 9 <<<
4
5
infixr 0 $
5
6
infixl 0 #
6
7
infixr 6 :
7
8
infixl 4 <$>
8
9
infixl 4 <*>
9
- infixl 3 <|>
10
10
infixl 1 >>=
11
11
infixl 7 *
12
12
infixl 7 /
@@ -26,7 +26,8 @@ infixr 2 ||
26
26
infixr 3 &&
27
27
infixr 5 <>
28
28
infixr 5 ++
29
- data Ordering = LT | GT | EQ
29
+ newtype Unit = Unit { }
30
+ data Ordering = LT | GT | EQ
30
31
class Semigroup a where
31
32
(<>) :: a -> a -> a
32
33
class BoolLike b where
@@ -56,9 +57,6 @@ class Num a where
56
57
class (Prelude.Applicative m , Prelude.Bind m ) <= Monad m where
57
58
class (Prelude.Apply m ) <= Bind m where
58
59
(>>=) :: forall a b . m a -> (a -> m b ) -> m b
59
- class Alternative f where
60
- empty :: forall a . f a
61
- (<|>) :: forall a . f a -> f a -> f a
62
60
class (Prelude.Apply f ) <= Applicative f where
63
61
pure :: forall a . a -> f a
64
62
class (Prelude.Functor f ) <= Apply f where
@@ -71,38 +69,19 @@ class (Prelude.Semigroupoid a) <= Category a where
71
69
id :: forall t . a t t
72
70
class Semigroupoid a where
73
71
(<<<) :: forall b c d . a c d -> a b c -> a b d
72
+ foreign import unit :: Prelude.Unit
74
73
foreign import (++) :: forall s . (Prelude.Semigroup s ) => s -> s -> s
75
- foreign import concatString :: Prim.String -> Prim.String -> Prim.String
76
- foreign import boolNot :: Prim.Boolean -> Prim.Boolean
77
- foreign import boolOr :: Prim.Boolean -> Prim.Boolean -> Prim.Boolean
78
- foreign import boolAnd :: Prim.Boolean -> Prim.Boolean -> Prim.Boolean
79
- foreign import numComplement :: Prim.Number -> Prim.Number
80
- foreign import numXor :: Prim.Number -> Prim.Number -> Prim.Number
81
- foreign import numOr :: Prim.Number -> Prim.Number -> Prim.Number
82
- foreign import numAnd :: Prim.Number -> Prim.Number -> Prim.Number
83
- foreign import numZshr :: Prim.Number -> Prim.Number -> Prim.Number
84
- foreign import numShr :: Prim.Number -> Prim.Number -> Prim.Number
85
- foreign import numShl :: Prim.Number -> Prim.Number -> Prim.Number
86
- foreign import numCompare :: Prim.Number -> Prim.Number -> Prelude.Ordering
87
74
foreign import (>=) :: forall a . (Prelude.Ord a ) => a -> a -> Prim.Boolean
88
75
foreign import (<=) :: forall a . (Prelude.Ord a ) => a -> a -> Prim.Boolean
89
76
foreign import (>) :: forall a . (Prelude.Ord a ) => a -> a -> Prim.Boolean
90
77
foreign import (<) :: forall a . (Prelude.Ord a ) => a -> a -> Prim.Boolean
91
78
foreign import refIneq :: forall a . a -> a -> Prim.Boolean
92
79
foreign import refEq :: forall a . a -> a -> Prim.Boolean
93
- foreign import numNegate :: Prim.Number -> Prim.Number
94
- foreign import numMod :: Prim.Number -> Prim.Number -> Prim.Number
95
- foreign import numDiv :: Prim.Number -> Prim.Number -> Prim.Number
96
- foreign import numMul :: Prim.Number -> Prim.Number -> Prim.Number
97
- foreign import numSub :: Prim.Number -> Prim.Number -> Prim.Number
98
- foreign import numAdd :: Prim.Number -> Prim.Number -> Prim.Number
99
80
foreign import ap :: forall m a b . (Prelude.Monad m ) => m (a -> b ) -> m a -> m b
100
81
foreign import liftM1 :: forall m a b . (Prelude.Monad m ) => (a -> b ) -> m a -> m b
101
82
foreign import return :: forall m a . (Prelude.Monad m ) => a -> m a
102
83
foreign import liftA1 :: forall f a b . (Prelude.Applicative f ) => (a -> b ) -> f a -> f b
103
- foreign import showArrayImpl :: forall a . (a -> Prim.String ) -> [a ] -> Prim.String
104
- foreign import showNumberImpl :: Prim.Number -> Prim.String
105
- foreign import showStringImpl :: Prim.String -> Prim.String
84
+ foreign import void :: forall f a . (Prelude.Functor f ) => f a -> f Prelude.Unit
106
85
foreign import cons :: forall a . a -> [a ] -> [a ]
107
86
foreign import (:) :: forall a . a -> [a ] -> [a ]
108
87
foreign import (#) :: forall a b . a -> (a -> b ) -> b
@@ -113,40 +92,91 @@ foreign import const :: forall a b. a -> b -> a
113
92
foreign import flip :: forall a b c . (a -> b -> c ) -> b -> a -> c
114
93
foreign import instance semigroupoidArr :: Prelude.Semigroupoid Prim.Function
115
94
foreign import instance categoryArr :: Prelude.Category Prim.Function
95
+ foreign import instance showUnit :: Prelude.Show Prelude.Unit
116
96
foreign import instance showString :: Prelude.Show Prim.String
117
97
foreign import instance showBoolean :: Prelude.Show Prim.Boolean
118
98
foreign import instance showNumber :: Prelude.Show Prim.Number
119
99
foreign import instance showArray :: (Prelude.Show a ) => Prelude.Show [a ]
100
+ foreign import instance functorArr :: Prelude.Functor (Prim.Function r )
101
+ foreign import instance applyArr :: Prelude.Apply (Prim.Function r )
102
+ foreign import instance applicativeArr :: Prelude.Applicative (Prim.Function r )
103
+ foreign import instance bindArr :: Prelude.Bind (Prim.Function r )
104
+ foreign import instance monadArr :: Prelude.Monad (Prim.Function r )
120
105
foreign import instance numNumber :: Prelude.Num Prim.Number
106
+ foreign import instance eqUnit :: Prelude.Eq Prelude.Unit
121
107
foreign import instance eqString :: Prelude.Eq Prim.String
122
108
foreign import instance eqNumber :: Prelude.Eq Prim.Number
123
109
foreign import instance eqBoolean :: Prelude.Eq Prim.Boolean
124
110
foreign import instance eqArray :: (Prelude.Eq a ) => Prelude.Eq [a ]
125
111
foreign import instance eqOrdering :: Prelude.Eq Prelude.Ordering
126
112
foreign import instance showOrdering :: Prelude.Show Prelude.Ordering
113
+ foreign import instance ordUnit :: Prelude.Ord Prelude.Unit
114
+ foreign import instance ordBoolean :: Prelude.Ord Prim.Boolean
127
115
foreign import instance ordNumber :: Prelude.Ord Prim.Number
116
+ foreign import instance ordString :: Prelude.Ord Prim.String
117
+ foreign import instance ordArray :: (Prelude.Ord a ) => Prelude.Ord [a ]
128
118
foreign import instance bitsNumber :: Prelude.Bits Prim.Number
129
119
foreign import instance boolLikeBoolean :: Prelude.BoolLike Prim.Boolean
120
+ foreign import instance semigroupUnit :: Prelude.Semigroup Prelude.Unit
130
121
foreign import instance semigroupString :: Prelude.Semigroup Prim.String
122
+ foreign import instance semigroupArr :: (Prelude.Semigroup s' ) => Prelude.Semigroup (s -> s' )
131
123
module Prelude.Unsafe where
124
+ import Prim ()
132
125
import Prelude ()
133
126
foreign import unsafeIndex :: forall a . [a ] -> Prim.Number -> a
134
127
module Data.Function where
128
+ import Prim ()
135
129
import Prelude ()
130
+ foreign import data Fn10 :: * -> * -> * -> * -> * -> * -> * -> * -> * -> * -> * -> *
131
+ foreign import data Fn9 :: * -> * -> * -> * -> * -> * -> * -> * -> * -> * -> *
132
+ foreign import data Fn8 :: * -> * -> * -> * -> * -> * -> * -> * -> * -> *
133
+ foreign import data Fn7 :: * -> * -> * -> * -> * -> * -> * -> * -> *
134
+ foreign import data Fn6 :: * -> * -> * -> * -> * -> * -> * -> *
135
+ foreign import data Fn5 :: * -> * -> * -> * -> * -> * -> *
136
+ foreign import data Fn4 :: * -> * -> * -> * -> * -> *
137
+ foreign import data Fn3 :: * -> * -> * -> * -> *
138
+ foreign import data Fn2 :: * -> * -> * -> *
139
+ foreign import data Fn1 :: * -> * -> *
140
+ foreign import data Fn0 :: * -> *
141
+ foreign import runFn10 :: forall a b c d e f g h i j k . Data.Function.Fn10 a b c d e f g h i j k -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k
142
+ foreign import runFn9 :: forall a b c d e f g h i j . Data.Function.Fn9 a b c d e f g h i j -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j
143
+ foreign import runFn8 :: forall a b c d e f g h i . Data.Function.Fn8 a b c d e f g h i -> a -> b -> c -> d -> e -> f -> g -> h -> i
144
+ foreign import runFn7 :: forall a b c d e f g h . Data.Function.Fn7 a b c d e f g h -> a -> b -> c -> d -> e -> f -> g -> h
145
+ foreign import runFn6 :: forall a b c d e f g . Data.Function.Fn6 a b c d e f g -> a -> b -> c -> d -> e -> f -> g
146
+ foreign import runFn5 :: forall a b c d e f . Data.Function.Fn5 a b c d e f -> a -> b -> c -> d -> e -> f
147
+ foreign import runFn4 :: forall a b c d e . Data.Function.Fn4 a b c d e -> a -> b -> c -> d -> e
148
+ foreign import runFn3 :: forall a b c d . Data.Function.Fn3 a b c d -> a -> b -> c -> d
149
+ foreign import runFn2 :: forall a b c . Data.Function.Fn2 a b c -> a -> b -> c
150
+ foreign import runFn1 :: forall a b . Data.Function.Fn1 a b -> a -> b
151
+ foreign import runFn0 :: forall a . Data.Function.Fn0 a -> a
152
+ foreign import mkFn10 :: forall a b c d e f g h i j k . (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k ) -> Data.Function.Fn10 a b c d e f g h i j k
153
+ foreign import mkFn9 :: forall a b c d e f g h i j . (a -> b -> c -> d -> e -> f -> g -> h -> i -> j ) -> Data.Function.Fn9 a b c d e f g h i j
154
+ foreign import mkFn8 :: forall a b c d e f g h i . (a -> b -> c -> d -> e -> f -> g -> h -> i ) -> Data.Function.Fn8 a b c d e f g h i
155
+ foreign import mkFn7 :: forall a b c d e f g h . (a -> b -> c -> d -> e -> f -> g -> h ) -> Data.Function.Fn7 a b c d e f g h
156
+ foreign import mkFn6 :: forall a b c d e f g . (a -> b -> c -> d -> e -> f -> g ) -> Data.Function.Fn6 a b c d e f g
157
+ foreign import mkFn5 :: forall a b c d e f . (a -> b -> c -> d -> e -> f ) -> Data.Function.Fn5 a b c d e f
158
+ foreign import mkFn4 :: forall a b c d e . (a -> b -> c -> d -> e ) -> Data.Function.Fn4 a b c d e
159
+ foreign import mkFn3 :: forall a b c d . (a -> b -> c -> d ) -> Data.Function.Fn3 a b c d
160
+ foreign import mkFn2 :: forall a b c . (a -> b -> c ) -> Data.Function.Fn2 a b c
161
+ foreign import mkFn1 :: forall a b . (a -> b ) -> Data.Function.Fn1 a b
162
+ foreign import mkFn0 :: forall a . (Prelude.Unit -> a ) -> Data.Function.Fn0 a
136
163
foreign import on :: forall a b c . (b -> b -> c ) -> (a -> b ) -> a -> a -> c
137
164
module Data.Eq where
165
+ import Prim ()
138
166
import Prelude ()
139
- data Ref a = Ref a
167
+ newtype Ref ( a :: *) = Ref a
140
168
foreign import liftRef :: forall a b . (a -> a -> b ) -> Data.Eq.Ref a -> Data.Eq.Ref a -> b
141
169
foreign import instance eqRef :: Prelude.Eq (Data.Eq.Ref a )
170
+ foreign import instance functorRef :: Prelude.Functor Data.Eq.Ref
142
171
module Control.Monad.Eff where
172
+ import Prim ()
143
173
import Prelude ()
144
- type Pure a = forall e . Control.Monad.Eff.Eff e a
174
+ type Pure ( a :: *) = forall e . Control.Monad.Eff.Eff e a
145
175
foreign import data Eff :: # ! -> * -> *
146
- foreign import foreachE :: forall e a . [a ] -> (a -> Control.Monad.Eff.Eff e { } ) -> Control.Monad.Eff.Eff e { }
147
- foreign import forE :: forall e . Prim.Number -> Prim.Number -> (Prim.Number -> Control.Monad.Eff.Eff e { } ) -> Control.Monad.Eff.Eff e { }
148
- foreign import whileE :: forall e a . Control.Monad.Eff.Eff e Prim.Boolean -> Control.Monad.Eff.Eff e a -> Control.Monad.Eff.Eff e { }
149
- foreign import untilE :: forall e . Control.Monad.Eff.Eff e Prim.Boolean -> Control.Monad.Eff.Eff e { }
176
+ foreign import foreachE :: forall e a . [a ] -> (a -> Control.Monad.Eff.Eff e Prelude.Unit ) -> Control.Monad.Eff.Eff e Prelude.Unit
177
+ foreign import forE :: forall e . Prim.Number -> Prim.Number -> (Prim.Number -> Control.Monad.Eff.Eff e Prelude.Unit ) -> Control.Monad.Eff.Eff e Prelude.Unit
178
+ foreign import whileE :: forall e a . Control.Monad.Eff.Eff e Prim.Boolean -> Control.Monad.Eff.Eff e a -> Control.Monad.Eff.Eff e Prelude.Unit
179
+ foreign import untilE :: forall e . Control.Monad.Eff.Eff e Prim.Boolean -> Control.Monad.Eff.Eff e Prelude.Unit
150
180
foreign import runPure :: forall a . Control.Monad.Eff.Pure a -> a
151
181
foreign import bindE :: forall e a b . Control.Monad.Eff.Eff e a -> (a -> Control.Monad.Eff.Eff e b ) -> Control.Monad.Eff.Eff e b
152
182
foreign import returnE :: forall e a . a -> Control.Monad.Eff.Eff e a
@@ -156,10 +186,12 @@ foreign import instance applicativeEff :: Prelude.Applicative (Control.Monad.Eff
156
186
foreign import instance bindEff :: Prelude.Bind (Control.Monad.Eff.Eff e )
157
187
foreign import instance monadEff :: Prelude.Monad (Control.Monad.Eff.Eff e )
158
188
module Control.Monad.Eff.Unsafe where
189
+ import Prim ()
159
190
import Prelude ()
160
191
import Control.Monad.Eff ()
161
192
foreign import unsafeInterleaveEff :: forall eff1 eff2 a . Control.Monad.Eff.Eff eff1 a -> Control.Monad.Eff.Eff eff2 a
162
193
module Control.Monad.ST where
194
+ import Prim ()
163
195
import Prelude ()
164
196
import Control.Monad.Eff ()
165
197
foreign import data STArray :: * -> * -> *
@@ -168,15 +200,16 @@ foreign import data ST :: * -> !
168
200
foreign import runSTArray :: forall a r . (forall h . Control.Monad.Eff.Eff (st :: Control.Monad.ST.ST h | r ) (Control.Monad.ST.STArray h a )) -> Control.Monad.Eff.Eff r [a ]
169
201
foreign import runST :: forall a r . (forall h . Control.Monad.Eff.Eff (st :: Control.Monad.ST.ST h | r ) a ) -> Control.Monad.Eff.Eff r a
170
202
foreign import pokeSTArray :: forall a h r . Control.Monad.ST.STArray h a -> Prim.Number -> a -> Control.Monad.Eff.Eff (st :: Control.Monad.ST.ST h | r ) a
171
- foreign import peekSTArray :: forall a h r . Control.Monad.ST.STArray h a -> Control.Monad.Eff.Eff (st :: Control.Monad.ST.ST h | r ) a
203
+ foreign import peekSTArray :: forall a h r . Control.Monad.ST.STArray h a -> Prim.Number -> Control.Monad.Eff.Eff (st :: Control.Monad.ST.ST h | r ) a
172
204
foreign import newSTArray :: forall a h r . Prim.Number -> a -> Control.Monad.Eff.Eff (st :: Control.Monad.ST.ST h | r ) (Control.Monad.ST.STArray h a )
173
205
foreign import writeSTRef :: forall a h r . Control.Monad.ST.STRef h a -> a -> Control.Monad.Eff.Eff (st :: Control.Monad.ST.ST h | r ) a
174
206
foreign import modifySTRef :: forall a h r . Control.Monad.ST.STRef h a -> (a -> a ) -> Control.Monad.Eff.Eff (st :: Control.Monad.ST.ST h | r ) a
175
207
foreign import readSTRef :: forall a h r . Control.Monad.ST.STRef h a -> Control.Monad.Eff.Eff (st :: Control.Monad.ST.ST h | r ) a
176
208
foreign import newSTRef :: forall a h r . a -> Control.Monad.Eff.Eff (st :: Control.Monad.ST.ST h | r ) (Control.Monad.ST.STRef h a )
177
209
module Debug.Trace where
210
+ import Prim ()
178
211
import Prelude ()
179
212
import Control.Monad.Eff ()
180
213
foreign import data Trace :: !
181
- foreign import print :: forall a r . (Prelude.Show a ) => a -> Control.Monad.Eff.Eff (trace :: Debug.Trace.Trace | r ) { }
182
- foreign import trace :: forall r . Prim.String -> Control.Monad.Eff.Eff (trace :: Debug.Trace.Trace | r ) { }
214
+ foreign import print :: forall a r . (Prelude.Show a ) => a -> Control.Monad.Eff.Eff (trace :: Debug.Trace.Trace | r ) Prelude.Unit
215
+ foreign import trace :: forall r . Prim.String -> Control.Monad.Eff.Eff (trace :: Debug.Trace.Trace | r ) Prelude.Unit
0 commit comments