module Data.Layout.Language (
    
      repeat
    , offset
    , group
    
    , word8
    , word16le
    , word32le
    , word64le
    , word16be
    , word32be
    , word64be
    
    , optimize
    
    , size
    , byteOrder
    , valueSize1
    , valueSizeN
    , valueCount
    , chunk
    ) where
import Prelude hiding (repeat)
import Data.Layout.Internal
repeat :: Reps -> Layout -> Layout
repeat n | n > 1     = Repeat n
         | n == 1    = id
         | otherwise = invalid "repeat" "repetition must be at least 1"
offset :: Bytes -> Layout -> Layout
offset n | n > 0     = Offset n
         | n == 0    = id
         | otherwise = invalid "offset" "must skip 0 or more bytes"
group :: Bytes -> Layout -> Layout
group n xs | n <= 0      = invalid "group" "must contain 1 or more bytes"
           | n < size xs = invalid "group" "cannot be smaller than the inner layout"
           | otherwise   = Group n xs
invalid :: String -> String -> a
invalid fn msg = error ("Data.Layout.Language." ++ fn ++ ": " ++ msg)
word8 :: Layout
word8 = Value Word8
word16le :: Layout
word16le = Value Word16le
word32le :: Layout
word32le = Value Word32le
word64le :: Layout
word64le = Value Word64le
word16be :: Layout
word16be = Value Word16be
word32be :: Layout
word32be = Value Word32be
word64be :: Layout
word64be = Value Word64be
formatSize :: ValueFormat -> Bytes
formatSize Word8    = 1
formatSize Word16le = 2
formatSize Word32le = 4
formatSize Word64le = 8
formatSize Word16be = 2
formatSize Word32be = 4
formatSize Word64be = 8
formatByteOrder :: ValueFormat -> ByteOrder
formatByteOrder Word8    = NoByteOrder
formatByteOrder Word16le = LittleEndian
formatByteOrder Word32le = LittleEndian
formatByteOrder Word64le = LittleEndian
formatByteOrder Word16be = BigEndian
formatByteOrder Word32be = BigEndian
formatByteOrder Word64be = BigEndian
data GroupStatus = NoGroup | GotGroup
optimizeGroups :: Layout -> Layout
optimizeGroups = go NoGroup
  where
    
    go NoGroup  (Group n xs) = Group n (go GotGroup xs)
    
    go GotGroup (Group _ xs) = go GotGroup xs
    
    go _       (Repeat n xs) = Repeat n (go NoGroup xs)
    
    go status x              = mapInner (go status) x
optimizeOffsets :: Layout -> Layout
optimizeOffsets = go
  where
    go (Offset n (Offset m xs)) = go (Offset (n + m) xs)
    go x                        = mapInner go x
optimize :: Layout -> Layout
optimize = optimizeOffsets . optimizeGroups
size :: Layout -> Int
size (Value  x)    = formatSize x
size (Offset x xs) = x + size xs
size (Group  x _)  = x
size (Repeat n xs) = n * size xs
valueFormat :: Layout -> ValueFormat
valueFormat (Value fmt)   = fmt
valueFormat (Offset _ xs) = valueFormat xs
valueFormat (Group  _ xs) = valueFormat xs
valueFormat (Repeat _ xs) = valueFormat xs
byteOrder :: Layout -> ByteOrder
byteOrder = formatByteOrder . valueFormat
valueSize1 :: Layout -> Int
valueSize1 = formatSize . valueFormat
valueSizeN :: Layout -> Int
valueSizeN x = valueSize1 x * valueCount x
valueCount :: Layout -> Int
valueCount (Value  _)    = 1
valueCount (Offset _ xs) = valueCount xs
valueCount (Group  _ xs) = valueCount xs
valueCount (Repeat n xs) = valueCount xs * n
mapInner :: (Layout -> Layout) -> Layout -> Layout
mapInner _ (Value fmt)   = Value fmt
mapInner f (Offset n xs) = Offset n (f xs)
mapInner f (Group  n xs) = Group  n (f xs)
mapInner f (Repeat n xs) = Repeat n (f xs)
chunk :: Int -> Layout -> [Layout]
chunk n (Repeat m xs) = replicate (m `div` n) (Repeat n xs) ++ [Repeat (m `rem` n) xs]
chunk _ xs            = [xs]