summaryrefslogtreecommitdiff
path: root/compiler/GHC/Core.hs
blob: 1c45e8de9b593022f003ecac349a1101c2c0b74e (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
1001
1002
1003
1004
1005
1006
1007
1008
1009
1010
1011
1012
1013
1014
1015
1016
1017
1018
1019
1020
1021
1022
1023
1024
1025
1026
1027
1028
1029
1030
1031
1032
1033
1034
1035
1036
1037
1038
1039
1040
1041
1042
1043
1044
1045
1046
1047
1048
1049
1050
1051
1052
1053
1054
1055
1056
1057
1058
1059
1060
1061
1062
1063
1064
1065
1066
1067
1068
1069
1070
1071
1072
1073
1074
1075
1076
1077
1078
1079
1080
1081
1082
1083
1084
1085
1086
1087
1088
1089
1090
1091
1092
1093
1094
1095
1096
1097
1098
1099
1100
1101
1102
1103
1104
1105
1106
1107
1108
1109
1110
1111
1112
1113
1114
1115
1116
1117
1118
1119
1120
1121
1122
1123
1124
1125
1126
1127
1128
1129
1130
1131
1132
1133
1134
1135
1136
1137
1138
1139
1140
1141
1142
1143
1144
1145
1146
1147
1148
1149
1150
1151
1152
1153
1154
1155
1156
1157
1158
1159
1160
1161
1162
1163
1164
1165
1166
1167
1168
1169
1170
1171
1172
1173
1174
1175
1176
1177
1178
1179
1180
1181
1182
1183
1184
1185
1186
1187
1188
1189
1190
1191
1192
1193
1194
1195
1196
1197
1198
1199
1200
1201
1202
1203
1204
1205
1206
1207
1208
1209
1210
1211
1212
1213
1214
1215
1216
1217
1218
1219
1220
1221
1222
1223
1224
1225
1226
1227
1228
1229
1230
1231
1232
1233
1234
1235
1236
1237
1238
1239
1240
1241
1242
1243
1244
1245
1246
1247
1248
1249
1250
1251
1252
1253
1254
1255
1256
1257
1258
1259
1260
1261
1262
1263
1264
1265
1266
1267
1268
1269
1270
1271
1272
1273
1274
1275
1276
1277
1278
1279
1280
1281
1282
1283
1284
1285
1286
1287
1288
1289
1290
1291
1292
1293
1294
1295
1296
1297
1298
1299
1300
1301
1302
1303
1304
1305
1306
1307
1308
1309
1310
1311
1312
1313
1314
1315
1316
1317
1318
1319
1320
1321
1322
1323
1324
1325
1326
1327
1328
1329
1330
1331
1332
1333
1334
1335
1336
1337
1338
1339
1340
1341
1342
1343
1344
1345
1346
1347
1348
1349
1350
1351
1352
1353
1354
1355
1356
1357
1358
1359
1360
1361
1362
1363
1364
1365
1366
1367
1368
1369
1370
1371
1372
1373
1374
1375
1376
1377
1378
1379
1380
1381
1382
1383
1384
1385
1386
1387
1388
1389
1390
1391
1392
1393
1394
1395
1396
1397
1398
1399
1400
1401
1402
1403
1404
1405
1406
1407
1408
1409
1410
1411
1412
1413
1414
1415
1416
1417
1418
1419
1420
1421
1422
1423
1424
1425
1426
1427
1428
1429
1430
1431
1432
1433
1434
{-
(c) The University of Glasgow 2006
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
-}

{-# LANGUAGE DeriveDataTypeable, FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE BangPatterns #-}

-- | GHC.Core holds all the main data types for use by for the Glasgow Haskell Compiler midsection
module GHC.Core (
        -- * Main data types
        Expr(..), Alt(..), Bind(..), AltCon(..), Arg,
        CoreProgram, CoreExpr, CoreAlt, CoreBind, CoreArg, CoreBndr,
        TaggedExpr, TaggedAlt, TaggedBind, TaggedArg, TaggedBndr(..), deTagExpr,

        -- * In/Out type synonyms
        InId, InBind, InExpr, InAlt, InArg, InType, InKind,
               InBndr, InVar, InCoercion, InTyVar, InCoVar,
        OutId, OutBind, OutExpr, OutAlt, OutArg, OutType, OutKind,
               OutBndr, OutVar, OutCoercion, OutTyVar, OutCoVar, MOutCoercion,

        -- ** 'Expr' construction
        mkLet, mkLets, mkLetNonRec, mkLetRec, mkLams,
        mkApps, mkTyApps, mkCoApps, mkVarApps, mkTyArg,

        mkIntLit, mkIntLitWrap,
        mkWordLit, mkWordLitWrap,
        mkWord8Lit,
        mkWord64LitWord64, mkInt64LitInt64,
        mkCharLit, mkStringLit,
        mkFloatLit, mkFloatLitFloat,
        mkDoubleLit, mkDoubleLitDouble,

        mkConApp, mkConApp2, mkTyBind, mkCoBind,
        varToCoreExpr, varsToCoreExprs,

        isId, cmpAltCon, cmpAlt, ltAlt,

        -- ** Simple 'Expr' access functions and predicates
        bindersOf, bindersOfBinds, rhssOfBind, rhssOfAlts,
        foldBindersOfBindStrict, foldBindersOfBindsStrict,
        collectBinders, collectTyBinders, collectTyAndValBinders,
        collectNBinders, collectNValBinders_maybe,
        collectArgs, stripNArgs, collectArgsTicks, flattenBinds,
        collectFunSimple,

        exprToType,
        wrapLamBody,

        isValArg, isTypeArg, isCoArg, isTyCoArg, valArgCount, valBndrCount,
        isRuntimeArg, isRuntimeVar,
    ) where

import GHC.Prelude
import GHC.Platform

import GHC.Types.Var
import GHC.Core.Type
import GHC.Core.Coercion
import GHC.Types.Literal
import GHC.Types.Tickish
import GHC.Core.DataCon
import GHC.Types.Basic (Arity, JoinArity)

import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Panic.Plain

import Data.Data hiding (TyCon)
import Data.Int
import Data.Word

infixl 4 `mkApps`, `mkTyApps`, `mkVarApps`, `App`, `mkCoApps`
-- Left associative, so that we can say (f `mkTyApps` xs `mkVarApps` ys)

{-
************************************************************************
*                                                                      *
\subsection{The main data types}
*                                                                      *
************************************************************************

These data types are the heart of the compiler
-}

-- | This is the data type that represents GHCs core intermediate language. Currently
-- GHC uses System FC <https://www.microsoft.com/en-us/research/publication/system-f-with-type-equality-coercions/> for this purpose,
-- which is closely related to the simpler and better known System F <http://en.wikipedia.org/wiki/System_F>.
--
-- We get from Haskell source to this Core language in a number of stages:
--
-- 1. The source code is parsed into an abstract syntax tree, which is represented
--    by the data type 'GHC.Hs.Expr.HsExpr' with the names being 'GHC.Types.Name.Reader.RdrNames'
--
-- 2. This syntax tree is /renamed/, which attaches a 'GHC.Types.Unique.Unique' to every 'GHC.Types.Name.Reader.RdrName'
--    (yielding a 'GHC.Types.Name.Name') to disambiguate identifiers which are lexically identical.
--    For example, this program:
--
-- @
--      f x = let f x = x + 1
--            in f (x - 2)
-- @
--
--    Would be renamed by having 'Unique's attached so it looked something like this:
--
-- @
--      f_1 x_2 = let f_3 x_4 = x_4 + 1
--                in f_3 (x_2 - 2)
-- @
--    But see Note [Shadowing] below.
--
-- 3. The resulting syntax tree undergoes type checking (which also deals with instantiating
--    type class arguments) to yield a 'GHC.Hs.Expr.HsExpr' type that has 'GHC.Types.Id.Id' as it's names.
--
-- 4. Finally the syntax tree is /desugared/ from the expressive 'GHC.Hs.Expr.HsExpr' type into
--    this 'Expr' type, which has far fewer constructors and hence is easier to perform
--    optimization, analysis and code generation on.
--
-- The type parameter @b@ is for the type of binders in the expression tree.
--
-- The language consists of the following elements:
--
-- *  Variables
--    See Note [Variable occurrences in Core]
--
-- *  Primitive literals
--
-- *  Applications: note that the argument may be a 'Type'.
--    See Note [Representation polymorphism invariants]
--
-- *  Lambda abstraction
--    See Note [Representation polymorphism invariants]
--
-- *  Recursive and non recursive @let@s. Operationally
--    this corresponds to allocating a thunk for the things
--    bound and then executing the sub-expression.
--
--    See Note [Core letrec invariant]
--    See Note [Core let-can-float invariant]
--    See Note [Representation polymorphism invariants]
--    See Note [Core type and coercion invariant]
--
-- *  Case expression. Operationally this corresponds to evaluating
--    the scrutinee (expression examined) to weak head normal form
--    and then examining at most one level of resulting constructor (i.e. you
--    cannot do nested pattern matching directly with this).
--
--    The binder gets bound to the value of the scrutinee,
--    and the 'Type' must be that of all the case alternatives
--
--    IMPORTANT: see Note [Case expression invariants]
--
-- *  Cast an expression to a particular type.
--    This is used to implement @newtype@s (a @newtype@ constructor or
--    destructor just becomes a 'Cast' in Core) and GADTs.
--
-- *  Ticks. These are used to represent all the source annotation we
--    support: profiling SCCs, HPC ticks, and GHCi breakpoints.
--
-- *  A type: this should only show up at the top level of an Arg
--
-- *  A coercion

{- Note [Why does Case have a 'Type' field?]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The obvious alternative is
   exprType (Case scrut bndr alts)
     | (_,_,rhs1):_ <- alts
     = exprType rhs1

But caching the type in the Case constructor
  exprType (Case scrut bndr ty alts) = ty
is better for at least three reasons:

* It works when there are no alternatives (see case invariant 1 above)

* It might be faster in deeply-nested situations.

* It might not be quite the same as (exprType rhs) for one
  of the RHSs in alts. Consider a phantom type synonym
       type S a = Int
   and we want to form the case expression
        case x of { K (a::*) -> (e :: S a) }
   Then exprType of the RHS is (S a), but we cannot make that be
   the 'ty' in the Case constructor because 'a' is simply not in
   scope there. Instead we must expand the synonym to Int before
   putting it in the Case constructor.  See GHC.Core.Utils.mkSingleAltCase.

   So we'd have to do synonym expansion in exprType which would
   be inefficient.

* The type stored in the case is checked with lintInTy. This checks
  (among other things) that it does not mention any variables that are
  not in scope. If we did not have the type there, it would be a bit
  harder for Core Lint to reject case blah of Ex x -> x where
      data Ex = forall a. Ex a.
-}

-- If you edit this type, you may need to update the GHC formalism
-- See Note [GHC Formalism] in GHC.Core.Lint
data Expr b
  = Var   Id
  | Lit   Literal
  | App   (Expr b) (Arg b)
  | Lam   b (Expr b)
  | Let   (Bind b) (Expr b)
  | Case  (Expr b) b Type [Alt b]   -- See Note [Case expression invariants]
                                    -- and Note [Why does Case have a 'Type' field?]
  | Cast  (Expr b) CoercionR        -- The Coercion has Representational role
  | Tick  CoreTickish (Expr b)
  | Type  Type
  | Coercion Coercion
  deriving Data

-- | Type synonym for expressions that occur in function argument positions.
-- Only 'Arg' should contain a 'Type' at top level, general 'Expr' should not
type Arg b = Expr b

-- | A case split alternative. Consists of the constructor leading to the alternative,
-- the variables bound from the constructor, and the expression to be executed given that binding.
-- The default alternative is @(DEFAULT, [], rhs)@

-- If you edit this type, you may need to update the GHC formalism
-- See Note [GHC Formalism] in GHC.Core.Lint
data Alt b
    = Alt AltCon [b] (Expr b)
    deriving (Data)

-- | A case alternative constructor (i.e. pattern match)

-- If you edit this type, you may need to update the GHC formalism
-- See Note [GHC Formalism] in GHC.Core.Lint
data AltCon
  = DataAlt DataCon   --  ^ A plain data constructor: @case e of { Foo x -> ... }@.
                      -- Invariant: the 'DataCon' is always from a @data@ type, and never from a @newtype@

  | LitAlt  Literal   -- ^ A literal: @case e of { 1 -> ... }@
                      -- Invariant: always an *unlifted* literal
                      -- See Note [Literal alternatives]

  | DEFAULT           -- ^ Trivial alternative: @case e of { _ -> ... }@
   deriving (Eq, Data)

-- This instance is a bit shady. It can only be used to compare AltCons for
-- a single type constructor. Fortunately, it seems quite unlikely that we'll
-- ever need to compare AltCons for different type constructors.
-- The instance adheres to the order described in [Core case invariants]
instance Ord AltCon where
  compare (DataAlt con1) (DataAlt con2) =
    assert (dataConTyCon con1 == dataConTyCon con2) $
    compare (dataConTag con1) (dataConTag con2)
  compare (DataAlt _) _ = GT
  compare _ (DataAlt _) = LT
  compare (LitAlt l1) (LitAlt l2) = compare l1 l2
  compare (LitAlt _) DEFAULT = GT
  compare DEFAULT DEFAULT = EQ
  compare DEFAULT _ = LT

-- | Binding, used for top level bindings in a module and local bindings in a @let@.

-- If you edit this type, you may need to update the GHC formalism
-- See Note [GHC Formalism] in GHC.Core.Lint
data Bind b = NonRec b (Expr b)
            | Rec [(b, (Expr b))]
  deriving Data

{-
Note [Shadowing]
~~~~~~~~~~~~~~~~
While various passes attempt to rename on-the-fly in a manner that
avoids "shadowing" (thereby simplifying downstream optimizations),
neither the simplifier nor any other pass GUARANTEES that shadowing is
avoided. Thus, all passes SHOULD work fine even in the presence of
arbitrary shadowing in their inputs.

In particular, scrutinee variables `x` in expressions of the form
`Case e x t` are often renamed to variables with a prefix
"wild_". These "wild" variables may appear in the body of the
case-expression, and further, may be shadowed within the body.

So the Unique in a Var is not really unique at all.  Still, it's very
useful to give a constant-time equality/ordering for Vars, and to give
a key that can be used to make sets of Vars (VarSet), or mappings from
Vars to other things (VarEnv).   Moreover, if you do want to eliminate
shadowing, you can give a new Unique to an Id without changing its
printable name, which makes debugging easier.

Note [Literal alternatives]
~~~~~~~~~~~~~~~~~~~~~~~~~~~
Literal alternatives (LitAlt lit) are always for *un-lifted* literals.
We have one literal, a literal Integer, that is lifted, and we don't
allow in a LitAlt, because LitAlt cases don't do any evaluation. Also
(see #5603) if you say
    case 3 of
      IS x -> ...
      IP _ -> ...
      IN _ -> ...
(where IS, IP, IN are the constructors for Integer) we don't want the
simplifier calling findAlt with argument (LitAlt 3).  No no.  Integer
literals are an opaque encoding of an algebraic data type, not of
an unlifted literal, like all the others.

Also, we do not permit case analysis with literal patterns on floating-point
types. See #9238 and Note [Rules for floating-point comparisons] in
GHC.Core.Opt.ConstantFold for the rationale for this restriction.

-------------------------- GHC.Core INVARIANTS ---------------------------

Note [Variable occurrences in Core]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Variable /occurrences/ are never CoVars, though /bindings/ can be.
All CoVars appear in Coercions.

For example
  \(c :: Age~#Int) (d::Int). d |> (sym c)
Here 'c' is a CoVar, which is lambda-bound, but it /occurs/ in
a Coercion, (sym c).

Note [Core letrec invariant]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The right hand sides of all top-level and recursive @let@s
/must/ be of lifted type (see "Type#type_classification" for
the meaning of /lifted/ vs. /unlifted/).

There is one exception to this rule, top-level @let@s are
allowed to bind primitive string literals: see
Note [Core top-level string literals].

Note [Core top-level string literals]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
As an exception to the usual rule that top-level binders must be lifted,
we allow binding primitive string literals (of type Addr#) of type Addr# at the
top level. This allows us to share string literals earlier in the pipeline and
crucially allows other optimizations in the Core2Core pipeline to fire.
Consider,

  f n = let a::Addr# = "foo"#
        in \x -> blah

In order to be able to inline `f`, we would like to float `a` to the top.
Another option would be to inline `a`, but that would lead to duplicating string
literals, which we want to avoid. See #8472.

The solution is simply to allow top-level unlifted binders. We can't allow
arbitrary unlifted expression at the top-level though, unlifted binders cannot
be thunks, so we just allow string literals.

We allow the top-level primitive string literals to be wrapped in Ticks
in the same way they can be wrapped when nested in an expression.
CoreToSTG currently discards Ticks around top-level primitive string literals.
See #14779.

Also see Note [Compilation plan for top-level string literals].

Note [Compilation plan for top-level string literals]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Here is a summary on how top-level string literals are handled by various
parts of the compilation pipeline.

* In the source language, there is no way to bind a primitive string literal
  at the top level.

* In Core, we have a special rule that permits top-level Addr# bindings. See
  Note [Core top-level string literals]. Core-to-core passes may introduce
  new top-level string literals.

* In STG, top-level string literals are explicitly represented in the syntax
  tree.

* A top-level string literal may end up exported from a module. In this case,
  in the object file, the content of the exported literal is given a label with
  the _bytes suffix.

Note [Core let-can-float invariant]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The let-can-float invariant:

    The right hand side of a non-recursive 'Let'
    /may/ be of unlifted type, but only if
    the expression is ok-for-speculation
    or the 'Let' is for a join point.

This means that the let can be floated around
without difficulty. For example, this is OK:

   y::Int# = x +# 1#

But this is not, as it may affect termination if the
expression is floated out:

   y::Int# = fac 4#

In this situation you should use @case@ rather than a @let@. The function
'GHC.Core.Utils.needsCaseBinding' can help you determine which to generate, or
alternatively use 'GHC.Core.Make.mkCoreLet' rather than this constructor directly,
which will generate a @case@ if necessary

The let-can-float invariant is initially enforced by mkCoreLet in GHC.Core.Make.

For discussion of some implications of the let-can-float invariant primops see
Note [Checking versus non-checking primops] in GHC.Builtin.PrimOps.

Historical Note [The let/app invariant]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Before 2022 GHC used the "let/app invariant", which applied the let-can-float rules
to the argument of an application, as well as to the RHS of a let.  This made some
kind of sense, because 'let' can always be encoded as application:
   let x=rhs in b   =    (\x.b) rhs

But the let/app invariant got in the way of RULES; see #19313.  For example
  up :: Int# -> Int#
  {-# RULES "up/down" forall x. up (down x) = x #-}
The LHS of this rule doesn't satisfy the let/app invariant.

Indeed RULES is a big reason that GHC doesn't use ANF, where the argument of an
application is always a variable or a constant.  To allow RULES to work nicely
we need to allow lots of things in the arguments of a call.

TL;DR: we relaxed the let/app invariant to become the let-can-float invariant.

Note [Case expression invariants]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Case expressions are one of the more complicated elements of the Core
language, and come with a number of invariants.  All of them should be
checked by Core Lint.

1. The list of alternatives may be empty;
   See Note [Empty case alternatives]

2. The 'DEFAULT' case alternative must be first in the list,
   if it occurs at all.  Checked in GHC.Core.Lint.checkCaseAlts.

3. The remaining cases are in order of (strictly) increasing
     tag  (for 'DataAlts') or
     lit  (for 'LitAlts').
   This makes finding the relevant constructor easy, and makes
   comparison easier too.   Checked in GHC.Core.Lint.checkCaseAlts.

4. The list of alternatives must be exhaustive. An /exhaustive/ case
   does not necessarily mention all constructors:

   @
        data Foo = Red | Green | Blue
        ... case x of
              Red   -> True
              other -> f (case x of
                              Green -> ...
                              Blue  -> ... ) ...
   @

   The inner case does not need a @Red@ alternative, because @x@
   can't be @Red@ at that program point.

   This is not checked by Core Lint -- it's very hard to do so.
   E.g. suppose that inner case was floated out, thus:
         let a = case x of
                   Green -> ...
                   Blue  -> ... )
         case x of
           Red   -> True
           other -> f a
   Now it's really hard to see that the Green/Blue case is
   exhaustive.  But it is.

   If you have a case-expression that really /isn't/ exhaustive,
   we may generate seg-faults.  Consider the Green/Blue case
   above.  Since there are only two branches we may generate
   code that tests for Green, and if not Green simply /assumes/
   Blue (since, if the case is exhaustive, that's all that
   remains).  Of course, if it's not Blue and we start fetching
   fields that should be in a Blue constructor, we may die
   horribly. See also Note [Core Lint guarantee] in GHC.Core.Lint.

5. Floating-point values must not be scrutinised against literals.
   See #9238 and Note [Rules for floating-point comparisons]
   in GHC.Core.Opt.ConstantFold for rationale.  Checked in lintCaseExpr;
   see the call to isFloatingPrimTy.

6. The 'ty' field of (Case scrut bndr ty alts) is the type of the
   /entire/ case expression.  Checked in lintAltExpr.
   See also Note [Why does Case have a 'Type' field?].

7. The type of the scrutinee must be the same as the type
   of the case binder, obviously.  Checked in lintCaseExpr.

8. The multiplicity of the binders in constructor patterns must be the
   multiplicity of the corresponding field /scaled by the multiplicity of the
   case binder/. Checked in lintCoreAlt.

Note [Core type and coercion invariant]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We allow a /non-recursive/, /non-top-level/ let to bind type and
coercion variables.  These can be very convenient for postponing type
substitutions until the next run of the simplifier.

* A type variable binding must have a RHS of (Type ty)

* A coercion variable binding must have a RHS of (Coercion co)

  It is possible to have terms that return a coercion, but we use
  case-binding for those; e.g.
     case (eq_sel d) of (co :: a ~# b) -> blah
  where eq_sel :: (a~b) -> (a~#b)

  Or even
      case (df @Int) of (co :: a ~# b) -> blah
  Which is very exotic, and I think never encountered; but see
  Note [Equality superclasses in quantified constraints]
  in GHC.Tc.Solver.Canonical

Note [Core case invariants]
~~~~~~~~~~~~~~~~~~~~~~~~~~~
See Note [Case expression invariants]

Note [Representation polymorphism invariants]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
GHC allows us to abstract over calling conventions using **representation polymorphism**.
For example, we have:

  ($) :: forall (r :: RuntimeRep) (a :: Type) (b :: TYPE r). a -> b -> b

In this example, the type `b` is representation-polymorphic: it has kind `TYPE r`,
where the type variable `r :: RuntimeRep` abstracts over the runtime representation
of values of type `b`.

To ensure that programs containing representation-polymorphism remain compilable,
we enforce the following representation-polymorphism invariants:

The paper "Levity Polymorphism" [PLDI'17] states the first two invariants:

  I1. The type of a bound variable must have a fixed runtime representation
      (except for join points: See Note [Invariants on join points])
  I2. The type of a function argument must have a fixed runtime representation.

On top of these two invariants, GHC's internal eta-expansion mechanism also requires:

  I3. In any partial application `f e_1 .. e_n`, where `f` is `hasNoBinding`,
      it must be the case that the application can be eta-expanded to match
      the arity of `f`.
      See Note [checkCanEtaExpand] in GHC.Core.Lint for more details.

Example of I1:

  \(r::RuntimeRep). \(a::TYPE r). \(x::a). e

    This contravenes I1 because x's type has kind (TYPE r), which has 'r' free.
    We thus wouldn't know how to compile this lambda abstraction.

Example of I2:

  f (undefined :: (a :: TYPE r))

    This contravenes I2: we are applying the function `f` to a value
    with an unknown runtime representation.

Examples of I3:

  myUnsafeCoerce# :: forall {r1} (a :: TYPE r1) {r2} (b :: TYPE r2). a -> b
  myUnsafeCoerce# = unsafeCoerce#

    This contravenes I3: we are instantiating `unsafeCoerce#` without any
    value arguments, and with a remaining argument type, `a`, which does not
    have a fixed runtime representation.
    But `unsafeCorce#` has no binding (see Note [Wiring in unsafeCoerce#]
    in GHC.HsToCore).  So before code-generation we must saturate it
    by eta-expansion (see GHC.CoreToStg.Prep.maybeSaturate), thus
       myUnsafeCoerce# = \x. unsafeCoerce# x
    But we can't do that because now the \x binding would violate I1.

  bar :: forall (a :: TYPE) r (b :: TYPE r). a -> b
  bar = unsafeCoerce#

    OK: eta expand to `\ (x :: Type) -> unsafeCoerce# x`,
    and `x` has a fixed RuntimeRep.

Note that we currently require something slightly stronger than a fixed runtime
representation: we check whether bound variables and function arguments have a
/fixed RuntimeRep/ in the sense of Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete.
See Note [Representation polymorphism checking] in GHC.Tc.Utils.Concrete
for an overview of how we enforce these invariants in the typechecker.

Note [Core let goal]
~~~~~~~~~~~~~~~~~~~~
* The simplifier tries to ensure that if the RHS of a let is a constructor
  application, its arguments are trivial, so that the constructor can be
  inlined vigorously.

Note [Empty case alternatives]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The alternatives of a case expression should be exhaustive.  But
this exhaustive list can be empty!

* A case expression can have empty alternatives if (and only if) the
  scrutinee is bound to raise an exception or diverge. When do we know
  this?  See Note [Bottoming expressions] in GHC.Core.Utils.

* The possibility of empty alternatives is one reason we need a type on
  the case expression: if the alternatives are empty we can't get the
  type from the alternatives!

* In the case of empty types (see Note [Bottoming expressions]), say
    data T
  we do NOT want to replace
    case (x::T) of Bool {}   -->   error Bool "Inaccessible case"
  because x might raise an exception, and *that*'s what we want to see!
  (#6067 is an example.) To preserve semantics we'd have to say
     x `seq` error Bool "Inaccessible case"
  but the 'seq' is just such a case, so we are back to square 1.

* We can use the empty-alternative construct to coerce error values from
  one type to another.  For example

    f :: Int -> Int
    f n = error "urk"

    g :: Int -> (# Char, Bool #)
    g x = case f x of { 0 -> ..., n -> ... }

  Then if we inline f in g's RHS we get
    case (error Int "urk") of (# Char, Bool #) { ... }
  and we can discard the alternatives since the scrutinee is bottom to give
    case (error Int "urk") of (# Char, Bool #) {}

  This is nicer than using an unsafe coerce between Int ~ (# Char,Bool #),
  if for no other reason that we don't need to instantiate the (~) at an
  unboxed type.

* We treat a case expression with empty alternatives as trivial iff
  its scrutinee is (see GHC.Core.Utils.exprIsTrivial).  This is actually
  important; see Note [Empty case is trivial] in GHC.Core.Utils

* An empty case is replaced by its scrutinee during the CoreToStg
  conversion; remember STG is un-typed, so there is no need for
  the empty case to do the type conversion.

Note [Join points]
~~~~~~~~~~~~~~~~~~
In Core, a *join point* is a specially tagged function whose only occurrences
are saturated tail calls. A tail call can appear in these places:

  1. In the branches (not the scrutinee) of a case
  2. Underneath a let (value or join point)
  3. Inside another join point

We write a join-point declaration as
  join j @a @b x y = e1 in e2,
like a let binding but with "join" instead (or "join rec" for "let rec"). Note
that we put the parameters before the = rather than using lambdas; this is
because it's relevant how many parameters the join point takes *as a join
point.* This number is called the *join arity,* distinct from arity because it
counts types as well as values. Note that a join point may return a lambda! So
  join j x = x + 1
is different from
  join j = \x -> x + 1
The former has join arity 1, while the latter has join arity 0.

The identifier for a join point is called a join id or a *label.* An invocation
is called a *jump.* We write a jump using the jump keyword:

  jump j 3

The words *label* and *jump* are evocative of assembly code (or Cmm) for a
reason: join points are indeed compiled as labeled blocks, and jumps become
actual jumps (plus argument passing and stack adjustment). There is no closure
allocated and only a fraction of the function-call overhead. Hence we would
like as many functions as possible to become join points (see OccurAnal) and
the type rules for join points ensure we preserve the properties that make them
efficient.

In the actual AST, a join point is indicated by the IdDetails of the binder: a
local value binding gets 'VanillaId' but a join point gets a 'JoinId' with its
join arity.

For more details, see the paper:

  Luke Maurer, Paul Downen, Zena Ariola, and Simon Peyton Jones. "Compiling
  without continuations." Submitted to PLDI'17.

  https://www.microsoft.com/en-us/research/publication/compiling-without-continuations/

Note [Invariants on join points]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Join points must follow these invariants:

  1. All occurrences must be tail calls. Each of these tail calls must pass the
     same number of arguments, counting both types and values; we call this the
     "join arity" (to distinguish from regular arity, which only counts values).

     See Note [Join points are less general than the paper]

  2. For join arity n, the right-hand side must begin with at least n lambdas.
     No ticks, no casts, just lambdas!  C.f. GHC.Core.Utils.joinRhsArity.

     2a. Moreover, this same constraint applies to any unfolding of
         the binder.  Reason: if we want to push a continuation into
         the RHS we must push it into the unfolding as well.

     2b. The Arity (in the IdInfo) of a join point varies independently of the
         join-arity. For example, we could have
             j x = case x of { T -> \y.y; F -> \y.3 }
         Its join-arity is 1, but its idArity is 2; and we do not eta-expand
         join points: see Note [Do not eta-expand join points] in
                          GHC.Core.Opt.Simplify.Utils.

         Allowing the idArity to be bigger than the join-arity is
         important in arityType; see GHC.Core.Opt.Arity
         Note [Arity for recursive join bindings]

         Historical note: see #17294.

  3. If the binding is recursive, then all other bindings in the recursive group
     must also be join points.

  4. The binding's type must not be polymorphic in its return type (as defined
     in Note [The polymorphism rule of join points]).

However, join points have simpler invariants in other ways

  5. A join point can have an unboxed type without the RHS being
     ok-for-speculation (i.e. drop the let-can-float invariant)
     e.g.  let j :: Int# = factorial x in ...

  6. The RHS of join point is not required to have a fixed runtime representation,
     e.g.  let j :: r :: TYPE l = fail (##) in ...
     This happened in an intermediate program #13394

Examples:

  join j1  x = 1 + x in jump j (jump j x)  -- Fails 1: non-tail call
  join j1' x = 1 + x in if even a
                          then jump j1 a
                          else jump j1 a b -- Fails 1: inconsistent calls
  join j2  x = flip (+) x in j2 1 2        -- Fails 2: not enough lambdas
  join j2' x = \y -> x + y in j3 1         -- Passes: extra lams ok
  join j @a (x :: a) = x                   -- Fails 4: polymorphic in ret type

Invariant 1 applies to left-hand sides of rewrite rules, so a rule for a join
point must have an exact call as its LHS.

Strictly speaking, invariant 3 is redundant, since a call from inside a lazy
binding isn't a tail call. Since a let-bound value can't invoke a free join
point, then, they can't be mutually recursive. (A Core binding group *can*
include spurious extra bindings if the occurrence analyser hasn't run, so
invariant 3 does still need to be checked.) For the rigorous definition of
"tail call", see Section 3 of the paper (Note [Join points]).

Invariant 4 is subtle; see Note [The polymorphism rule of join points].

Invariant 6 is to enable code like this:

  f = \(r :: RuntimeRep) (a :: TYPE r) (x :: T).
      join j :: a
           j = error @r @a "bloop"
      in case x of
           A -> j
           B -> j
           C -> error @r @a "blurp"

Core Lint will check these invariants, anticipating that any binder whose
OccInfo is marked AlwaysTailCalled will become a join point as soon as the
simplifier (or simpleOptPgm) runs.

Note [Join points are less general than the paper]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
In the paper "Compiling without continuations", this expression is
perfectly valid:

    join { j = \_ -> e }
    in (case blah of       )
       (  True  -> j void# ) arg
       (  False -> blah    )

assuming 'j' has arity 1.   Here the call to 'j' does not look like a
tail call, but actually everything is fine. See Section 3, "Managing \Delta"
in the paper.

In GHC, however, we adopt a slightly more restrictive subset, in which
join point calls must be tail calls.  I think we /could/ loosen it up, but
in fact the simplifier ensures that we always get tail calls, and it makes
the back end a bit easier I think.  Generally, just less to think about;
nothing deeper than that.

Note [The type of a join point]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
A join point has the same type it would have as a function. That is, if it takes
an Int and a Bool and its body produces a String, its type is `Int -> Bool ->
String`. Natural as this may seem, it can be awkward. A join point shouldn't be
thought to "return" in the same sense a function does---a jump is one-way. This
is crucial for understanding how case-of-case interacts with join points:

  case (join
          j :: Int -> Bool -> String
          j x y = ...
        in
          jump j z w) of
    "" -> True
    _  -> False

The simplifier will pull the case into the join point (see Note [Join points
and case-of-case] in GHC.Core.Opt.Simplify):

  join
    j :: Int -> Bool -> Bool -- changed!
    j x y = case ... of "" -> True
                        _  -> False
  in
    jump j z w

The body of the join point now returns a Bool, so the label `j` has to
have its type updated accordingly, which is done by
GHC.Core.Opt.Simplify.Env.adjustJoinPointType. Inconvenient though
this may be, it has the advantage that 'GHC.Core.Utils.exprType' can
still return a type for any expression, including a jump.

Relationship to the paper

This plan differs from the paper (see Note [Invariants on join
points]). In the paper, we instead give j the type `Int -> Bool ->
forall a. a`. Then each jump carries the "return type" as a parameter,
exactly the way other non-returning functions like `error` work:

  case (join
          j :: Int -> Bool -> forall a. a
          j x y = ...
        in
          jump j z w @String) of
    "" -> True
    _  -> False

Now we can move the case inward and we only have to change the jump:

  join
    j :: Int -> Bool -> forall a. a
    j x y = case ... of "" -> True
                        _  -> False
  in
    jump j z w @Bool

(Core Lint would still check that the body of the join point has the right type;
that type would simply not be reflected in the join id.)

Note [The polymorphism rule of join points]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Invariant 4 of Note [Invariants on join points] forbids a join point to be
polymorphic in its return type. That is, if its type is

  forall a1 ... ak. t1 -> ... -> tn -> r

where its join arity is k+n, none of the type parameters ai may occur free in r.

In some way, this falls out of the fact that given

  join
     j @a1 ... @ak x1 ... xn = e1
  in e2

then all calls to `j` are in tail-call positions of `e`, and expressions in
tail-call positions in `e` have the same type as `e`.
Therefore the type of `e1` -- the return type of the join point -- must be the
same as the type of e2.
Since the type variables aren't bound in `e2`, its type can't include them, and
thus neither can the type of `e1`.

This unfortunately prevents the `go` in the following code from being a
join-point:

  iter :: forall a. Int -> (a -> a) -> a -> a
  iter @a n f x = go @a n f x
    where
      go :: forall a. Int -> (a -> a) -> a -> a
      go @a 0 _ x = x
      go @a n f x = go @a (n-1) f (f x)

In this case, a static argument transformation would fix that (see
ticket #14620):

  iter :: forall a. Int -> (a -> a) -> a -> a
  iter @a n f x = go' @a n f x
    where
      go' :: Int -> (a -> a) -> a -> a
      go' 0 _ x = x
      go' n f x = go' (n-1) f (f x)

In general, loopification could be employed to do that (see #14068.)

Can we simply drop the requirement, and allow `go` to be a join-point? We
could, and it would work. But we could not longer apply the case-of-join-point
transformation universally. This transformation would do:

  case (join go @a n f x = case n of 0 -> x
                                     n -> go @a (n-1) f (f x)
        in go @Bool n neg True) of
    True -> e1; False -> e2

 ===>

  join go @a n f x = case n of 0 -> case x of True -> e1; False -> e2
                               n -> go @a (n-1) f (f x)
  in go @Bool n neg True

but that is ill-typed, as `x` is type `a`, not `Bool`.


This also justifies why we do not consider the `e` in `e |> co` to be in
tail position: A cast changes the type, but the type must be the same. But
operationally, casts are vacuous, so this is a bit unfortunate! See #14610 for
ideas how to fix this.

************************************************************************
*                                                                      *
            In/Out type synonyms
*                                                                      *
********************************************************************* -}

{- Many passes apply a substitution, and it's very handy to have type
   synonyms to remind us whether or not the substitution has been applied -}

-- Pre-cloning or substitution
type InBndr     = CoreBndr
type InType     = Type
type InKind     = Kind
type InBind     = CoreBind
type InExpr     = CoreExpr
type InAlt      = CoreAlt
type InArg      = CoreArg
type InCoercion = Coercion

-- Post-cloning or substitution
type OutBndr     = CoreBndr
type OutType     = Type
type OutKind     = Kind
type OutCoercion = Coercion
type OutBind     = CoreBind
type OutExpr     = CoreExpr
type OutAlt      = CoreAlt
type OutArg      = CoreArg
type MOutCoercion = MCoercion

{-
************************************************************************
*                                                                      *
                  AltCon
*                                                                      *
************************************************************************
-}

-- The Ord is needed for the FiniteMap used in the lookForConstructor
-- in GHC.Core.Opt.Simplify.Env.  If you declared that lookForConstructor
-- *ignores* constructor-applications with LitArg args, then you could get rid
-- of this Ord.

instance Outputable AltCon where
  ppr (DataAlt dc) = ppr dc
  ppr (LitAlt lit) = ppr lit
  ppr DEFAULT      = text "__DEFAULT"

cmpAlt :: Alt a -> Alt a -> Ordering
cmpAlt (Alt con1 _ _) (Alt con2 _ _) = con1 `cmpAltCon` con2

ltAlt :: Alt a -> Alt a -> Bool
ltAlt a1 a2 = (a1 `cmpAlt` a2) == LT

cmpAltCon :: AltCon -> AltCon -> Ordering
-- ^ Compares 'AltCon's within a single list of alternatives
-- DEFAULT comes out smallest, so that sorting by AltCon puts
-- alternatives in the order required: see Note [Case expression invariants]
cmpAltCon DEFAULT      DEFAULT     = EQ
cmpAltCon DEFAULT      _           = LT

cmpAltCon (DataAlt d1) (DataAlt d2) = dataConTag d1 `compare` dataConTag d2
cmpAltCon (DataAlt _)  DEFAULT      = GT
cmpAltCon (LitAlt  l1) (LitAlt  l2) = l1 `compare` l2
cmpAltCon (LitAlt _)   DEFAULT      = GT

cmpAltCon con1 con2 = pprPanic "cmpAltCon" (ppr con1 $$ ppr con2)

{-
************************************************************************
*                                                                      *
\subsection{Useful synonyms}
*                                                                      *
************************************************************************

Note [CoreProgram]
~~~~~~~~~~~~~~~~~~
The top level bindings of a program, a CoreProgram, are represented as
a list of CoreBind

 * Later bindings in the list can refer to earlier ones, but not vice
   versa.  So this is OK
      NonRec { x = 4 }
      Rec { p = ...q...x...
          ; q = ...p...x }
      Rec { f = ...p..x..f.. }
      NonRec { g = ..f..q...x.. }
   But it would NOT be ok for 'f' to refer to 'g'.

 * The occurrence analyser does strongly-connected component analysis
   on each Rec binding, and splits it into a sequence of smaller
   bindings where possible.  So the program typically starts life as a
   single giant Rec, which is then dependency-analysed into smaller
   chunks.
-}

-- If you edit this type, you may need to update the GHC formalism
-- See Note [GHC Formalism] in GHC.Core.Lint
type CoreProgram = [CoreBind]   -- See Note [CoreProgram]

-- | The common case for the type of binders and variables when
-- we are manipulating the Core language within GHC
type CoreBndr = Var
-- | Expressions where binders are 'CoreBndr's
type CoreExpr = Expr CoreBndr
-- | Argument expressions where binders are 'CoreBndr's
type CoreArg  = Arg  CoreBndr
-- | Binding groups where binders are 'CoreBndr's
type CoreBind = Bind CoreBndr
-- | Case alternatives where binders are 'CoreBndr's
type CoreAlt  = Alt  CoreBndr

{-
************************************************************************
*                                                                      *
\subsection{Tagging}
*                                                                      *
************************************************************************
-}

-- | Binders are /tagged/ with a t
data TaggedBndr t = TB CoreBndr t       -- TB for "tagged binder"

type TaggedBind t = Bind (TaggedBndr t)
type TaggedExpr t = Expr (TaggedBndr t)
type TaggedArg  t = Arg  (TaggedBndr t)
type TaggedAlt  t = Alt  (TaggedBndr t)

instance Outputable b => Outputable (TaggedBndr b) where
  ppr (TB b l) = char '<' <> ppr b <> comma <> ppr l <> char '>'

deTagExpr :: TaggedExpr t -> CoreExpr
deTagExpr (Var v)                   = Var v
deTagExpr (Lit l)                   = Lit l
deTagExpr (Type ty)                 = Type ty
deTagExpr (Coercion co)             = Coercion co
deTagExpr (App e1 e2)               = App (deTagExpr e1) (deTagExpr e2)
deTagExpr (Lam (TB b _) e)          = Lam b (deTagExpr e)
deTagExpr (Let bind body)           = Let (deTagBind bind) (deTagExpr body)
deTagExpr (Case e (TB b _) ty alts) = Case (deTagExpr e) b ty (map deTagAlt alts)
deTagExpr (Tick t e)                = Tick t (deTagExpr e)
deTagExpr (Cast e co)               = Cast (deTagExpr e) co

deTagBind :: TaggedBind t -> CoreBind
deTagBind (NonRec (TB b _) rhs) = NonRec b (deTagExpr rhs)
deTagBind (Rec prs)             = Rec [(b, deTagExpr rhs) | (TB b _, rhs) <- prs]

deTagAlt :: TaggedAlt t -> CoreAlt
deTagAlt (Alt con bndrs rhs) = Alt con [b | TB b _ <- bndrs] (deTagExpr rhs)

{-
************************************************************************
*                                                                      *
\subsection{Core-constructing functions with checking}
*                                                                      *
************************************************************************
-}

-- | Apply a list of argument expressions to a function expression in a nested fashion. Prefer to
-- use 'GHC.Core.Make.mkCoreApps' if possible
mkApps    :: Expr b -> [Arg b]  -> Expr b
-- | Apply a list of type argument expressions to a function expression in a nested fashion
mkTyApps  :: Expr b -> [Type]   -> Expr b
-- | Apply a list of coercion argument expressions to a function expression in a nested fashion
mkCoApps  :: Expr b -> [Coercion] -> Expr b
-- | Apply a list of type or value variables to a function expression in a nested fashion
mkVarApps :: Expr b -> [Var] -> Expr b
-- | Apply a list of argument expressions to a data constructor in a nested fashion. Prefer to
-- use 'GHC.Core.Make.mkCoreConApps' if possible
mkConApp      :: DataCon -> [Arg b] -> Expr b

mkApps    f args = foldl' App                       f args
mkCoApps  f args = foldl' (\ e a -> App e (Coercion a)) f args
mkVarApps f vars = foldl' (\ e a -> App e (varToCoreExpr a)) f vars
mkConApp con args = mkApps (Var (dataConWorkId con)) args

mkTyApps  f args = foldl' (\ e a -> App e (mkTyArg a)) f args

mkConApp2 :: DataCon -> [Type] -> [Var] -> Expr b
mkConApp2 con tys arg_ids = Var (dataConWorkId con)
                            `mkApps` map Type tys
                            `mkApps` map varToCoreExpr arg_ids

mkTyArg :: Type -> Expr b
mkTyArg ty
  | Just co <- isCoercionTy_maybe ty = Coercion co
  | otherwise                        = Type ty

-- | Create a machine integer literal expression of type @Int#@ from an @Integer@.
-- If you want an expression of type @Int@ use 'GHC.Core.Make.mkIntExpr'
mkIntLit :: Platform -> Integer -> Expr b
mkIntLit platform n = Lit (mkLitInt platform n)

-- | Create a machine integer literal expression of type @Int#@ from an
-- @Integer@, wrapping if necessary.
-- If you want an expression of type @Int@ use 'GHC.Core.Make.mkIntExpr'
mkIntLitWrap :: Platform -> Integer -> Expr b
mkIntLitWrap platform n = Lit (mkLitIntWrap platform n)

-- | Create a machine word literal expression of type  @Word#@ from an @Integer@.
-- If you want an expression of type @Word@ use 'GHC.Core.Make.mkWordExpr'
mkWordLit :: Platform -> Integer -> Expr b
mkWordLit platform w = Lit (mkLitWord platform w)

-- | Create a machine word literal expression of type  @Word#@ from an
-- @Integer@, wrapping if necessary.
-- If you want an expression of type @Word@ use 'GHC.Core.Make.mkWordExpr'
mkWordLitWrap :: Platform -> Integer -> Expr b
mkWordLitWrap platform w = Lit (mkLitWordWrap platform w)

mkWord8Lit :: Integer -> Expr b
mkWord8Lit    w = Lit (mkLitWord8 w)

mkWord64LitWord64 :: Word64 -> Expr b
mkWord64LitWord64 w = Lit (mkLitWord64 (toInteger w))

mkInt64LitInt64 :: Int64 -> Expr b
mkInt64LitInt64 w = Lit (mkLitInt64 (toInteger w))

-- | Create a machine character literal expression of type @Char#@.
-- If you want an expression of type @Char@ use 'GHC.Core.Make.mkCharExpr'
mkCharLit :: Char -> Expr b
-- | Create a machine string literal expression of type @Addr#@.
-- If you want an expression of type @String@ use 'GHC.Core.Make.mkStringExpr'
mkStringLit :: String -> Expr b

mkCharLit   c = Lit (mkLitChar c)
mkStringLit s = Lit (mkLitString s)

-- | Create a machine single precision literal expression of type @Float#@ from a @Rational@.
-- If you want an expression of type @Float@ use 'GHC.Core.Make.mkFloatExpr'
mkFloatLit :: Rational -> Expr b
-- | Create a machine single precision literal expression of type @Float#@ from a @Float@.
-- If you want an expression of type @Float@ use 'GHC.Core.Make.mkFloatExpr'
mkFloatLitFloat :: Float -> Expr b

mkFloatLit      f = Lit (mkLitFloat f)
mkFloatLitFloat f = Lit (mkLitFloat (toRational f))

-- | Create a machine double precision literal expression of type @Double#@ from a @Rational@.
-- If you want an expression of type @Double@ use 'GHC.Core.Make.mkDoubleExpr'
mkDoubleLit :: Rational -> Expr b
-- | Create a machine double precision literal expression of type @Double#@ from a @Double@.
-- If you want an expression of type @Double@ use 'GHC.Core.Make.mkDoubleExpr'
mkDoubleLitDouble :: Double -> Expr b

mkDoubleLit       d = Lit (mkLitDouble d)
mkDoubleLitDouble d = Lit (mkLitDouble (toRational d))

-- | Bind all supplied binding groups over an expression in a nested let expression. Assumes
-- that the rhs satisfies the let-can-float invariant.  Prefer to use
-- 'GHC.Core.Make.mkCoreLets' if possible, which does guarantee the invariant
mkLets        :: [Bind b] -> Expr b -> Expr b
-- | Bind all supplied binders over an expression in a nested lambda expression. Prefer to
-- use 'GHC.Core.Make.mkCoreLams' if possible
mkLams        :: [b] -> Expr b -> Expr b

mkLams binders body = foldr Lam body binders
mkLets binds body   = foldr mkLet body binds

mkLet :: Bind b -> Expr b -> Expr b
-- The desugarer sometimes generates an empty Rec group
-- which Lint rejects, so we kill it off right away
mkLet (Rec []) body = body
mkLet bind     body = Let bind body

-- | @mkLetNonRec bndr rhs body@ wraps @body@ in a @let@ binding @bndr@.
mkLetNonRec :: b -> Expr b -> Expr b -> Expr b
mkLetNonRec b rhs body = Let (NonRec b rhs) body

-- | @mkLetRec binds body@ wraps @body@ in a @let rec@ with the given set of
-- @binds@ if binds is non-empty.
mkLetRec :: [(b, Expr b)] -> Expr b -> Expr b
mkLetRec [] body = body
mkLetRec bs body = Let (Rec bs) body

-- | Create a binding group where a type variable is bound to a type.
-- Per Note [Core type and coercion invariant],
-- this can only be used to bind something in a non-recursive @let@ expression
mkTyBind :: TyVar -> Type -> CoreBind
mkTyBind tv ty      = NonRec tv (Type ty)

-- | Create a binding group where a type variable is bound to a type.
-- Per Note [Core type and coercion invariant],
-- this can only be used to bind something in a non-recursive @let@ expression
mkCoBind :: CoVar -> Coercion -> CoreBind
mkCoBind cv co      = NonRec cv (Coercion co)

-- | Convert a binder into either a 'Var' or 'Type' 'Expr' appropriately
varToCoreExpr :: CoreBndr -> Expr b
varToCoreExpr v | isTyVar v = Type (mkTyVarTy v)
                | isCoVar v = Coercion (mkCoVarCo v)
                | otherwise = assert (isId v) $ Var v

varsToCoreExprs :: [CoreBndr] -> [Expr b]
varsToCoreExprs vs = map varToCoreExpr vs

{-
************************************************************************
*                                                                      *
   Getting a result type
*                                                                      *
************************************************************************

These are defined here to avoid a module loop between GHC.Core.Utils and GHC.Core.FVs

-}

-- | If the expression is a 'Type', converts. Otherwise,
-- panics. NB: This does /not/ convert 'Coercion' to 'CoercionTy'.
exprToType :: CoreExpr -> Type
exprToType (Type ty)     = ty
exprToType _bad          = pprPanic "exprToType" empty

{-
************************************************************************
*                                                                      *
\subsection{Simple access functions}
*                                                                      *
************************************************************************
-}

-- | Extract every variable by this group
bindersOf  :: Bind b -> [b]
-- If you edit this function, you may need to update the GHC formalism
-- See Note [GHC Formalism] in GHC.Core.Lint
bindersOf (NonRec binder _) = [binder]
bindersOf (Rec pairs)       = [binder | (binder, _) <- pairs]

-- | 'bindersOf' applied to a list of binding groups
bindersOfBinds :: [Bind b] -> [b]
bindersOfBinds binds = foldr ((++) . bindersOf) [] binds

-- We inline this to avoid unknown function calls.
{-# INLINE foldBindersOfBindStrict #-}
foldBindersOfBindStrict :: (a -> b -> a) -> a -> Bind b -> a
foldBindersOfBindStrict f
  = \z bind -> case bind of
      NonRec b _rhs -> f z b
      Rec pairs -> foldl' f z $ map fst pairs

{-# INLINE foldBindersOfBindsStrict #-}
foldBindersOfBindsStrict :: (a -> b -> a) -> a -> [Bind b] -> a
foldBindersOfBindsStrict f = \z binds -> foldl' fold_bind z binds
  where
    fold_bind = (foldBindersOfBindStrict f)


rhssOfBind :: Bind b -> [Expr b]
rhssOfBind (NonRec _ rhs) = [rhs]
rhssOfBind (Rec pairs)    = [rhs | (_,rhs) <- pairs]

rhssOfAlts :: [Alt b] -> [Expr b]
rhssOfAlts alts = [e | Alt _ _ e <- alts]

-- | Collapse all the bindings in the supplied groups into a single
-- list of lhs\/rhs pairs suitable for binding in a 'Rec' binding group
flattenBinds :: [Bind b] -> [(b, Expr b)]
flattenBinds (NonRec b r : binds) = (b,r) : flattenBinds binds
flattenBinds (Rec prs1   : binds) = prs1 ++ flattenBinds binds
flattenBinds []                   = []

-- | We often want to strip off leading lambdas before getting down to
-- business. Variants are 'collectTyBinders', 'collectValBinders',
-- and 'collectTyAndValBinders'
collectBinders         :: Expr b   -> ([b],     Expr b)
collectTyBinders       :: CoreExpr -> ([TyVar], CoreExpr)
collectValBinders      :: CoreExpr -> ([Id],    CoreExpr)
collectTyAndValBinders :: CoreExpr -> ([TyVar], [Id], CoreExpr)

-- | Strip off exactly N leading lambdas (type or value).
-- Good for use with join points.
-- Panic if there aren't enough
collectNBinders :: JoinArity -> Expr b -> ([b], Expr b)

collectBinders expr
  = go [] expr
  where
    go bs (Lam b e) = go (b:bs) e
    go bs e          = (reverse bs, e)

collectTyBinders expr
  = go [] expr
  where
    go tvs (Lam b e) | isTyVar b = go (b:tvs) e
    go tvs e                     = (reverse tvs, e)

collectValBinders expr
  = go [] expr
  where
    go ids (Lam b e) | isId b = go (b:ids) e
    go ids body               = (reverse ids, body)

collectTyAndValBinders expr
  = (tvs, ids, body)
  where
    (tvs, body1) = collectTyBinders expr
    (ids, body)  = collectValBinders body1

collectNBinders orig_n orig_expr
  = go orig_n [] orig_expr
  where
    go 0 bs expr      = (reverse bs, expr)
    go n bs (Lam b e) = go (n-1) (b:bs) e
    go _ _  _         = pprPanic "collectNBinders" $ int orig_n

-- | Strip off exactly N leading value lambdas
-- returning all the binders found up to that point
-- Return Nothing if there aren't enough
collectNValBinders_maybe :: Arity -> CoreExpr -> Maybe ([Var], CoreExpr)
collectNValBinders_maybe orig_n orig_expr
  = go orig_n [] orig_expr
  where
    go 0 bs expr      = Just (reverse bs, expr)
    go n bs (Lam b e) | isId b    = go (n-1) (b:bs) e
                      | otherwise = go n     (b:bs) e
    go _ _  _         = Nothing

-- | Takes a nested application expression and returns the function
-- being applied and the arguments to which it is applied
collectArgs :: Expr b -> (Expr b, [Arg b])
collectArgs expr
  = go expr []
  where
    go (App f a) as = go f (a:as)
    go e         as = (e, as)

-- | Takes a nested application expression and returns the function
-- being applied. Looking through casts and ticks to find it.
collectFunSimple :: Expr b -> Expr b
collectFunSimple expr
  = go expr
  where
    go expr' =
      case expr' of
        App f _a    -> go f
        Tick _t e   -> go e
        Cast e _co  -> go e
        e           -> e

-- | fmap on the body of a lambda.
--   wrapLamBody f (\x -> body) == (\x -> f body)
wrapLamBody :: (CoreExpr -> CoreExpr) -> CoreExpr -> CoreExpr
wrapLamBody f expr = go expr
  where
  go (Lam v body) = Lam v $ go body
  go expr = f expr

-- | Attempt to remove the last N arguments of a function call.
-- Strip off any ticks or coercions encountered along the way and any
-- at the end.
stripNArgs :: Word -> Expr a -> Maybe (Expr a)
stripNArgs !n (Tick _ e) = stripNArgs n e
stripNArgs n (Cast f _) = stripNArgs n f
stripNArgs 0 e = Just e
stripNArgs n (App f _) = stripNArgs (n - 1) f
stripNArgs _ _ = Nothing

-- | Like @collectArgs@, but also collects looks through floatable
-- ticks if it means that we can find more arguments.
collectArgsTicks :: (CoreTickish -> Bool) -> Expr b
                 -> (Expr b, [Arg b], [CoreTickish])
collectArgsTicks skipTick expr
  = go expr [] []
  where
    go (App f a)  as ts = go f (a:as) ts
    go (Tick t e) as ts
      | skipTick t      = go e as (t:ts)
    go e          as ts = (e, as, reverse ts)


{-
************************************************************************
*                                                                      *
\subsection{Predicates}
*                                                                      *
************************************************************************

At one time we optionally carried type arguments through to runtime.
@isRuntimeVar v@ returns if (Lam v _) really becomes a lambda at runtime,
i.e. if type applications are actual lambdas because types are kept around
at runtime.  Similarly isRuntimeArg.
-}

-- | Will this variable exist at runtime?
isRuntimeVar :: Var -> Bool
isRuntimeVar = isId

-- | Will this argument expression exist at runtime?
isRuntimeArg :: CoreExpr -> Bool
isRuntimeArg = isValArg

-- | Returns @True@ for value arguments, false for type args
-- NB: coercions are value arguments (zero width, to be sure,
-- like State#, but still value args).
isValArg :: Expr b -> Bool
isValArg e = not (isTypeArg e)

-- | Returns @True@ iff the expression is a 'Type' or 'Coercion'
-- expression at its top level
isTyCoArg :: Expr b -> Bool
isTyCoArg (Type {})     = True
isTyCoArg (Coercion {}) = True
isTyCoArg _             = False

-- | Returns @True@ iff the expression is a 'Coercion'
-- expression at its top level
isCoArg :: Expr b -> Bool
isCoArg (Coercion {}) = True
isCoArg _             = False

-- | Returns @True@ iff the expression is a 'Type' expression at its
-- top level.  Note this does NOT include 'Coercion's.
isTypeArg :: Expr b -> Bool
isTypeArg (Type {}) = True
isTypeArg _         = False

-- | The number of binders that bind values rather than types
valBndrCount :: [CoreBndr] -> Int
valBndrCount = count isId

-- | The number of argument expressions that are values rather than types at their top level
valArgCount :: [Arg b] -> Int
valArgCount = count isValArg