module Sound.Tidal.ID (ID(..)) where

{-
    ID.hs - Polymorphic pattern identifiers
    Copyright (C) 2020, Alex McLean and contributors

    This library is free software: you can redistribute it and/or modify
    it under the terms of the GNU General Public License as published by
    the Free Software Foundation, either version 3 of the License, or
    (at your option) any later version.

    This library is distributed in the hope that it will be useful,
    but WITHOUT ANY WARRANTY; without even the implied warranty of
    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
    GNU General Public License for more details.

    You should have received a copy of the GNU General Public License
    along with this library.  If not, see <http://www.gnu.org/licenses/>.
-}

import GHC.Exts ( IsString(..) )

-- | Wrapper for literals that can be coerced to a string and used as an identifier.
-- | Similar to Show typeclass, but constrained to strings and integers and designed
-- | so that similar cases (such as 1 and "1") convert to the same value.
newtype ID = ID { ID -> String
fromID :: String } deriving (ID -> ID -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ID -> ID -> Bool
$c/= :: ID -> ID -> Bool
== :: ID -> ID -> Bool
$c== :: ID -> ID -> Bool
Eq, Int -> ID -> ShowS
[ID] -> ShowS
ID -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ID] -> ShowS
$cshowList :: [ID] -> ShowS
show :: ID -> String
$cshow :: ID -> String
showsPrec :: Int -> ID -> ShowS
$cshowsPrec :: Int -> ID -> ShowS
Show, Eq ID
ID -> ID -> Bool
ID -> ID -> Ordering
ID -> ID -> ID
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ID -> ID -> ID
$cmin :: ID -> ID -> ID
max :: ID -> ID -> ID
$cmax :: ID -> ID -> ID
>= :: ID -> ID -> Bool
$c>= :: ID -> ID -> Bool
> :: ID -> ID -> Bool
$c> :: ID -> ID -> Bool
<= :: ID -> ID -> Bool
$c<= :: ID -> ID -> Bool
< :: ID -> ID -> Bool
$c< :: ID -> ID -> Bool
compare :: ID -> ID -> Ordering
$ccompare :: ID -> ID -> Ordering
Ord, ReadPrec [ID]
ReadPrec ID
Int -> ReadS ID
ReadS [ID]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ID]
$creadListPrec :: ReadPrec [ID]
readPrec :: ReadPrec ID
$creadPrec :: ReadPrec ID
readList :: ReadS [ID]
$creadList :: ReadS [ID]
readsPrec :: Int -> ReadS ID
$creadsPrec :: Int -> ReadS ID
Read)


noOv :: String -> a
noOv :: forall a. String -> a
noOv String
meth = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
meth forall a. [a] -> [a] -> [a]
++ String
": not supported for ids"

instance Num ID where
  fromInteger :: Integer -> ID
fromInteger = String -> ID
ID forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
  + :: ID -> ID -> ID
(+) = forall a. String -> a
noOv String
"+"
  * :: ID -> ID -> ID
(*) = forall a. String -> a
noOv String
"*"
  abs :: ID -> ID
abs = forall a. String -> a
noOv String
"abs"
  signum :: ID -> ID
signum = forall a. String -> a
noOv String
"signum"
  (-) = forall a. String -> a
noOv String
"-"

instance IsString ID where
  fromString :: String -> ID
fromString = String -> ID
ID