module Data.Strictness.HT where {-# INLINE arguments1 #-} arguments1 :: (a -> x) -> a -> x arguments1 :: forall a x. (a -> x) -> a -> x arguments1 a -> x f a a = a -> x f forall a b. (a -> b) -> a -> b $! a a {-# INLINE arguments2 #-} arguments2 :: (a -> b -> x) -> a -> b -> x arguments2 :: forall a b x. (a -> b -> x) -> a -> b -> x arguments2 a -> b -> x f a a b b = (a -> b -> x f forall a b. (a -> b) -> a -> b $! a a) forall a b. (a -> b) -> a -> b $! b b {-# INLINE arguments3 #-} arguments3 :: (a -> b -> c -> x) -> a -> b -> c -> x arguments3 :: forall a b c x. (a -> b -> c -> x) -> a -> b -> c -> x arguments3 a -> b -> c -> x f a a b b c c = ((a -> b -> c -> x f forall a b. (a -> b) -> a -> b $! a a) forall a b. (a -> b) -> a -> b $! b b) forall a b. (a -> b) -> a -> b $! c c {-# INLINE arguments4 #-} arguments4 :: (a -> b -> c -> d -> x) -> a -> b -> c -> d -> x arguments4 :: forall a b c d x. (a -> b -> c -> d -> x) -> a -> b -> c -> d -> x arguments4 a -> b -> c -> d -> x f a a b b c c d d = (((a -> b -> c -> d -> x f forall a b. (a -> b) -> a -> b $! a a) forall a b. (a -> b) -> a -> b $! b b) forall a b. (a -> b) -> a -> b $! c c) forall a b. (a -> b) -> a -> b $! d d {-# INLINE arguments5 #-} arguments5 :: (a -> b -> c -> d -> e -> x) -> a -> b -> c -> d -> e -> x arguments5 :: forall a b c d e x. (a -> b -> c -> d -> e -> x) -> a -> b -> c -> d -> e -> x arguments5 a -> b -> c -> d -> e -> x f a a b b c c d d e e = ((((a -> b -> c -> d -> e -> x f forall a b. (a -> b) -> a -> b $! a a) forall a b. (a -> b) -> a -> b $! b b) forall a b. (a -> b) -> a -> b $! c c) forall a b. (a -> b) -> a -> b $! d d) forall a b. (a -> b) -> a -> b $! e e