[Haskell-cafe] Partially applied type synonyms
Branimir Maksimovic
branimir.maksimovic at gmail.com
Sat Oct 9 06:25:41 UTC 2021
> On 09.10.2021., at 07:04, Ttt Mmm <amindfv at mailbox.org> wrote:
>
>>
>> On 10/09/2021 4:14 AM Branimir Maksimovic <branimir.maksimovic at gmail.com> wrote:
>>
>>
>> {-# LANGUAGE KindSignatures,FlexibleInstances #-}
>>
>> import Data.IntSet (IntSet)
>> import qualified Data.IntSet as IntSet
>> import Data.Set (Set)
>> import qualified Data.Set as Set
>> import Maybes
>> -- Start with this definition:
>> data Var s x
>> = Var {
>> xs :: s x
>> , getX :: s x -> Maybe x
>> }
>>
>> x :: Var Set Double
>> x = Var (Set.fromList [1,2,3]) Set.lookupMax
>>
>> data Person m
>> = Person {
>> name :: m String
>> , age :: m Int
>> }
>>
>> person0 :: Person (Var Set)
>> person0 = Person {
>> name = Var (Set.fromList ["alice", "bob"]) Set.lookupMin
>> , age = Var (Set.fromList [20,30]) Set.lookupMin
>> }
>>
>> varMay :: Person (Var Set) -> Person Maybe
>> varMay (Person nm ag) =
>> Person (getX nm (xs nm)) (getX ag (xs ag))
>>
>> instance Show (Var' IntSet Int)
>> where
>> show (Var' a b) = show a
>> data Var' a b = Var'{
>> xs' :: a
>> ,getX' :: a -> Maybe b
>> }
>> y :: Var' IntSet Int
>> y = Var' (IntSet.fromList [1,2,3]) (fmap fst . IntSet.minView)
>
> Thanks for this suggestion, but here Var' is defined as a totally separate type than Var, whereas I want/need Var to be defined in terms of Var'.
>
Why, what do mean by that? they are unrelated types as IntSet has one var less then Set?
> Cheers,
> Tom
Greets, Branimir,
>
>> main = print y
>>
>>> On 09.10.2021., at 01:56, Ttt Mmm via Haskell-Cafe <haskell-cafe at haskell.org <mailto:haskell-cafe at haskell.org>> wrote:
>>>
>>> {-# LANGUAGE KindSignatures #-}
>>>
>>> import Data.IntSet (IntSet)
>>> import qualified Data.IntSet as IntSet
>>> import Data.Set (Set)
>>> import qualified Data.Set as Set
>>>
>>> -- Start with this definition:
>>> data Var s x
>>> = Var {
>>> xs :: s x
>>> , getX :: s x -> Maybe x
>>> }
>>>
>>> x :: Var Set Double
>>> x = Var (Set.fromList [1,2,3]) Set.lookupMax
>>>
>>> data Person m
>>> = Person {
>>> name :: m String
>>> , age :: m Int
>>> }
>>>
>>> person0 :: Person (Var Set)
>>> person0 = Person {
>>> name = Var (Set.fromList ["alice", "bob"]) Set.lookupMin
>>> , age = Var (Set.fromList [20,30]) Set.lookupMin
>>> }
>>>
>>> varMay :: Person (Var Set) -> Person Maybe
>>> varMay (Person nm ag) =
>>> Person (getX nm (xs nm)) (getX ag (xs ag))
>>>
>>> -- So far so good. But what if you want to define a version of 'Var' that uses 'IntSet' internally?
>>>
>>> -- An attempt would be to comment out the definition of 'Var' above and instead say:
>>> {-
>>> data Var' sx x
>>> = Var {
>>> xs :: sx
>>> , getX :: sx -> Maybe x
>>> }
>>>
>>> type Var s x = Var' (s x) x
>>>
>>> y :: Var' IntSet Int
>>> y = Var (IntSet.fromList [1,2,3]) (fmap fst . IntSet.minView)
>>> -}
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20211009/0096ab70/attachment.html>
More information about the Haskell-Cafe
mailing list