Skip to content

Instantly share code, notes, and snippets.

@vincenthz
Last active October 27, 2016 13:20
Show Gist options
  • Save vincenthz/51c0a7f04ae199a28d2249e67a7833ab to your computer and use it in GitHub Desktop.
Save vincenthz/51c0a7f04ae199a28d2249e67a7833ab to your computer and use it in GitHub Desktop.
experiment with rebindable syntax -- Prelude Reboot (like CSS reset)
--
-- Preboot -- Prelude Reboot
--
-- A minimal prelude reboot with better base classes
--
-- * Provide a module to Work with the RebindableSyntax extension
-- * Better classes:
-- * Monad : no return or fail
-- * Enum : hiding fromEnum and toEnum
-- * Number Literal become the Integral class (e.g. Int) or Fractional class (e.g. Double).
-- * Number Literal don't assume any operations apart from being able to be transformed from an integer.
-- * No Num with +,-,*,/,div defined
-- * SignedNumber to deal with negative number (Integral or Fractional)
--
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -Wall -Wno-redundant-constraints #-}
module Preboot
(
-- * Class
Functor(..)
, Applicative(..)
, Monad(..)
, MonadFail(..)
, return
, Integral(..)
, SignedNumber(..)
, Fractional(..)
, IsString(..)
, Prelude.Enum(succ, pred, enumFrom, enumFromTo, enumFromThen, enumFromThenTo)
, EnumI(..)
, toEnumInt
, fromEnumInt
, Prelude.Show(..)
, Prelude.Eq(..)
, Prelude.Ord(..)
, DShow
-- * Types
, Bool(..)
, Char
, Int
, Word
, Integer
, Rational
, FP32
, FP64
, IO
, Maybe(..)
, Either(..)
-- * Basic
, ($)
, (.)
, ifThenElse
) where
import Prelude (Int, Word, Integer, Char, Rational, Float, Double, Bool(..), ($), (.), Maybe(..), Either(..), Eq(..), Ord(..), Enum(..), Functor(..))
import GHC.IO
import Control.Applicative (Applicative(..))
import qualified Prelude
import Data.String (IsString(..))
import Data.Word
import Data.Int
-- | FP32
type FP32 = Float
-- | FP64
type FP64 = Double
-- | Prelude Show alias for easy deriving
type DShow = Prelude.Show
class EnumI a where
type EnumIntegral a
toEnum :: forall i . (Integral i, EnumIntegral a ~ i) => EnumIntegral a -> a
fromEnum :: forall i . (Integral i, EnumIntegral a ~ i) => a -> EnumIntegral a
toEnumInt :: (Enum a, EnumIntegral a ~ Int) => Int -> a
toEnumInt = Prelude.toEnum
fromEnumInt :: (Enum a, EnumIntegral a ~ Int) => a -> Int
fromEnumInt = Prelude.fromEnum
class Applicative m => Monad m where
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
(>>) ma mb = ma >>= \_ -> mb
class Monad m => MonadFail m where
fail :: [Char] -> m a
instance Monad IO where
(>>=) (IO ma) mb = IO (\s1 ->
case ma s1 of
(# s2, a #) ->
case mb a of
IO mbr -> mbr s2)
instance Monad Maybe where
(>>=) Nothing _ = Nothing
(>>=) (Just a) mb = mb a
instance Monad (Either l) where
(>>=) (Left l) _ = Left l
(>>=) (Right r) mb = mb r
instance MonadFail (Either [Char]) where
fail e = Left e
return :: forall (m :: * -> *). Applicative m => forall a. a -> m a
return = pure
class Integral a where
fromInteger :: Integer -> a
class Fractional a where
fromRational :: Rational -> a
instance Integral Integer where
fromInteger a = a
instance Integral Int where
fromInteger a = Prelude.fromInteger a
instance Integral Word where
fromInteger a = Prelude.fromInteger a
instance Integral Word8 where
fromInteger a = Prelude.fromInteger a
instance Integral Word16 where
fromInteger a = Prelude.fromInteger a
instance Integral Word32 where
fromInteger a = Prelude.fromInteger a
instance Integral Word64 where
fromInteger a = Prelude.fromInteger a
instance Integral Int8 where
fromInteger a = Prelude.fromInteger a
instance Integral Int16 where
fromInteger a = Prelude.fromInteger a
instance Integral Int32 where
fromInteger a = Prelude.fromInteger a
instance Integral Int64 where
fromInteger a = Prelude.fromInteger a
instance Fractional Rational where
fromRational a = Prelude.fromRational a
instance Fractional Float where
fromRational a = Prelude.fromRational a
instance Fractional Double where
fromRational a = Prelude.fromRational a
class SignedNumber a where
abs :: a -> a
negate :: a -> a
instance SignedNumber Int where
abs = Prelude.abs
negate = Prelude.negate
instance SignedNumber Integer where
abs = Prelude.abs
negate = Prelude.negate
instance SignedNumber Int8 where
abs = Prelude.abs
negate = Prelude.negate
instance SignedNumber Int16 where
abs = Prelude.abs
negate = Prelude.negate
instance SignedNumber Int32 where
abs = Prelude.abs
negate = Prelude.negate
instance SignedNumber Int64 where
abs = Prelude.abs
negate = Prelude.negate
instance SignedNumber Double where
abs = Prelude.abs
negate = Prelude.negate
instance SignedNumber Float where
abs = Prelude.abs
negate = Prelude.negate
default (Int, Integer, FP64)
ifThenElse :: Bool -> a -> a -> a
ifThenElse True e1 _ = e1
ifThenElse False _ e2 = e2
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment