{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE RebindableSyntax #-} {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedLists #-} {-# LANGUAGE BlockArguments #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PostfixOperators #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UnicodeSyntax #-} --{-# LANGUAGE ApplicativeDo #-} {-# OPTIONS_GHC -Wno-missing-signatures #-} {-# OPTIONS_GHC -Wno-unused-do-bind #-} {-# OPTIONS_GHC -Wno-orphans #-} {-# OPTIONS_GHC -Wno-unused-imports #-} module Symantic.Compta.Lang.Rebindable where --import Data.Map.Strict (Map) --import GHC.Exts (IsList(..)) --import GHC.Num (Integer) --import qualified Control.Monad.Trans.Reader as MT --import qualified Data.Time.Clock as Time import Control.Applicative (Applicative(..)) import Control.Monad (Monad(..)) import Data.Bool (Bool(..)) import Data.Decimal (Decimal) import Data.Foldable (foldr) import Data.Function (($), (.), id) import Data.Functor (Functor, (<$>)) import Data.Int (Int) import Data.Kind import Data.Ratio (Rational) import Data.Semigroup (Semigroup(..)) import Data.String (String) import Data.Typeable import GHC.Stack import GHC.TypeLits (Symbol, ErrorMessage(..)) import Numeric.Natural (Natural) import Prelude (Integer, error) import Text.Show (Show(..)) import qualified Data.List as List import qualified Data.String as String import qualified Data.Time.Calendar as Time import qualified GHC.Exts as GHC import qualified Prelude ifThenElse :: Bool -> a -> a -> a ifThenElse True x _ = x ifThenElse False _ y = y -- * Class 'IsString' -- | Like 'String.IsString' but with an 'HasCallStack' constraint -- to report the location of the 'String'. -- This is to be used with the @OverloadedStrings@ and @RebindableSyntax@ extensions -- to replace literal strings by this 'fromString'. class IsString a where fromString :: HasCallStack => String -> a default fromString :: String.IsString a => HasCallStack => String -> a fromString = String.fromString instance IsString String.String -- * Class 'FromInteger' class FromInteger a where fromInteger :: HasCallStack => Prelude.Integer -> a default fromInteger :: Prelude.Num a => Prelude.Integer -> a fromInteger = Prelude.fromInteger instance FromInteger Int instance FromInteger Integer instance FromInteger Natural instance FromInteger Decimal -- * Class 'FromRational' class FromRational a where fromRational :: HasCallStack => Prelude.Rational -> a default fromRational :: Prelude.Fractional a => Prelude.Rational -> a fromRational = Prelude.fromRational instance FromRational Decimal instance FromRational Rational -- * Class 'IsList' {- class IsList a where type Item a :: Type type Item a = GHC.Item a fromList :: HasCallStack => [Item a] -> a fromListN :: HasCallStack => Prelude.Int -> [Item a] -> a toList :: HasCallStack => a -> [Item a] default fromList :: GHC.Item a ~ Item a => GHC.IsList a => [Item a] -> a default fromListN :: GHC.Item a ~ Item a => GHC.IsList a => Prelude.Int -> [Item a] -> a default toList :: GHC.Item a ~ Item a => GHC.IsList a => a -> [Item a] fromList = GHC.fromList fromListN = GHC.fromListN toList = GHC.toList instance IsList [a] -} class Listable repr where cons :: repr a -> repr [a] -> repr [a] nil :: repr [a] concat :: repr [a] -> repr [a] -> repr [a] class IsList repr where fromList :: HasCallStack => [repr a] -> repr [a] fromListN :: HasCallStack => Int -> [repr a] -> repr [a] --toList :: HasCallStack => repr [a] -> [repr a] {- default fromList :: GHC.Item a ~ Item a => GHC.IsList a => [Item a] -> a default fromListN :: GHC.Item a ~ Item a => GHC.IsList a => Prelude.Int -> [Item a] -> a default toList :: GHC.Item a ~ Item a => GHC.IsList a => a -> [Item a] fromList = GHC.fromList fromListN = GHC.fromListN toList = GHC.toList -} instance Listable repr => IsList repr where fromList = foldr cons nil fromListN n = foldr cons nil --toList = error "toList" {- class Applicative repr where fmap :: (a->b) -> repr a -> repr b pure :: a -> repr a (<*>) :: repr (a->b) -> repr a -> repr b join :: repr (repr a) -> repr a -}