Skip to content

Commit

Permalink
Wrapped instance for Point
Browse files Browse the repository at this point in the history
  • Loading branch information
bergey committed Jan 24, 2014
1 parent e49ec1c commit 08257dd
Showing 1 changed file with 11 additions and 3 deletions.
14 changes: 11 additions & 3 deletions src/Diagrams/Core/Points.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@
{-# LANGUAGE TypeFamilies
#-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
-- Should probably move Wrapped instance upstream
{-# OPTIONS_GHC -fno-warn-orphans #-}
-----------------------------------------------------------------------------
-- |
-- Module : Diagrams.Core.Points
Expand All @@ -18,11 +21,16 @@ module Diagrams.Core.Points

) where

import Control.Lens (Wrapped(..), iso)

-- We just import from Data.AffineSpace.Point (defined in the
-- vector-space-points package) and re-export. We also define an
-- instance of V for Point here.
import Data.AffineSpace.Point

import Diagrams.Core.V

type instance V (Point v) = v
type instance V (Point v) = v

instance Wrapped v v' (Point v) (Point v') where
wrapped = iso P unPoint

0 comments on commit 08257dd

Please sign in to comment.