{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE UndecidableInstances #-} module System.Random.OneLiner.Internal ( Pair(..) , dePair , State(..) ) where data Pair a = Pair !a !a deriving a -> Pair b -> Pair a (a -> b) -> Pair a -> Pair b (forall a b. (a -> b) -> Pair a -> Pair b) -> (forall a b. a -> Pair b -> Pair a) -> Functor Pair forall a b. a -> Pair b -> Pair a forall a b. (a -> b) -> Pair a -> Pair b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: a -> Pair b -> Pair a $c<$ :: forall a b. a -> Pair b -> Pair a fmap :: (a -> b) -> Pair a -> Pair b $cfmap :: forall a b. (a -> b) -> Pair a -> Pair b Functor dePair :: Pair a -> (a, a) dePair :: Pair a -> (a, a) dePair (Pair a x a y) = (a x, a y) {-# INLINE dePair #-} newtype State s a = State { State s a -> s -> (a, s) runState :: s -> (a, s) } deriving a -> State s b -> State s a (a -> b) -> State s a -> State s b (forall a b. (a -> b) -> State s a -> State s b) -> (forall a b. a -> State s b -> State s a) -> Functor (State s) forall a b. a -> State s b -> State s a forall a b. (a -> b) -> State s a -> State s b forall s a b. a -> State s b -> State s a forall s a b. (a -> b) -> State s a -> State s b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: a -> State s b -> State s a $c<$ :: forall s a b. a -> State s b -> State s a fmap :: (a -> b) -> State s a -> State s b $cfmap :: forall s a b. (a -> b) -> State s a -> State s b Functor instance Applicative (State s) where pure :: a -> State s a pure a x = (s -> (a, s)) -> State s a forall s a. (s -> (a, s)) -> State s a State (a x,) {-# INLINE pure #-} State s (a -> b) sf <*> :: State s (a -> b) -> State s a -> State s b <*> State s a sx = (s -> (b, s)) -> State s b forall s a. (s -> (a, s)) -> State s a State ((s -> (b, s)) -> State s b) -> (s -> (b, s)) -> State s b forall a b. (a -> b) -> a -> b $ \s s0 -> let (a -> b f, !s s1) = State s (a -> b) -> s -> (a -> b, s) forall s a. State s a -> s -> (a, s) runState State s (a -> b) sf s s0 (a x, !s s2) = State s a -> s -> (a, s) forall s a. State s a -> s -> (a, s) runState State s a sx s s1 in (a -> b f a x, s s2) {-# INLINE (<*>) #-} instance Monad (State s) where return :: a -> State s a return a x = (s -> (a, s)) -> State s a forall s a. (s -> (a, s)) -> State s a State (a x,) {-# INLINE return #-} State s a sx >>= :: State s a -> (a -> State s b) -> State s b >>= a -> State s b f = (s -> (b, s)) -> State s b forall s a. (s -> (a, s)) -> State s a State ((s -> (b, s)) -> State s b) -> (s -> (b, s)) -> State s b forall a b. (a -> b) -> a -> b $ \s s0 -> let (a x, !s s1) = State s a -> s -> (a, s) forall s a. State s a -> s -> (a, s) runState State s a sx s s0 in State s b -> s -> (b, s) forall s a. State s a -> s -> (a, s) runState (a -> State s b f a x) s s1 {-# INLINE (>>=) #-}