@@ -285,6 +285,8 @@ unboxedTypeTagFromInt = \case
285
285
3 -> NatTag
286
286
_ -> error " intToUnboxedTypeTag: invalid tag"
287
287
288
+ {- ORMOLU_DISABLE -}
289
+ {- because ormolu-0.7.2.0 can’t handle CPP used within a declaration. -}
288
290
data GClosure comb
289
291
= GPAp
290
292
! CombIx
@@ -306,6 +308,7 @@ data GClosure comb
306
308
| GUnboxedSentinel
307
309
#endif
308
310
deriving stock (Show , Functor , Foldable , Traversable )
311
+ {- ORMOLU_ENABLE -}
309
312
310
313
-- Singleton black hole value to avoid allocation.
311
314
blackHole :: Closure
@@ -802,69 +805,72 @@ alloc = do
802
805
pure $ Stack {ap = - 1 , fp = - 1 , sp = - 1 , ustk, bstk}
803
806
{-# INLINE alloc #-}
804
807
805
- peek :: DebugCallStack => Stack -> IO Val
808
+ {- ORMOLU_DISABLE -}
809
+ {- because ormolu-0.7.2.0 can’t handle CPP used within declarations. -}
810
+
811
+ peek :: (DebugCallStack ) => Stack -> IO Val
806
812
peek stk@ (Stack _ _ sp ustk _) = do
807
813
-- Can't use upeek here because in stack-check mode it will assert that the stack slot is unboxed.
808
814
u <- readByteArray ustk sp
809
815
b <- bpeek stk
810
816
pure (Val u b)
811
817
{-# INLINE peek #-}
812
818
813
- peekI :: DebugCallStack => Stack -> IO Int
819
+ peekI :: ( DebugCallStack ) => Stack -> IO Int
814
820
peekI _stk@ (Stack _ _ sp ustk _) = do
815
821
#ifdef STACK_CHECK
816
822
assertUnboxed _stk 0
817
823
#endif
818
824
readByteArray ustk sp
819
825
{-# INLINE peekI #-}
820
826
821
- peekOffI :: DebugCallStack => Stack -> Off -> IO Int
827
+ peekOffI :: ( DebugCallStack ) => Stack -> Off -> IO Int
822
828
peekOffI _stk@ (Stack _ _ sp ustk _) i = do
823
829
#ifdef STACK_CHECK
824
830
assertUnboxed _stk i
825
831
#endif
826
832
readByteArray ustk (sp - i)
827
833
{-# INLINE peekOffI #-}
828
834
829
- bpeek :: DebugCallStack => Stack -> IO BVal
835
+ bpeek :: ( DebugCallStack ) => Stack -> IO BVal
830
836
bpeek (Stack _ _ sp _ bstk) = readArray bstk sp
831
837
{-# INLINE bpeek #-}
832
838
833
- upeek :: DebugCallStack => Stack -> IO UVal
839
+ upeek :: ( DebugCallStack ) => Stack -> IO UVal
834
840
upeek _stk@ (Stack _ _ sp ustk _) = do
835
841
#ifdef STACK_CHECK
836
842
assertUnboxed _stk 0
837
843
#endif
838
844
readByteArray ustk sp
839
845
{-# INLINE upeek #-}
840
846
841
- peekOff :: DebugCallStack => Stack -> Off -> IO Val
847
+ peekOff :: ( DebugCallStack ) => Stack -> Off -> IO Val
842
848
peekOff stk@ (Stack _ _ sp ustk _) i = do
843
849
-- Can't use upeekOff here because in stack-check mode it will assert that the stack slot is unboxed.
844
850
u <- readByteArray ustk (sp - i)
845
851
b <- bpeekOff stk i
846
852
pure $ Val u b
847
853
{-# INLINE peekOff #-}
848
854
849
- bpeekOff :: DebugCallStack => Stack -> Off -> IO BVal
855
+ bpeekOff :: ( DebugCallStack ) => Stack -> Off -> IO BVal
850
856
bpeekOff (Stack _ _ sp _ bstk) i = readArray bstk (sp - i)
851
857
{-# INLINE bpeekOff #-}
852
858
853
- upeekOff :: DebugCallStack => Stack -> Off -> IO UVal
859
+ upeekOff :: ( DebugCallStack ) => Stack -> Off -> IO UVal
854
860
upeekOff _stk@ (Stack _ _ sp ustk _) i = do
855
861
#ifdef STACK_CHECK
856
862
assertUnboxed _stk i
857
863
#endif
858
864
readByteArray ustk (sp - i)
859
865
{-# INLINE upeekOff #-}
860
866
861
- upokeT :: DebugCallStack => Stack -> UVal -> BVal -> IO ()
867
+ upokeT :: ( DebugCallStack ) => Stack -> UVal -> BVal -> IO ()
862
868
upokeT ! stk@ (Stack _ _ sp ustk _) ! u ! t = do
863
869
bpoke stk t
864
870
writeByteArray ustk sp u
865
871
{-# INLINE upokeT #-}
866
872
867
- poke :: DebugCallStack => Stack -> Val -> IO ()
873
+ poke :: ( DebugCallStack ) => Stack -> Val -> IO ()
868
874
poke _stk@ (Stack _ _ sp ustk bstk) (Val u b) = do
869
875
#ifdef STACK_CHECK
870
876
assertBumped _stk 0
@@ -876,57 +882,57 @@ poke _stk@(Stack _ _ sp ustk bstk) (Val u b) = do
876
882
-- | Sometimes we get back an int from a foreign call which we want to use as a Nat.
877
883
-- If we know it's positive and smaller than 2^63 then we can safely store the Int directly as a Nat without
878
884
-- checks.
879
- unsafePokeIasN :: DebugCallStack => Stack -> Int -> IO ()
885
+ unsafePokeIasN :: ( DebugCallStack ) => Stack -> Int -> IO ()
880
886
unsafePokeIasN stk n = do
881
887
upokeT stk n natTypeTag
882
888
{-# INLINE unsafePokeIasN #-}
883
889
884
890
-- | Store an unboxed tag to later match on.
885
891
-- Often used to indicate the constructor of a data type that's been unpacked onto the stack,
886
892
-- or some tag we're about to branch on.
887
- pokeTag :: DebugCallStack => Stack -> Int -> IO ()
893
+ pokeTag :: ( DebugCallStack ) => Stack -> Int -> IO ()
888
894
pokeTag =
889
895
-- For now we just use ints, but maybe should have a separate type for tags so we can detect if we're leaking them.
890
896
pokeI
891
897
{-# INLINE pokeTag #-}
892
898
893
- peekTag :: DebugCallStack => Stack -> IO Int
899
+ peekTag :: ( DebugCallStack ) => Stack -> IO Int
894
900
peekTag = peekI
895
901
{-# INLINE peekTag #-}
896
902
897
- peekTagOff :: DebugCallStack => Stack -> Off -> IO Int
903
+ peekTagOff :: ( DebugCallStack ) => Stack -> Off -> IO Int
898
904
peekTagOff = peekOffI
899
905
{-# INLINE peekTagOff #-}
900
906
901
- pokeBool :: DebugCallStack => Stack -> Bool -> IO ()
907
+ pokeBool :: ( DebugCallStack ) => Stack -> Bool -> IO ()
902
908
pokeBool stk b =
903
909
poke stk $ if b then trueVal else falseVal
904
910
{-# INLINE pokeBool #-}
905
911
906
912
-- | Store a boxed value.
907
913
-- We don't bother nulling out the unboxed stack,
908
914
-- it's extra work and there's nothing to garbage collect.
909
- bpoke :: DebugCallStack => Stack -> BVal -> IO ()
915
+ bpoke :: ( DebugCallStack ) => Stack -> BVal -> IO ()
910
916
bpoke _stk@ (Stack _ _ sp _ bstk) b = do
911
917
#ifdef STACK_CHECK
912
918
assertBumped _stk 0
913
919
#endif
914
920
writeArray bstk sp b
915
921
{-# INLINE bpoke #-}
916
922
917
- pokeOff :: DebugCallStack => Stack -> Off -> Val -> IO ()
923
+ pokeOff :: ( DebugCallStack ) => Stack -> Off -> Val -> IO ()
918
924
pokeOff stk i (Val u t) = do
919
925
bpokeOff stk i t
920
926
writeByteArray (ustk stk) (sp stk - i) u
921
927
{-# INLINE pokeOff #-}
922
928
923
- upokeOffT :: DebugCallStack => Stack -> Off -> UVal -> BVal -> IO ()
929
+ upokeOffT :: ( DebugCallStack ) => Stack -> Off -> UVal -> BVal -> IO ()
924
930
upokeOffT stk i u t = do
925
931
bpokeOff stk i t
926
932
writeByteArray (ustk stk) (sp stk - i) u
927
933
{-# INLINE upokeOffT #-}
928
934
929
- bpokeOff :: DebugCallStack => Stack -> Off -> BVal -> IO ()
935
+ bpokeOff :: ( DebugCallStack ) => Stack -> Off -> BVal -> IO ()
930
936
bpokeOff _stk@ (Stack _ _ sp _ bstk) i b = do
931
937
#ifdef STACK_CHECK
932
938
assertBumped _stk i
@@ -1171,6 +1177,8 @@ peekOffC _stk@(Stack _ _ sp ustk _) i = do
1171
1177
Char. chr <$> readByteArray ustk (sp - i)
1172
1178
{-# INLINE peekOffC #-}
1173
1179
1180
+ {- ORMOLU_ENABLE -}
1181
+
1174
1182
pokeN :: Stack -> Word64 -> IO ()
1175
1183
pokeN stk@ (Stack _ _ sp ustk _) n = do
1176
1184
bpoke stk natTypeTag
0 commit comments